source: trunk/SOURCES/flottab2-0.7.f90 @ 23

Last change on this file since 23 was 4, checked in by dumas, 10 years ago

initial import GRISLI trunk

File size: 35.1 KB
Line 
1!> \file flottab2-0.7.f90
2!! Module pour determiner les endroits ou la glace
3!! flotte , les iles, et la position du front de glace
4!<
5
6!> \namespace flottab_mod
7!! Determine les endroits ou la glace
8!! flotte , les iles, et la position du front de glace
9!! \author Vincent & Cat
10!! \date 10 juillet 2005
11!! @note Used module
12!! @note   - use module3D_phy
13!! @note   - use module_choix
14!! @todo "nasty Island". If the bedrock is above sealevel force grounded (mk_init)
15!<
16module flottab_mod
17 
18USE module3D_phy
19use module_choix
20
21
22
23 IMPLICIT NONE
24
25 real ::  surnet !< surnet hauteur de glace au dessus de la mer
26 real ::  archim !< test de flottaison
27
28 integer:: itestf
29
30 logical,dimension(nx,ny) ::  gz1mx,gz1my
31 logical,dimension(nx,ny) ::  fl1mx,fl1my
32
33
34 real,dimension(nx,ny) ::  uxs1   !< uxbar a l'entree de flottab
35 real,dimension(nx,ny) ::  uys1   !< uybar a l'entree de flottab
36
37
38 integer pmx,pmy !pm=plus-moins -1 ou 1 pour x et y
39
40
41! Variables pour la determination des differents shelfs/stream
42! (representés comme des taches ou l'on resoud l'eq elliptique)
43!________________________________________________________________
44 integer,parameter               :: n_ta_max=2000!< nombre de tache max
45 integer,dimension(nx,ny)        :: table_out    !< pour les numeros des taches
46 integer,dimension(nx,ny)        :: tablebis     !< pour les numeros des taches
47 integer,dimension(0:n_ta_max)     :: compt        !< contient les equivalence entre les taches
48 integer,dimension(0:n_ta_max)     :: nb_pts_tache !< indique le nombre de points par tache
49 logical,dimension(0:n_ta_max)     :: iceberg      !< T si iceberg, F si calotte posee
50
51 logical,dimension(nx,ny)        :: mask_tache_ij !< masque de travail
52                                                  !< vrai pour toute la tache de i,j
53 integer,dimension(2)            :: smax_coord    !< pour le maxloc des iles
54
55!  Variables pour determiner le point le plus haut (surf)
56!  d'une ile completement stream
57!_________________________________________________________
58
59! icetrim : T si ice stream, F si calotte posee(vertical shear)
60 logical,dimension(n_ta_max) :: icetrim 
61
62 integer ::  ii,jj
63 integer ::  smax_i
64 integer ::  smax_j
65 real    ::  smax_
66 integer ::  numtache
67 integer ::  nb_pt
68contains
69! -----------------------------------------------------------------------------------
70!> SUBROUTINE: flottab()
71!! Cette routine determine les endroits ou la glace
72!! flotte , les iles, et la position du front de glace
73!! @note Il y a 4 sortes de zone
74!! @note    - Pose
75!  @note    - Grounding zone et streams    gzmx et gzmy
76!  @note    - Iles             ilemx, ilemy
77!  @note    - flottant  flot sur le noeud majeur, flotmx sur le noeud mineur
78!>
79       subroutine flottab()
80!
81!                                       Vince 5 Jan 95
82!                                       Modifie 20 Jan 95
83!                                       Modifie le 30 Novembre 98
84!    Passage f90 + determination des fronts Vincent dec 2003
85!    nettoyage et nouvelle détermination de gzmx et gzmy Cat le 10 juillet 2005
86!    Re-nettoyage par Cat en aout 2006.
87!    Le calcul de gzmx et gzmy pour les points intérieurs passe dans la subroutine dragging
88!    pour les points cotiers, toujours fait dans flottab
89!
90!                                       -----------------
91!
92!      Cette routine determine les endroits ou la glace
93!      flotte , les iles, et la position du front de glace
94!
95!      Il y a 4 sortes de zone
96!      Pose
97!      Grounding zone et streams    gzmx et gzmy
98!      Iles             ilemx, ilemy
99!      flottant  flot sur le noeud majeur, flotmx sur le noeud mineur
100
101!   passage dans flottab tous les pas de temps dt  !
102!
103! _________________________________________________________
104
105
106
107if (itracebug.eq.1)  call tracebug(' Entree dans routine flottab')
108
109 SHELFY = .FALSE.
110
111
112! cas particulier des runs paleo ou on impose un masque grounded
113
114 if (igrdline.eq.2) then
115    where ( mk_init(:,:).eq.1)                 ! pose
116       flot(:,:) = .False.
117       H(:,:)=max(H(:,:),(10.+sealevel-Bsoc(:,:))*row/ro)  ! pour avoir archim=10
118       S(:,:) = Bsoc(:,:) + H(:,:) 
119    elsewhere
120       flot(:,:) = .True.
121    end where
122 end if
123
124
125! 1-INITIALISATION
126! ----------------
127! initialisation des variables pour detecter les points qui se mettent
128! a flotter entre 2 dtt
129
130       appel_new_flot=.false.
131       do j=1,ny
132          do i=1,nx
133             new_flot_point(i,j)=.false.
134             new_flotmx(i,j)=.false.
135             new_flotmy(i,j)=.false.
136          enddo
137       enddo
138
139! ICE(:,:)=(H(:,:).gt.1) ! ice=.true. si epaisseur > 1m
140
141      ICE(:,:)=0
142      front(:,:)=0
143      frontfacex(:,:)=0
144      frontfacey(:,:)=0
145      isolx(:,:)=.FALSE.
146      isoly(:,:)=.FALSE.
147      cotemx(:,:)=.false.
148      cotemy(:,:)=.false.
149      boost=.false.
150
151! fin de l'initialisation
152!_____________________________________________________________________
153
154! 2-TESTE LES NOUVEAUX POINTS FLOTTANTS
155! -------------------------------------
156
157
158 do j=1,ny
159   do i=1,nx
160
161      uxs1(i,j)=uxbar(i,j)
162      uys1(i,j)=uybar(i,j)
163
164      archim = Bsoc(i,j)+H(i,j)*ro/row -sealevel
165
166
167arch: if ((ARCHIM.LT.0.).and.(H(I,J).gt.1.E-3)) then    ! le point flotte
168   mk(i,j)=1
169
170
171ex_pose: if ((.not.FLOT(I,J)).and.(isynchro.eq.1)) then  !  il ne flottait pas avant
172            FLOT(I,J)=.true.
173            BOOST=.false.
174
175! Attention :  avec le bloc dessous il faut faire un calcul de flottaison a la lecture
176 
177             if (igrdline.eq.1) then   ! en cas de grounding line prescrite
178                flot(i,j)=.false.
179                H(i,j)=(10.+sealevel-Bsoc(i,j))*row/ro  ! pour avoir archim=10
180                new_flot_point(i,j)=.false.
181             endif
182
183
184
185
186         else                                       ! isynchro=0 ou il flottait déja
187                     
188            if (.not.FLOT(I,J)) then               ! il ne flottait pas (isynchro=0)
189               new_flot_point(i,j)=.true.          ! signale un point qui ne flottait pas
190                                                   ! au pas de temps precedent
191                       flot(i,j)=.true.
192 
193                if (igrdline.eq.1) then   ! en cas de grounding line prescrite
194                    flot(i,j)=.false.
195                    H(i,j)=(10.+sealevel-Bsoc(i,j))*row/ro  ! pour avoir archim=10
196                   new_flot_point(i,j)=.false.
197               endif
198
199            endif
200         endif ex_pose
201
202
203       else                           !    le point ne flotte pas
204mk(i,j)=0
205
206           if(FLOT(I,J)) then         !  mais il flottait avant
207                FLOT(I,J)=.false.
208                BOOST=.false.
209           endif
210       endif arch
211
212!   Si la glace flotte -> PRUDENCE !!!
213!   S et B sont alors determines avec la condition de flottabilite
214
215       if (flot(i,j)) then
216          shelfy = .true.
217         
218          surnet=H(i,j)*(1.-ro/row)
219          S(i,j)=surnet+sealevel
220          B(i,j)=S(i,j)-H(i,j)
221       end if
222
223    end do
224 end do
225
226
227!!$ do i=1,nx
228!!$    do j=1,ny
229!!$       if (flot(i,j)) then
230!!$          mk(i,j)=1
231!!$       else
232!!$          mk(i,j)=0
233!!$       endif
234!!$    end do
235!!$ end do
236
237
238
239
240
241!-----------------------------------------------------------------------
242
243domain_x: do j=1,ny       
244         do i=2,nx
245
246!    3_x    A- NOUVELLE DEFINITION DE FLOTMX, LES POINTS
247!            AYANT UN DES VOISINS FLOTTANTS SONT FLOTMX ET GZMX
248!         -------------------------------------------
249
250!            fl1 est l'ancienne valeur de flotmx
251             gz1mx(i,j)=gzmx(i,j)         !     gz1 est l'ancienne valeur de gzmx
252             fl1mx(i,j)=flotmx(i,j)       !     fl1 est l'ancienne valeur de flotmx
253
254             flotmx(i,j)=flot(i,j).and.flot(i-1,j)
255
256! test pour detecter les nouveaux flotmx entre 2 dtt :
257
258             if (flotmx(i,j).and.(new_flot_point(i,j).or. &
259                new_flot_point(i-1,j))) then
260                appel_new_flot=.true.
261                new_flotmx(i,j)=.true.
262             endif
263
264
265!   premiere determination de gzmx
266!__________________________________________________________________________
267
268! gzmx si un des deux voisins est flottant et l'autre posé
269!                                                                   i-1   i
270             gzmx(i,j)=((flot(i,j).and..not.flot(i-1,j)) & !         F    P
271             .or.(.not.flot(i,j).and.flot(i-1,j)))         !         P    F
272
273!                 A condition d'etre assez proche de la flottaison
274!                 sur le demi noeud condition archim < 100 m
275
276             archim=(Bsoc(i,j)+Bsoc(i-1,j))*0.5-sealevel+ro/row*Hmx(i,j)
277             gzmx(i,j)=gzmx(i,j).and.(archim.le.100.) 
278             cotemx(i,j)=gzmx(i,j)
279
280          end do
281       end do domain_x
282
283if (itracebug.eq.1)  call tracebug('  routine flottab apres domain_x')
284
285!     3_y    B- NOUVELLE DEFINITION DE FLOTMY
286!         --------------------------------
287domain_y: do j=2,ny       
288         do i=1,nx
289
290             gz1my(i,j)=gzmy(i,j)           !       gz1 est l'ancienne valeur de gzmy
291             fl1my(i,j)=flotmy(i,j)         !       fl1 est l'ancienne valeur de flotmy
292
293             flotmy(i,j)=flot(i,j).and.flot(i,j-1)
294
295! test pour detecter les nouveaux flotmy entre 2 dtt :
296
297             if (flotmy(i,j).and.(new_flot_point(i,j).or.     &
298             new_flot_point(i,j-1))) then
299                appel_new_flot=.true.
300                new_flotmy(i,j)=.true.
301             endif
302
303!   premiere determination de gzmy
304!__________________________________________________________________________
305
306! gzmy si un des deux voisins est flottant et l'autre posé
307
308             gzmy(i,j)=((flot(i,j).and..not.flot(i,j-1))          &
309             .or.(.not.flot(i,j).and.flot(i,j-1)))                 
310
311!                 A condition d'etre assez proche de la flottaison
312!                 sur le demi noeud condition archim > 100 m
313
314             archim=(Bsoc(i,j)+Bsoc(i,j-1))*0.5-sealevel+ro/row*Hmy(i,j)
315             gzmy(i,j)=gzmy(i,j).and.(archim.le.100.) 
316             cotemy(i,j)=gzmy(i,j)
317
318          end do
319       end do domain_y
320
321
322
323!-------------------------------------------------------------------------------------
324! attention : pour expériences Heino
325!             gzmy(i,j)=gzmy_heino(i,j)
326!             shelfy=.true.
327!             shelfy=.false.
328!____________________________________________________________________________________
329
330
331!!$
332!!$
333!!$! 4- Condition sur les bords
334!!$
335!!$     
336!!$       do i=2,nx
337!!$         flotmx(i,1) = (flot(i,1).or.flot(i-1,1))
338!!$         flotmy(i,1) = .false.
339!!$       end do
340!!$       
341!!$       do j=2,ny
342!!$          flotmy(1,j) = (flot(1,j).or.flot(1,j-1))
343!!$          flotmx(1,j) = .false.
344!!$       end do
345!!$
346!!$       flotmx(1,1) = .false.
347!!$       flotmy(1,1) = .false.
348!!$
349
350
351!      4- determination des iles
352!      -------------------------
353 
354          ilemx(:,:)=.false.
355          ilemy(:,:)=.false.
356
357!       selon x
358ilesx:  do j=2,ny-1
359           do i=3,nx-2
360!                       F   G   F   
361!                           x
362! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
363            if ((flot(i-1,j).and..not.flot(i,j).and.flot(i+1,j)).and. &
364                (sdx(i,j).LT.1.E-02)) then
365             ilemx(i,j)=.true.
366             ilemx(i+1,j)=.true.
367
368!                      F  G   G   F
369!                         x
370! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
371            else if ((flot(i-1,j).and..not.flot(i,j)                  &
372                .and..not.flot(i+1,j)).and.flot(i+2,j).and.           &
373                 (sdx(i,j).LT.1.E-02.and.sdx(i+1,j).LT.1.E-02)) then
374              ilemx(i,j)=.true.
375              ilemx(i+1,j)=.true.
376              ilemx(i+2,j)=.true.
377
378!                      F   G   G   F
379!                              x
380! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
381            else if ((flot(i-2,j).and..not.flot(i-1,j)                &
382                .and..not.flot(i,j)).and.flot(i+1,j).and.             &
383                 (sdx(i,j).LT.1.E-02.and.sdx(i-1,j).LT.1.E-02)) then
384              ilemx(i-1,j)=.true.
385              ilemx(i,j)=.true.
386              ilemx(i+1,j)=.true.
387
388!                      F   G   G   G    F
389!                              x
390! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
391            else if ((i.lt.nx-2)                                      &
392                .and.(flot(i-2,j).and..not.flot(i-1,j)                &
393                .and..not.flot(i,j)).and..not.flot(i+1,j)             &
394                 .and.flot(i+2,j).and.                                &
395                 (sdx(i,j).LT.1.E-02.and.sdx(i-1,j).LT.1.E-02         &
396                 .and.sdx(i+1,j).LT.1.E-02)) then
397              ilemx(i-1,j)=.true.
398              ilemx(i,j)=.true.
399              ilemx(i+1,j)=.true.
400              ilemx(i+2,j)=.true.
401
402            endif
403
404         end do
405      end do ilesx
406
407!       selon y
408ilesy: do j=3,ny-2
409           do i=2,nx-1
410!                       F   G   F   
411!                           x
412! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
413            if ((flot(i,j-1).and..not.flot(i,j).and.flot(i,j+1)).and. &
414                 (sdy(i,j).LT.1.E-02)) then
415             ilemy(i,j)=.true.
416             ilemy(i,j+1)=.true.
417
418!                      F  G   G   F
419!                         x
420! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
421            else if ((flot(i,j-1).and..not.flot(i,j)                  &
422                .and..not.flot(i,j+1)).and.flot(i,j+2).and.           &
423                 (sdy(i,j).LT.1.E-02.and.sdy(i,j+1).LT.1.E-02)) then
424              ilemy(i,j)=.true.
425              ilemy(i,j+1)=.true.
426              ilemy(i,j+2)=.true.
427
428!                      F   G   G   F
429!                              x
430! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
431            else if ((flot(i,j-2).and..not.flot(i,j-1)                 &
432                .and..not.flot(i,j)).and.flot(i,j+1).and.              &
433                 (sdy(i,j).LT.1.E-02.and.sdy(i,j-1).LT.1.E-02)) then
434              ilemy(i,j-1)=.true.
435              ilemy(i,j)=.true.
436              ilemy(i,j+1)=.true.
437
438!                      F   G   G   G    F
439!                              x
440! modif tof 26/08/02 limite sur la pente (si diff S > 400 m)
441            else if ((j.lt.ny-2)                                      &
442                .and.(flot(i,j-2).and..not.flot(i,j-1)                &
443                .and..not.flot(i,j)).and..not.flot(i,j+1)             &
444                 .and.flot(i,j+2).and.                                &
445                 (sdy(i,j).LT.1.E-02.and.sdy(i,j-1).LT.1.E-02         &
446                 .and.sdy(i,j+1).LT.1.E-02)) then
447              ilemy(i,j-1)=.true.
448              ilemy(i,j)=.true.
449              ilemy(i,j+1)=.true.
450              ilemy(i,j+2)=.true.
451            endif
452         end do
453      end do ilesy
454! fin des iles
455
456!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
457!!$if (itestf.gt.0) then
458!!$   write(6,*) 'dans flottab avant dragging asymetrie sur H  pour time=',time
459!!$   stop
460!!$else
461!!$   write(6,*) 'dans flottab avant dragging pas d asymetrie sur H  pour time=',time
462!!$
463!!$end if
464
465! 5- calcule les noeuds qui sont streams a l'interieur et donne le betamx et betamy
466!----------------------------------------------------------------------------------
467if (iter_beta.eq.0) then
468 Call dragging         
469endif
470if (itracebug.eq.1)  call tracebug(' routine flottab apres call dragging')
471!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
472!!$if (itestf.gt.0) then
473!!$   write(6,*) 'dans flottab apres dragging asymetrie sur H  pour time=',time
474!!$   stop
475!!$else
476!!$   write(6,*) 'dans flottab aapres dragging pas d asymetrie sur H  pour time=',time
477!!$
478!!$end if
479
480!   6- calcule les vitesses des points qui sont devenus gzm
481         
482do j=1,ny
483   do i=2,nx-1
484!      si le point etait posé (non gz) et devient gzmx
485!      definir la direction de la vitesse (moyenne des points)
486
487      if ((.not.gz1mx(i,j)).and.(.not.fl1mx(i,j)).and.gzmx(i,j).and. &
488       (i.gt.2).and.(i.lt.nx))  then
489         uxs1(i,j)=(uxbar(i+1,j)+uxbar(i-1,j))/2.
490      endif
491
492   end do
493end do
494
495do j=2,ny-1
496   do i=1,nx
497!      si le point etait posé (non gz) et devient gzmy
498!      definir la direction de la vitesse (moyenne des points)
499      if ((.not.gz1my(i,j)).and.(.not.fl1my(i,j)).and.gzmy(i,j).and. &
500       (j.gt.2).and.(j.lt.ny))  then
501          uys1(i,j)=(uybar(i,j+1)+uybar(i,j-1))/2.
502       endif
503   
504    end do
505end do
506
507
508
509!  7-On determine finalement la position des noeuds stream ou shelf
510!  -------------------------------------------------------------
511
512if (nt.ge.2) then   ! pour ne pas faire ce calcul lors du premier passage
513   uxbar(:,:)=uxs1(:,:)
514   uybar(:,:)=uys1(:,:) 
515endif
516
517flgzmx(:,:)=(marine.and.(flotmx(:,:).or.gzmx(:,:).or.ilemx(:,:)))   &
518     .or.(.not.marine.and.flotmx(:,:))
519flgzmy(:,:)=(marine.and.(flotmy(:,:).or.gzmy(:,:).or.ilemy(:,:)))   &
520     .or.(.not.marine.and.flotmy(:,:))
521
522
523
524! 8- Pour la fusion basale sous les ice shelves- region proche de la grounding line
525!---------------------------------------------------------------------------------
526!       fbm est vrai si le point est flottant mais un des voisins est pose
527!_________________________________________________________________________
528do j=2,ny-1
529  do i=2,nx-1
530
531! if (i.gt.2.AND.i.lt.nx) then   
532        fbm(i,j)=flot(i,j).and.      & 
533             ((.not.flot(i+1,j)).or.(.not.flot(i,j+1)) &
534             .or.(.not.flot(i-1,j)).or.(.not.flot(i,j-1)))
535!     endif
536  end do
537end do
538
539
540
541!  9-On determine maintenant la position du front de glace
542!  -------------------------------------------------------
543!  C'est ici que l'on determine la position et le type de front
544!       print*,'on est dans flottab pour definir les fronts'
545     
546
547
548!!$do i=3,nx-2
549!!$   do j=3,ny-2
550!!$      if (h(i,j).gt.1.1) ice(i,j)=1       
551!!$   end do
552!!$end do
553
554where (flot(:,:))
555   where (H(:,:).gt.(1.1)) 
556      ice(:,:)=1
557   elsewhere 
558      ice(:,:)=0
559   end where
560elsewhere
561  where (H(:,:).gt.(.1)) 
562      ice(:,:)=1
563   elsewhere 
564      ice(:,:)=0
565   end where
566end where
567
568call DETERMIN_TACHE 
569
570synchro :    if (isynchro.eq.1) then
571!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
572!!$if (itestf.gt.0) then
573!!$   write(6,*) 'dans flottab avant DETERMIN_TACHE  asymetrie sur H  pour time=',time
574!!$   stop
575!!$else
576!!$   write(6,*) 'dans flottab apres  DETERMIN_TACHE pas d asymetrie sur H  pour time=',time
577!!$
578!!$end if
579
580
581!----------------------------------------------!
582!On determine les differents ice strean/shelf  !
583      call DETERMIN_TACHE                      !
584!----------------------------------------------!
585
586
587!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
588!!$if (itestf.gt.0) then
589!!$   write(6,*) 'dans flottab apres DETERMIN_TACHE  asymetrie sur H  pour time=',time
590!!$   stop
591!!$else
592!!$   write(6,*) 'dans flottab apres DETERMIN_TACHE pas d asymetrie sur H  pour time=',time
593!!$
594!!$end if
595
596! / test aurel
597debug_3d(:,:,43)=table_out(:,:)
598
599iceberg(:)=.true.
600do j=1,ny
601   do i=1,nx
602      if(.not.flot(i,j)) then
603         iceberg(table_out(i,j))=.false.
604      end if
605   end do
606end do
607
608do j=1,ny
609   do i=1,nx
610
611      debug_3d(i,j,56)=nb_pts_tache(table_out(i,j))
612      if (iceberg(table_out(i,j))) then
613         debug_3d(i,j,57)=1
614      else
615         debug_3d(i,j,57)=0       
616      end if
617   end do
618end do
619! fin test aurel /
620
621
622!ice(:,:)=0   Attention, voir si ca marche toujours pour l'Antarctique et heminord !
623
624!On compte comme englacé uniquement les calottes dont une partie est posée     
625
626do i=3,nx-2
627   do j=3,ny-2
628test1:  if (.not.iceberg(table_out(i,j))) then ! on est pas sur un iceberg
629         if (nb_pts_tache(table_out(i,j)).ge.1) then
630            ice(i,j)=1
631            if (nb_pts_tache(table_out(i,j)).le.10) then  ! les petites iles sont en sia
632!    write(6,*) 'petite ile ',i,j
633              flgzmx(i,j)=.false.
634               flgzmx(i+1,j)=.false.
635               flgzmy(i,j)=.false.
636               flgzmy(i,j+1)=.false.
637               gzmx(i:i+1,j)=.false.
638               gzmy(i,j:j+1)=.false.
639            endif
640
641
642! ici on est sur une tache non iceberg >= 5 points                       
643! on teste si la tache n'est pas completement ice stream
644
645test2:       if (icetrim(table_out(i,j))) then   ! on a une ile d'ice stream
646
647   mask_tache_ij(:,:)=.false.
648   mask_tache_ij(:,:)=(table_out(:,:).eq.table_out(i,j))       ! pour toute la tache
649
650     smax_=maxval(S(:,:),MASK=mask_tache_ij(:,:))
651     smax_coord(:)=maxloc(S(:,:),MASK=mask_tache_ij(:,:))
652     smax_i=smax_coord(1)
653     smax_j=smax_coord(2)
654
655!!$               smax_i=0 ; smax_j=0 ; smax_=sealevel
656!!$               do ii=3,nx-2
657!!$                  do jj=3,ny-2
658!!$                     if (table_out(ii,jj).eq.table_out(i,j)) then
659!!$                        if (s(ii,jj).gt.smax_) then                           
660!!$                           smax_ =s(ii,jj)
661!!$                           smax_i=ii
662!!$                           smax_j=jj
663!!$                        endif
664!!$                     endif
665!!$                  end do
666!!$               end do
667
668
669               gzmx(smax_i,smax_j)=.false. ; gzmx(smax_i+1,smax_j)=.false.
670               gzmy(smax_i,smax_j)=.false. ; gzmx(smax_i,smax_j+1)=.false.
671               flgzmx(smax_i,smax_j)=.false. ; flgzmx(smax_i+1,smax_j)=.false.
672               flgzmy(smax_i,smax_j)=.false. ; flgzmx(smax_i,smax_j+1)=.false.
673 
674               if (Smax_.le.sealevel) then
675                  write(num_tracebug,*)'Attention, une ile avec la surface sous l eau'
676                  write(num_tracebug,*)'time=',time,'   coord:',smax_i,smax_j
677               end if
678
679            endif test2 
680         end if                                             ! endif deplace
681         
682      else ! on est sur un iceberg                          !   test1
683         ice(i,j)=0
684         h(i,j)=1.
685         surnet=H(i,j)*(1.-ro/row)
686         S(i,j)=surnet+sealevel
687         B(i,j)=S(i,j)-H(i,j)
688         
689      endif test1
690
691
692   end do
693end do
694
695
696!----------------------------------------------
697! On caracterise le front des ice shelfs/streams
698
699!      call DETERMIN_FRONT   
700
701!----------------------------------------------     
702!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
703!!$if (itestf.gt.0) then
704!!$   write(6,*) 'dans flottab apres DETERMIN_front  asymetrie sur H  pour time=',time
705!!$   stop
706!!$else
707!!$   write(6,*) 'dans flottab apres DETERMIN_front pas d asymetrie sur H  pour time=',time
708!!$
709!!$end if
710
711endif synchro
712
713! correction momentanée pour symetrie Heino
714!where ((.not.flot(:,:)).and.(ice(:,:).eq.0)) H(:,:)=0.     
715
716!fin de routine flottab2
717!print*, 'front',front(50,30),ice(50,30),flotmx(i,j),uxbar(i,j)
718
719
720
721end subroutine flottab
722!-------------------------------------------------------------------- 
723
724!> SUBROUTINE: determin_tache
725!! Routine pour la dtermination du numero de tache a effectuer
726!>
727subroutine determin_tache
728
729implicit none
730integer :: indice
731integer :: label         ! no des taches rencontrées dans le mask
732integer :: label_max     ! no temporaire maxi de tache rencontrées
733!      integer :: mask_nb = 4
734integer,parameter :: mask_nb = 2   ! version ou on ne compte pas les diagonales
735integer :: vartemp       ! variable temporaire pour reorganiser compt
736!     integer,dimension(mask_nb) :: mask
737integer,dimension(mask_nb) :: mask
738
739
740! 1-initialisation
741!-----------------
742label_max=1      ! numero de la tache, la premiere tache est notée 1
743label=1
744do i=1,n_ta_max
745   compt(i)=i
746enddo
747!      table_in  = .false.
748
749table_out(:,:) = 0
750iceberg(:)  = .true.
751icetrim (:) = .true.
752nb_pts_tache(:) = 0
753
754!    open(unit=100,file="tache.data",status='replace')
755
756! 2-reperage des taches
757!----------------------
758do i=2,nx-1
759  do j=2,ny-1
760
761
762
763     IF (ice(i,j).ge.1) THEN ! on est sur la glace-----------------------------!
764
765        if ((ice(i-1,j).ge.1).or.(ice(i,j-1).ge.1)) then   !masque de 2 cases adjacentes
766           !      un des voisins est deja en glace
767           mask(1) = table_out(i-1,j)
768           mask(2) = table_out(i,j-1) 
769           label = label_max
770
771           !on determine la valeur de la tache minimun (>0) presente ds le masque
772           do indice=1,mask_nb
773              if (mask(indice).gt.0) label=min(label,mask(indice))
774           enddo
775
776           !on fixe la valeur de la tache voisine minimun au point etudie (via label)
777           table_out(i,j)=label
778           !si ce noeud est posé, alors la tache n'est pas un iceberg et iceberg=.F.
779           if (.not.FLOT(I,J)) then
780              iceberg(label)=.false.
781           endif
782
783           !si ce noeud est posé, alors la tache n'est pas un ice stream et icestrim=.F.
784           if ((.not.gzmx(i,j).and..not.gzmx(i+1,j)).and.  &
785               (.not.gzmy(i,j).and..not.gzmy(i,j+1))) then
786              icetrim(label)=.false.
787           endif
788
789           ! si 2 taches differentes sont dans le masque, il faut les identifier dans compt
790           ! i.e. les plus grands numeros correspondent au plus petit
791           ! on lui affecte le numero de la tache fondamentale avec un signe -
792           ! pour indiquer le changement
793
794           do indice=1,mask_nb
795              if(mask(indice).gt.label) then
796                 compt(mask(indice))=-label
797              endif
798           enddo
799
800        else !aucun des voisins est une tache
801           table_out(i,j)= label_max
802           compt(label_max)=label_max
803           !si ce noeud est posé, alors la ache n'est pas un iceberg et iceberg=.F.
804           if (.not.FLOT(I,J)) then
805              iceberg(label_max)=.false.
806           endif
807
808           !si ce noeud est posé, alors le tache n'est pas un ice stream et icestrim=.F.
809           if ((.not.gzmx(i,j).and..not.gzmx(i+1,j)).and.  &
810               (.not.gzmy(i,j).and..not.gzmy(i,j+1))) then
811              icetrim(label)=.false.
812           endif
813             
814           label_max  = label_max+1
815           if (label_max.gt.n_ta_max) print*,'trop de taches=',label_max 
816        endif
817
818
819     else           !on est pas sur une tache----------------------------------------------
820        table_out(i,j)=0    ! Pas necessaire (reecrit 0 sur 0)             
821     endif          !---------------------------------------------------------------------
822
823
824  enddo
825enddo
826
827
828
829! On reorganise compt en ecrivant le numero de la tache fondamentale
830! i.e. du plus petit numero present sur la tache (Sans utiliser de recursivité)
831! On indique aussi le nb de point que contient chaque taches (nb_pts_tache)       
832do indice=1,label_max
833   vartemp = compt(indice)
834   if (compt(indice).lt.0) then
835      compt(indice)= compt(-vartemp)
836      if (.not.iceberg(indice)) iceberg(-vartemp)=.false.
837      if (.not.icetrim(indice)) icetrim(-vartemp)=.false.
838   endif   
839enddo
840
841do i=1,nx
842   do j=1,ny
843      if (table_out(i,j).ne.0) then
844         table_out(i,j)=compt(table_out(i,j)) 
845         nb_pts_tache(compt(table_out(i,j)))= nb_pts_tache(compt(table_out(i,j)))+1   
846      endif
847   enddo
848enddo
849
850
851
852
853!!$tablebis(:,:)=table_out(:,:)
854!!$do j=1,ny
855!!$   do i=1,nx
856!!$      if (tablebis(i,j).ne.0) then     ! tache de glace
857!!$         numtache=table_out(i,j)
858!!$         nb_pt=count(table_out(:,:).eq.numtache)  ! compte tous les points de la tache
859!!$         nb_pts_tache(table_out(i,j))=nb_pt       !
860!!$
861!!$         where (table_out(:,:).eq.numtache)         
862!!$            tablebis(:,:)=0                       ! la table de tache est remise a 0 pour eviter de repasser
863!!$         end where
864!!$          write(6,*) i,j,nb_pt,table_out(i,j)
865!!$      endif
866!!$   enddo
867!!$enddo
868
869!!$do j=1,ny
870!!$   do i=1,nx
871!!$      debug_3d(i,j,56)=nb_pts_tache(table_out(i,j))
872!!$   end do
873!!$end do
874!!$     
875end subroutine determin_tache
876!----------------------------------------------------------------------
877!> SUBROUTINE: determin_front
878!!Routine pour la determination du front
879!>
880subroutine determin_front
881
882integer :: i_moins1,i_plus1,i_plus2
883integer :: j_moins1,j_plus1,j_plus2
884     
885      do i=3,nx-2
886       do j=3,ny-2
887
888 surice:if  (ice(i,j).eq.0) then
889         do pmx=-1,1,2
890          do pmy=-1,1,2
891
892 diagice :  if (ice(i+pmx,j+pmy).eq.1) then
893
894              if ((ice(i+pmx,j)+ice(i,j+pmy).eq.2)) then    ! test (i) pour eviter les langues
895                                                            ! de glaces diagonales en coin(26dec04)
896                   if ((ice(i+2*pmx,j).eq.1.and.ice(i+2*pmx,j+pmy).eq.0).or.&
897                       (ice(i,j+2*pmy).eq.1.and.ice(i+pmx,j+2*pmy).eq.0)) then
898                           ice(i,j)=1
899                           h(i,j)=max(1.,h(i,j))
900                   endif         
901
902! test (i) pour eviter les langues de glaces diagonales :
903!                        mouvement du cheval aux echecs 
904
905               if ((ice(i+2*pmx,j+pmy)+ice(i+pmx,j+2*pmy).eq.1)) then
906                   if (ice(i+2*pmx,j+pmy).eq.1.and. &
907                      (ice(i+2*pmx,j+2*pmy)+ice(i,j+2*pmy)).ge.1) then
908                           ice(i,j)=1
909                           h(i,j)=max(1.,h(i,j))
910                   endif       
911                   if (ice(i+pmx,j+2*pmy).eq.1.and. &
912                      (ice(i+2*pmx,j+2*pmy)+ice(i+2*pmx,j)).ge.1) then
913                           ice(i,j)=1
914                           h(i,j)=max(1.,h(i,j))
915                   endif       
916
917! test (ii) pour eviter les langues de glaces diagonales :
918!            le point glace ice(i+pmx,j+pmy) a :
919!                          - ses 4 voisins frontaux en glace
920!                          - mais 2 voisins vides diagonalement opposes   
921           
922               elseif ((ice(i+2*pmx,j+pmy)+ice(i+pmx,j+2*pmy).eq.2)  &
923                                .and.ice(i+2*pmx,j+2*pmy).eq.0) then
924
925! test (iii) pour faire les tests (i) et (ii)
926                    ice(i,j)=1
927                    h(i,j)=max(1.,h(i,j))
928                    ice(i+2*pmx,j+2*pmy)=1
929                    h(i+2*pmx,j+2*pmy)=max(1.,h(i+2*pmx,j+2*pmy))
930               endif
931            endif
932           endif diagice   
933          enddo
934         enddo
935         endif surice       
936       end do
937      end do
938
939
940!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
941!!$if (itestf.gt.0) then
942!!$   write(6,*) 'dans front avant remplissage baies asymetrie sur H  pour time=',time
943!!$   stop
944!!$else
945!!$   write(6,*) 'dans front avant remplissage baies pas d asymetrie sur H  pour time=',time
946!!$
947!!$end if
948
949
950!     print*,'dans remplissage baies',time
951baies: do k=1,2
952do j=1,ny
953   do i=1,nx
954
955surice_xy: if  (ice(i,j).eq.0) then
956   i_moins1=max(i-1,1)
957   j_moins1=max(j-1,1)
958   i_plus1=min(i+1,nx)
959   j_plus1=min(j+1,ny)
960   i_plus2=min(i+2,nx)
961   j_plus2=min(j+2,ny)
962 
963! test (iii) pour trouver les baies de largeur 1 ou 2 cases
964! et combler les trous si ce sont des baies
965! si ce ne sont pas des baies, ne pas combler et creer des langues de glaces artificielles             
966! baies horizontales 
967 
968         if (ice(i_moins1,j).eq.1.and.(ice(i_plus1,j).eq.1.or.ice(i_plus2,j).eq.1)) then
969            if (ice(i,j_moins1).eq.1.or.ice(i,j_plus1).eq.1)  then    ! ice(i,j)=1
970               ice(i,j)=1
971               H(i,j)=max(1.,H(i,j))
972            endif
973         endif
974
975
976         if (ice(i,j_moins1).eq.1.and.(ice(i,j_plus1).eq.1.or.ice(i,j_plus2).eq.1)) then
977            if (ice(i_moins1,j).eq.1.or.ice(i_plus1,j).eq.1) then !ice(i,j)=1
978               ice(i,j)=1
979               H(i,j)=max(1.,H(i,j))
980            endif
981         endif
982
983      endif surice_xy
984   end do
985end do
986end do baies
987
988!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
989!!$if (itestf.gt.0) then
990!!$   write(6,*) 'dans front apres remplissage baies asymetrie sur H  pour time=',time
991!!$   stop
992!!$else
993!!$   write(6,*) 'dans front apres remplissage baies pas d asymetrie sur H  pour time=',time
994!!$
995!!$end if
996
997
998do i=2,nx-1
999   do j=2,ny-1
1000
1001      if (ice(i,j).eq.1) then     !         test si ice=1
1002
1003! if ice, on determine front...
1004! ainsi, front=0 sur les zones = 0
1005
1006         front(i,j)=(ice(i-1,j)+ice(i+1,j)+ice(i,j+1)+ice(i,j-1))
1007         !front= le nb de faces en contact avec un voisin englacé
1008      endif
1009   end do
1010end do
1011
1012! traitement des bords. On considere que l'exterieur n'a pas de glace
1013! attention ce n'est vrai que sur la grande grille
1014
1015
1016do j=2,ny-1
1017   i=1
1018   front(i,j)=(ice(i+1,j)+ice(i,j+1)+ice(i,j-1))
1019   i=nx
1020   front(i,j)=(ice(i-1,j)+ice(i,j+1)+ice(i,j-1))
1021end do
1022
1023do i=2,nx-1
1024   j=1 
1025   front(i,j)=(ice(i-1,j)+ice(i+1,j)+ice(i,j+1))
1026   j=ny
1027   front(i,j)=(ice(i-1,j)+ice(i+1,j)+ice(i,j-1))
1028end do
1029
1030! traitement des coins
1031
1032front(1,1)=ice(2,1)+ice(2,1)
1033front(1,ny)=ice(2,ny)+ice(1,ny-1)
1034front(nx,1)=ice(nx,2)+ice(nx-1,1)
1035front(nx,ny)=ice(nx,ny-1)+ice(nx-1,ny)
1036
1037!!$call detect_assym(nx,ny,0,41,1,0,1,0,H,itestf)
1038!!$if (itestf.gt.0) then
1039!!$   write(6,*) 'dans front apres front asymetrie sur H  pour time=',time
1040!!$   stop
1041!!$else
1042!!$   write(6,*) 'dans front apres front pas d asymetrie sur H  pour time=',time
1043!!$
1044!!$end if
1045
1046!   on ne compte pas les taches de glace de 2 cases (horizontales ou verticales)
1047!   en fait, si ces deux cases sont flottantes, il faut enlever les icebergs
1048!   de n'importe quelle taille).
1049!   si ces deux taches sont posées (ou une des deux), il n'y a pas assez de conditions aux limites
1050
1051
1052do j=1,ny
1053   do i=1,nx-1
1054      if (front(i,j).eq.1) then
1055         if (front(i+1,j).eq.1) then
1056            ice(i,j)=0
1057            ice(i+1,j)=0
1058            front(i,j)=0
1059            front(i+1,j)=0
1060         endif
1061      endif
1062   end do
1063end do
1064
1065do j=1,ny-1
1066   do i=1,nx
1067      if (front(i,j).eq.1) then
1068         if (front(i,j+1).eq.1) then
1069            ice(i,j)=0
1070            ice(i,j+1)=0
1071            front(i,j)=0
1072            front(i,j+1)=0
1073         endif
1074      end if
1075   end do
1076end do
1077
1078!isolx signifie pas de voisins en x
1079!isoly signifie pas de voisins en y
1080!remarque :
1081!si isolx/y=.true. alors frontfacex/y=0 (a la fois +1 & -1 or +1-1=0)
1082
1083! calcul de frontfacex et isolx
1084do j=1,ny
1085   do i=2,nx-1
1086
1087      if (front(i,j).ge.1.and.front(i,j).le.3) then    !front(entre 1 et 3)
1088         
1089         if ((ice(i-1,j)+ice(i+1,j)).lt.2) then        ! il y a un front // a x
1090         
1091            if ((ice(i-1,j)+ice(i+1,j)).eq.0) then
1092               isolx(i,j)=.true.
1093            elseif (ice(i-1,j).eq.0) then
1094               frontfacex(i,j)=-1                      ! front  i-1 |i  i+1
1095            else
1096               frontfacex(i,j)=+1                      ! front  i-1  i| i+1
1097            endif
1098         endif
1099      end if !fin du test il y a un front
1100         
1101   end do
1102end do
1103
1104! calcul de frontfacey et isoly
1105do j=2,ny-1
1106   do i=1,nx
1107
1108      if (front(i,j).ge.1.and.front(i,j).le.3) then   !front(entre 1 et 3)
1109         
1110         if ((ice(i,j-1)+ice(i,j+1)).lt.2) then       ! il y a un front // a y
1111             
1112            if ((ice(i,j-1)+ice(i,j+1)).eq.0) then
1113               isoly(i,j)=.true.                      !front   j-1 |j| j+1
1114            elseif (ice(i,j-1).eq.0) then
1115               frontfacey(i,j)=-1                     !front   j-1 |j j+1
1116            else
1117               frontfacey(i,j)=+1                     !front   j-1  j| j+1
1118            endif
1119         endif
1120     end if !fin du test il y a un front
1121         
1122   end do
1123end do
1124
1125
1126
1127! traitement des bords. On considere que l'exterieur n'a pas de glace
1128! attention ce n'est vrai que sur la grande grille
1129
1130
1131do j=2,ny-1
1132   i=1
1133   if (front(i,j).ge.1)  then
1134      if (ice(i+1,j).eq.0) then
1135         isolx(i,j)=.true.
1136      else
1137         frontfacex(i,j)=-1
1138      endif
1139   end if
1140   i=nx
1141   if (front(i,j).ge.1)  then
1142      if (ice(i-1,j).eq.0) then
1143         isolx(i,j)=.true.
1144      else
1145         frontfacex(i,j)=1
1146      endif
1147   end if
1148end do
1149
1150do i=2,nx-1
1151   j=1 
1152   if (front(i,j).ge.1)  then
1153      if (ice(i,j+1).eq.0) then
1154         isoly(i,j)=.true.
1155      else
1156         frontfacey(i,j)=-1
1157      endif
1158   end if
1159   j=ny
1160   if (front(i,j).ge.1)  then
1161      if (ice(i,j-1).eq.0) then
1162         isoly(i,j)=.true.
1163      else
1164         frontfacey(i,j)=1
1165      endif
1166   end if
1167end do
1168
1169
1170
1171return
1172end subroutine determin_front
1173!------------------------------------------------------------------------------
1174
1175end module flottab_mod
1176
1177
Note: See TracBrowser for help on using the repository browser.