source: trunk/SOURCES/New-remplimat/diagno-L2_mod.f90 @ 98

Last change on this file since 98 was 98, checked in by dumas, 7 years ago

Schoof update : Schoof only if nt > 15000

File size: 14.5 KB
Line 
1!module diagno_L2_mod               ! Nouvelle version, compatible remplimat 2008 Cat
2module diagno_mod                   ! nom pendant les tests
3 !$ USE OMP_LIB
4use module3D_phy
5use module_choix
6     
7implicit none
8
9
10
11real                   :: somint,test,delp,prec
12real, dimension(nx,ny) :: uxb1
13real, dimension(nx,ny) :: uyb1
14
15real, dimension(nx,ny) :: uxb1ramollo
16real, dimension(nx,ny) :: uyb1ramollo
17real, dimension(nx,ny) :: pvi_keep
18
19
20!cdc transfere dans module3d pour compatibilite avec furst_schoof_mod
21!cdc  integer, dimension(nx,ny) :: imx_diag
22!cdc  integer, dimension(nx,ny) :: imy_diag
23
24integer :: nxd1,nxd2     ! domaine selon x Dans l'appel rempli_L2
25integer :: nyd1,nyd2     ! domaine selon y
26
27integer :: itour_pvi
28
29integer :: ifail_diagno  ! pour recuperation d'erreur
30integer :: ifail_diagno_ramollo  ! pour recuperation d'erreur shelf ramollo
31integer :: iplus1,jplus1
32integer ::  ctvisco,iumax,jumax
33real  :: delumax,errmax
34real  :: phiphi,bt2,d02,discr,ttau
35real :: sf3,sf1,epsxxm,epsyym,epsm,sf01,sf03    ! pour le calcul de la viscosite
36real :: viscm
37real :: sf_shelf                                ! coef mult enhancement factor pour shelves
38
39logical :: stopvisco,viscolin
40logical :: test_visc
41
42contains   
43
44!------------------------------------------------------------------------------------
45subroutine init_diagno
46
47namelist/diagno_rheol/sf01,sf03,pvimin
48
49! attribution des coefficients de viscosite
50
51! formats pour les ecritures dans 42
52428 format(A)
53
54! lecture des parametres du run                      block draghwat
55!--------------------------------------------------------------------
56
57rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
58read(num_param,diagno_rheol)
59
60write(num_rep_42,428)'!___________________________________________________________' 
61write(num_rep_42,428) '&diagno_rheol              ! nom du bloc  diagno_rheol'
62write(num_rep_42,*)
63write(num_rep_42,*) 'sf01           = ',sf01 
64write(num_rep_42,*) 'sf03           = ',sf03
65write(num_rep_42,*) 'pvimin         = ',pvimin
66write(num_rep_42,*)'/'     
67write(num_rep_42,428) '! coefficients par rapport a la loi glace posee '                       
68write(num_rep_42,428) '! sf01 : coefficient viscosite loi lineaire '
69write(num_rep_42,428) '! sf03 : coefficient viscosite loi n=3 '
70write(num_rep_42,428) '! pvimin : valeur de pvi pour les noeuds fictifs ~ 1.e3'
71write(num_rep_42,428) '! tres petit par rapport aux valeurs standards ~ 1.e10'
72
73write(num_rep_42,*)
74
75
76!      Precision utilisee dans de calcul
77prec = 1.e-2
78itour_pvi=1   ! si prend les valeurs analytiques dans le shelf
79
80if (geoplace(1:5).eq.'mism3') then
81   sf_shelf = 1.
82   itour_pvi= 0
83
84else
85   sf_shelf = 0.4
86end if
87
88
89return
90end subroutine init_diagno
91
92!------------------------------------------------------------------------------------
93subroutine diagnoshelf !      Resolution numerique des equations diagnostiques
94
95
96  if (itracebug.eq.1)  call tracebug(' Entree dans diagnoshelf')
97
98
99  itour_pvi=itour_pvi+1       ! boucle sur la viscosite (pour l'instant pas actif)
100
101!  pvi(:,:)=0.
102  Taushelf(:,:)=0.
103
104  ! attention le bloc suivant est pour debug
105!!$gzmx(:,:)=.false.
106!!$gzmy(:,:)=.false.
107!!$ilemx(:,:)=.false.
108!!$ilemy(:,:)=.false.
109!!$flgzmx(:,:)=flotmx(:,:)
110!!$flgzmy(:,:)=flotmy(:,:)
111
112  call dragging                    ! doit etre appele avant imx_imy
113
114
115
116if (itour_pvi.le.1) then
117  call calc_pvi                    ! calcule les viscosites integrees
118
119!$OMP PARALLEL
120!$OMP WORKSHARE
121   where (flot(:,:).and.(H.gt.1))  ! valeur analytique pour les shelfs
122      pvi(:,:) = (4./coef_Sflot/rog)**2/btt(:,:,1,1)/H(:,:)
123   end where
124!$OMP END WORKSHARE
125!$OMP END PARALLEL
126  ! avec couplage thermomecanique
127!  write(166,*) ' apres call calc_pvi',itour_pvi
128
129else
130   call calc_pvi   
131end if
132
133  call imx_imy_nx_ny         ! pour rempli_L2 : calcule les masques imx et imy qui
134
135!cdc debug Schoof !!!!!!!!!!!! 
136!~   do j=1,ny
137!~              do i=1,nx
138!~                      write(578,*) uxbar(i,j)
139!~                      write(579,*) uybar(i,j)
140!~              enddo
141!~      enddo   
142 
143  if (Schoof.eq.1.and.nt.GT.15000) then ! flux grounding line Schoof
144                call interpol_glflux ! calcul flux GL + interpolation sur voisins
145        endif   
146       
147!~       do j=1,ny
148!~              do i=1,nx
149!~                      write(588,*) uxbar(i,j)
150!~                      write(589,*) uybar(i,j)
151!~              enddo
152!~      enddo   
153!~      print*,'ecriteure termineee !!!!!!'
154!~      read(*,*)
155       
156  ! donnent les cas de conditions aux limites
157  !
158  ! version pour travailler sur tout le domaine nx ny
159
160  if (geoplace(1:5).eq.'mism3') call mismip_boundary_cond
161
162
163  ! appel a la routine rempl_L2 -------------------domaine nx x ny ------------
164  !
165
166  ! pour tout le domaine
167  nxd1=1
168  nxd2=nx
169  nyd1=1
170  nyd2=ny
171
172  !call rempli_L2(1,nx,1,ny,uxbar,uybar,uxb1,uyb1,imx_diag,imy_diag,ifail_diagno)   
173  !nxd1=15
174  !nxd2=19
175  !nyd1=30
176  !nyd2=34
177
178  !nxd1=35
179  !nxd2=60
180  !nyd1=35
181  !nyd2=60
182
183  call rempli_L2(nxd1,nxd2,nyd1,nyd2,uxbar(nxd1:nxd2,nyd1:nyd2),uybar(nxd1:nxd2,nyd1:nyd2), & 
184       uxb1(nxd1:nxd2,nyd1:nyd2),uyb1(nxd1:nxd2,nyd1:nyd2),  &
185       imx_diag(nxd1:nxd2,nyd1:nyd2),imy_diag(nxd1:nxd2,nyd1:nyd2),ifail_diagno)
186       
187  if (Schoof.eq.1.and.nt.GT.15000) then ! flux grounding line Schoof avec calcul de la back force par shelf ramollo
188    pvi_keep(:,:)=pvi(:,:)       
189                where (flot(:,:).and.H(:,:).GT.2.)
190                                pvi(:,:)=1.e5   
191!                               pvi(:,:)=pvimin
192                endwhere
193                                       
194                call rempli_L2(nxd1,nxd2,nyd1,nyd2,uxbar(nxd1:nxd2,nyd1:nyd2),uybar(nxd1:nxd2,nyd1:nyd2), & 
195       uxb1ramollo(nxd1:nxd2,nyd1:nyd2),uyb1ramollo(nxd1:nxd2,nyd1:nyd2),  &
196       imx_diag(nxd1:nxd2,nyd1:nyd2),imy_diag(nxd1:nxd2,nyd1:nyd2),ifail_diagno_ramollo)
197       
198    pvi(:,:)=pvi_keep(:,:) 
199   
200    where ((uxb1ramollo(:,:)**2 + uyb1ramollo(:,:)**2).GT.0.)
201                        back_force(:,:) = sqrt(uxb1(:,:)**2+ uyb1(:,:)**2) / sqrt(uxb1ramollo(:,:)**2 + uyb1ramollo(:,:)**2)
202                elsewhere
203                        back_force(:,:)=1.
204                endwhere
205               
206                if (ifail_diagno_ramollo.gt.0) then
207                        write(6,*) ' Probleme resolution systeme L2. ramollo ifail=',ifail_diagno_ramollo
208                        STOP
209                endif
210!~   do j=1,ny
211!~              do i=1,nx
212!~                if (sqrt(uxb1(i,j)**2+ uyb1(i,j)**2).gt.0..and..not.flot(i,j)) then
213!~                              write(1034,*) sqrt(uxb1(i,j)**2+ uyb1(i,j)**2) / sqrt(uxb1ramollo(i,j)**2 + uyb1ramollo(i,j)**2)
214!~                else
215!~                              write(1034,*) 1.
216!~                      endif
217!~              enddo           
218!~      enddo
219       
220!~   print*,'apres calcul rempli_L2'
221!~   read(*,*)     
222  endif
223 
224
225  ! Dans rempli_L2
226
227  !      uxprex(n1,n2)                                                 
228  !      uyprec(n1,n2) vitesses de l'iteration precedente     
229  !                                                                   
230  !      uxnew(n1,n2)                                                   
231  !      uynew(n1,n2) uynew resultat de cette iteration
232  !
233  !      imx(n1,n2) masque pour imposer les vitesses ou leur dérivee   
234  !      imy(n1,n2) masque pour imposer les vitesses ou leur dérivée   
235
236  ! eventuellement le domaine n1,n2 peut etre un sous-domaine de nx,ny
237  ! attention il faudra alors appeler avec des sous-tableaux
238
239  ! Dans l'appel uxbar -> uxprec   et Uxb1 -> Uxnew
240
241  !---------------------------------------------------------------------------
242
243  if (ifail_diagno.gt.0) then
244     write(6,*) ' Probleme resolution systeme L2. ifail=',ifail_diagno
245     STOP
246  endif
247
248  !      nouvelles vitesses         
249  !$OMP PARALLEL
250  !$OMP WORKSHARE
251  uxbar(:,:)=uxb1(:,:)
252  uybar(:,:)=uyb1(:,:)
253  !$OMP END WORKSHARE
254
255
256  !    calcul de tobmx et tobmy (frottement basal) apres calcul des vitesses
257  !    ---------------------------------------------------------------------
258  !$OMP DO
259  do j=1,ny
260     do i=1,nx
261        tobmx(i,j)=-betamx(i,j)*uxbar(i,j)
262        tobmy(i,j)=-betamy(i,j)*uybar(i,j)
263     enddo
264  enddo
265  !$OMP END DO
266
267  ! Mise ne réserve des vitesses flgzmx et flgzmy
268  !$OMP WORKSHARE
269  where (flgzmx(:,:))
270     uxflgz(:,:)=uxbar(:,:)
271  elsewhere
272     uxflgz(:,:)=0.
273  endwhere
274
275  where (flgzmy(:,:))
276     uyflgz(:,:)=uybar(:,:)
277  elsewhere
278     uyflgz(:,:)=0.
279  endwhere
280  !$OMP END WORKSHARE
281  !$OMP END PARALLEL
282  !i=92
283  !j=152
284  !write(6,*) 'time',time, uxbar(92,152),gzmx(92,152),ilemx(92,152),flotmx(92,152), flgzmx(92,152)
285
286  return
287end subroutine diagnoshelf
288
289
290!-------------------------------------------------------------------
291subroutine calc_pvi
292
293! calcule les viscosites integrees pvi et pvm
294! loi polynomiale + couplage thermomécanique
295!
296!     Attention ne marche que si la loi est la loi en n=3 + n=1
297!     y compris le pur glen (n=3) ou le pur Newtonien (n=1)
298! --------------------------------------------------------------------
299
300!     les deformations sont supposées indépendantes de la profondeur
301!     et sont calculées dans strain_rate (appelé par main)       
302
303!     eps(i,j) -> eps
304!     ttau -> tau (2eme invariant du deviateur des contraintes)
305!     BT2 loi en n=3, phiphi loi en n=1 calculés dans flowlaw
306
307!
308     
309
310! La viscosité est calculée partout y compris pour la glace posée (ou elle est moins
311! précise qu'un calcul direct avec la loi de déformation.)
312! Pour les noeuds posés mais ayant un voisin stream ou flottant, on calcule
313! la viscosité avec stream/shelves
314! le calcul se fait sur les noeuds majeurs
315
316!$  integer :: rang ,nb_taches
317!$  logical :: paral
318
319  integer :: t1,t2,ir
320  real                           :: temps, t_cpu_0, t_cpu_1, t_cpu, norme 
321
322if (itracebug.eq.1)  call tracebug(' Calc pvi')
323
324!$OMP PARALLEL PRIVATE(rang,iplus1,jplus1,sf3,sf1,BT2,phiphi,ttau,d02,discr)
325!$ paral = OMP_IN_PARALLEL()
326!$ rang=OMP_GET_THREAD_NUM()
327!$ nb_taches=OMP_GET_NUM_THREADS()
328
329!$OMP WORKSHARE
330pvi(:,:)  = pvimin
331Abar(:,:) = 0.
332!$OMP END WORKSHARE
333
334!$OMP DO
335do j=1,ny
336   do i=1,nx
337      iplus1=min(i+1,nx)
338      jplus1=min(j+1,ny)
339
340
341      if (flot(i,j)) then    ! noeuds flottants
342         sf3=sf03*sf_shelf     
343         sf1=sf01*sf_shelf
344     
345      else if (gzmx(i,j).or.gzmx(iplus1,j).or.gzmy(i,j).or.gzmy(i,jplus1)) then
346         sf1=sf01
347         sf3=max(sf03,0.01)   ! pour les fleuves de glace, un peu de Glen
348     
349      else if (ilemx(i,j).or.ilemx(iplus1,j).or.ilemy(i,j).or.ilemy(i,jplus1)) then
350         sf1=sf01
351         sf3=max(sf03,0.01)   ! pour les iles aussi
352
353      else
354!         sf1=1
355!         sf3=1
356         sf1=sf01             ! pour la viscosite anisotrope (ici en longitudinal)
357         sf3=sf03
358      endif
359
360
361      do k=1,nz 
362
363         BT2=BTT(i,j,k,1)*sf3    ! changement du sf
364         phiphi=BTT(i,j,k,2)*sf1 !  changement du sf
365
366
367
368         if (BT2.lt.1.e-25) then      ! pur newtonien
369            visc(i,j,k)=1./phiphi
370            ttau=2.*visc(i,j,k)*eps(i,j)
371         else                         ! polynomial
372
373
374!  en mettant Bt2 en facteur
375            d02=eps(i,j) 
376            discr=((phiphi/3.)**3.)/Bt2+d02**2
377            discr=discr**0.5
378
379            ttau=(d02+discr)**(1./3.)-(discr-d02)**(1./3.)
380
381
382            ttau=ttau*Bt2**(-1./3.)
383
384
385            visc(i,j,k)=Bt2*ttau*ttau+phiphi
386
387            if (visc(i,j,k).gt.1.e-15) then
388               visc(i,j,k)=1./visc(i,j,k)
389            else
390               visc(i,j,k)=1.e15
391            endif
392         endif
393         pvi(i,j)=pvi(i,j)+visc(i,j,k)
394         Abar(i,j) =(Bt2/2.)**(-1./3.) + Abar(i,j) 
395
396         Taushelf(i,j)=Taushelf(i,j)+ttau
397
398
399      end do
400     
401
402   
403      pvi(i,j)  = pvi(i,j)*H(i,j)/nz
404      Abar(i,j) = (Abar(i,j) /nz)**(-3.)
405     
406
407      Taushelf(i,j)=Taushelf(i,j)/nz
408   
409   
410   end do
411end do
412!$OMP END DO
413
414! cas des noeuds fictifs, si l'épaisseur est très petite
415! pvimin est très petit
416!$OMP WORKSHARE
417where (H(:,:).le.1.)
418   pvi(:,:) = pvimin
419end where
420
421where (ramollo(:,:).ge..5)
422   pvi(:,:) = pvimin
423end where
424
425
426debug_3D(:,:,27)=pvi(:,:)
427!$OMP END WORKSHARE
428! attention run 35
429!--------------------
430!!$if (time.gt.10.) then
431!!$   where (flot(:,:))
432!!$      pvi(:,:)=pvimin
433!!$   end where
434!!$end if
435
436!  calcul de la viscosite integree au milieu des mailles (pvm)
437!$OMP DO
438do i=2,nx
439   do j=2,ny
440
441! les lignes suivantes pour un pvm moyenne des pvi
442      pvm(i,j)=0.25*((pvi(i,j)+pvi(i-1,j-1))+    &   
443           (pvi(i,j-1)+pvi(i-1,j)))
444
445   end do
446end do
447!$OMP END DO
448!$OMP END PARALLEL
449
450end subroutine calc_pvi
451!------------------------------------------------------------------
452
453subroutine imx_imy_nx_ny
454
455! definition des masques
456! pour rempli_L2 : calcule les masques imx et imy qui
457! donnent les cas de conditions aux limites
458! version pour travailler sur tout le domaine nx ny
459!----------------------------------------------------
460
461
462
463!   -34                -3   Nord              -23   
464!     !----------------------------------------!
465!     !                                        !
466!     !              1 (prescrite)             !
467!  -4 !                   ou                   ! -2
468! West!              2 (L2)                    !  Est
469!     !                                        !
470!     !                                        !
471!     !----------------------------------------!
472!    -41               -1  Sud                -12
473
474!$OMP PARALLEL
475!$OMP WORKSHARE
476imx_diag(:,:)=0
477imy_diag(:,:)=0
478
479! a l'interieur du domaine
480!-------------------------
481
482where (flgzmx(:,:))
483   imx_diag(:,:)=2             ! shelf ou stream       
484elsewhere
485   imx_diag(:,:)=1             ! vitesse imposee
486end where
487
488where (flgzmy(:,:))     
489   imy_diag(:,:)=2             ! shelf ou stream
490elsewhere
491   imy_diag(:,:)=1             ! vitesse imposee
492end where
493
494! bord sud
495imx_diag(:,1)=-1
496imy_diag(:,2)=-1
497
498! bord nord
499imx_diag(:,ny)=-3
500imy_diag(:,ny)=-3
501
502! bord Est
503imx_diag(1,:)=0    ! hors domaine a cause des mailles alternees
504imx_diag(2,:)=-4
505imy_diag(1,:)=-4
506
507! bord West
508imx_diag(nx,:)=-2
509imy_diag(nx,:)=-2
510
511! Coins
512imx_diag(2,1)=-41       ! SW
513imy_diag(1,2)=-41
514
515imx_diag(nx,1)=-12      ! SE
516imy_diag(nx,2)=-12
517
518imx_diag(nx,ny)=-23     ! NE
519imy_diag(nx,ny)=-23
520
521imx_diag(2,ny)=-34      ! NW
522imy_diag(1,ny)=-34
523
524! hors domaine
525imx_diag(1,:)=0     ! hors domaine a cause des mailles alternees
526imy_diag(:,1)=0     ! hors domaine a cause des mailles alternees
527!$OMP END WORKSHARE
528!$OMP END PARALLEL
529 
530end subroutine imx_imy_nx_ny
531!___________________________________________________________________________
532! pour imposer les conditions de mismip sur les bords du fleuve
533! a appeler apres imx_imy_nx_ny
534
535subroutine mismip_boundary_cond
536if (itracebug.eq.1)  call tracebug(' Subroutine mismip_boundray_cond')
537
538! Condition pas de flux sur les bords nord et sud
539
540 imy_diag(:,2)      = 1
541 imy_diag(:,3)      = 1
542 imy_diag(:,ny-1)   = 1
543 imy_diag(:,ny)     = 1
544
545
546 Uybar(:,2)    = 0.
547 Uybar(:,3)    = 0.
548 Uybar(:,ny-1) = 0.
549 Uybar(:,ny)   = 0.
550
551
552! condition pas de cisaillement sur les bords nord et sud
553imx_diag(:,2)    = -1
554imx_diag(:,ny-1) = -3
555
556! coins
557imx_diag(2,2)     =  -41
558imx_diag(nx,2)    =  -12
559imx_diag(2,ny-1)  =  -34
560imx_diag(nx,ny-1) =  -23
561imx_diag(1,:)     =    0     ! ces points sont hors grille
562
563end subroutine mismip_boundary_cond
564
565!end module diagno_L2_mod
566end module diagno_mod
Note: See TracBrowser for help on using the repository browser.