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

Last change on this file since 104 was 104, checked in by aquiquet, 7 years ago

Schoof: back force in x/y from ramollos.

File size: 14.9 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  if (Schoof.eq.1) then ! flux grounding line Schoof
145     call interpol_glflux ! calcul flux GL + interpolation sur voisins
146  endif
147
148!~       do j=1,ny
149!~              do i=1,nx
150!~                      write(588,*) uxbar(i,j)
151!~                      write(589,*) uybar(i,j)
152!~              enddo
153!~      enddo   
154!~      print*,'ecriteure termineee !!!!!!'
155!~      read(*,*)
156
157  ! donnent les cas de conditions aux limites
158  !
159  ! version pour travailler sur tout le domaine nx ny
160
161  if (geoplace(1:5).eq.'mism3') call mismip_boundary_cond
162
163
164  ! appel a la routine rempl_L2 -------------------domaine nx x ny ------------
165  !
166
167  ! pour tout le domaine
168  nxd1=1
169  nxd2=nx
170  nyd1=1
171  nyd2=ny
172
173  !call rempli_L2(1,nx,1,ny,uxbar,uybar,uxb1,uyb1,imx_diag,imy_diag,ifail_diagno)   
174  !nxd1=15
175  !nxd2=19
176  !nyd1=30
177  !nyd2=34
178
179  !nxd1=35
180  !nxd2=60
181  !nyd1=35
182  !nyd2=60
183
184  call rempli_L2(nxd1,nxd2,nyd1,nyd2,uxbar(nxd1:nxd2,nyd1:nyd2),uybar(nxd1:nxd2,nyd1:nyd2), & 
185       uxb1(nxd1:nxd2,nyd1:nyd2),uyb1(nxd1:nxd2,nyd1:nyd2),  &
186       imx_diag(nxd1:nxd2,nyd1:nyd2),imy_diag(nxd1:nxd2,nyd1:nyd2),ifail_diagno)
187       
188  !if (Schoof.eq.1.and.nt.GT.15000) then ! flux grounding line Schoof avec calcul de la back force par shelf ramollo
189  if (Schoof.eq.1) then ! flux grounding line Schoof avec calcul de la back force par shelf ramollo
190    pvi_keep(:,:)=pvi(:,:)       
191    where (flot(:,:).and.H(:,:).GT.2.)
192       pvi(:,:)=1.e5   
193!       pvi(:,:)=pvimin
194    endwhere
195
196    call rempli_L2(nxd1,nxd2,nyd1,nyd2,uxbar(nxd1:nxd2,nyd1:nyd2),uybar(nxd1:nxd2,nyd1:nyd2), & 
197       uxb1ramollo(nxd1:nxd2,nyd1:nyd2),uyb1ramollo(nxd1:nxd2,nyd1:nyd2),  &
198       imx_diag(nxd1:nxd2,nyd1:nyd2),imy_diag(nxd1:nxd2,nyd1:nyd2),ifail_diagno_ramollo)
199       
200    pvi(:,:)=pvi_keep(:,:) 
201   
202    where (abs(uxb1ramollo(:,:)) .GT.1.e-5)
203       back_force_x(:,:) = 1.0 * abs(uxb1(:,:)) / abs(uxb1ramollo(:,:))
204    elsewhere
205       back_force_x(:,:)=1.
206    endwhere
207    where (abs(uyb1ramollo(:,:)) .GT.1.e-5)
208       back_force_y(:,:) = 1.0 * abs(uyb1(:,:)) / abs(uyb1ramollo(:,:))
209    elsewhere
210       back_force_y(:,:)=1.
211    endwhere
212
213    if (ifail_diagno_ramollo.gt.0) then
214!       write(6,*) ' Probleme resolution systeme L2. ramollo ifail=',ifail_diagno_ramollo
215!       STOP
216       write(*,*) ' Probleme resolution systeme L2. ramollo ifail=',ifail_diagno_ramollo
217       write(*,*) '          ... we go on anyway!'
218    endif
219!~   do j=1,ny
220!~              do i=1,nx
221!~                if (sqrt(uxb1(i,j)**2+ uyb1(i,j)**2).gt.0..and..not.flot(i,j)) then
222!~                              write(1034,*) sqrt(uxb1(i,j)**2+ uyb1(i,j)**2) / sqrt(uxb1ramollo(i,j)**2 + uyb1ramollo(i,j)**2)
223!~                else
224!~                              write(1034,*) 1.
225!~                      endif
226!~              enddo           
227!~      enddo
228
229!~   print*,'apres calcul rempli_L2'
230!~   read(*,*)     
231  endif
232 
233
234  ! Dans rempli_L2
235
236  !      uxprex(n1,n2)                                                 
237  !      uyprec(n1,n2) vitesses de l'iteration precedente     
238  !                                                                   
239  !      uxnew(n1,n2)                                                   
240  !      uynew(n1,n2) uynew resultat de cette iteration
241  !
242  !      imx(n1,n2) masque pour imposer les vitesses ou leur dérivee   
243  !      imy(n1,n2) masque pour imposer les vitesses ou leur dérivée   
244
245  ! eventuellement le domaine n1,n2 peut etre un sous-domaine de nx,ny
246  ! attention il faudra alors appeler avec des sous-tableaux
247
248  ! Dans l'appel uxbar -> uxprec   et Uxb1 -> Uxnew
249
250  !---------------------------------------------------------------------------
251
252  if (ifail_diagno.gt.0) then
253     write(6,*) ' Probleme resolution systeme L2. ifail=',ifail_diagno
254     STOP
255  endif
256
257  !      nouvelles vitesses         
258  !$OMP PARALLEL
259  !$OMP WORKSHARE
260  uxbar(:,:)=uxb1(:,:)
261  uybar(:,:)=uyb1(:,:)
262  !$OMP END WORKSHARE
263
264
265  !    calcul de tobmx et tobmy (frottement basal) apres calcul des vitesses
266  !    ---------------------------------------------------------------------
267  !$OMP DO
268  do j=1,ny
269     do i=1,nx
270        tobmx(i,j)=-betamx(i,j)*uxbar(i,j)
271        tobmy(i,j)=-betamy(i,j)*uybar(i,j)
272     enddo
273  enddo
274  !$OMP END DO
275
276  ! Mise ne réserve des vitesses flgzmx et flgzmy
277  !$OMP WORKSHARE
278  where (flgzmx(:,:))
279     uxflgz(:,:)=uxbar(:,:)
280  elsewhere
281     uxflgz(:,:)=0.
282  endwhere
283
284  where (flgzmy(:,:))
285     uyflgz(:,:)=uybar(:,:)
286  elsewhere
287     uyflgz(:,:)=0.
288  endwhere
289  !$OMP END WORKSHARE
290  !$OMP END PARALLEL
291  !i=92
292  !j=152
293  !write(6,*) 'time',time, uxbar(92,152),gzmx(92,152),ilemx(92,152),flotmx(92,152), flgzmx(92,152)
294
295  return
296end subroutine diagnoshelf
297
298
299!-------------------------------------------------------------------
300subroutine calc_pvi
301
302! calcule les viscosites integrees pvi et pvm
303! loi polynomiale + couplage thermomécanique
304!
305!     Attention ne marche que si la loi est la loi en n=3 + n=1
306!     y compris le pur glen (n=3) ou le pur Newtonien (n=1)
307! --------------------------------------------------------------------
308
309!     les deformations sont supposées indépendantes de la profondeur
310!     et sont calculées dans strain_rate (appelé par main)       
311
312!     eps(i,j) -> eps
313!     ttau -> tau (2eme invariant du deviateur des contraintes)
314!     BT2 loi en n=3, phiphi loi en n=1 calculés dans flowlaw
315
316!
317     
318
319! La viscosité est calculée partout y compris pour la glace posée (ou elle est moins
320! précise qu'un calcul direct avec la loi de déformation.)
321! Pour les noeuds posés mais ayant un voisin stream ou flottant, on calcule
322! la viscosité avec stream/shelves
323! le calcul se fait sur les noeuds majeurs
324
325!$  integer :: rang ,nb_taches
326!$  logical :: paral
327
328  integer :: t1,t2,ir
329  real                           :: temps, t_cpu_0, t_cpu_1, t_cpu, norme 
330
331if (itracebug.eq.1)  call tracebug(' Calc pvi')
332
333!$OMP PARALLEL PRIVATE(rang,iplus1,jplus1,sf3,sf1,BT2,phiphi,ttau,d02,discr)
334!$ paral = OMP_IN_PARALLEL()
335!$ rang=OMP_GET_THREAD_NUM()
336!$ nb_taches=OMP_GET_NUM_THREADS()
337
338!$OMP WORKSHARE
339pvi(:,:)  = pvimin
340Abar(:,:) = 0.
341!$OMP END WORKSHARE
342
343!$OMP DO
344do j=1,ny
345   do i=1,nx
346      iplus1=min(i+1,nx)
347      jplus1=min(j+1,ny)
348
349
350      if (flot(i,j)) then    ! noeuds flottants
351         sf3=sf03*sf_shelf     
352         sf1=sf01*sf_shelf
353     
354      else if (gzmx(i,j).or.gzmx(iplus1,j).or.gzmy(i,j).or.gzmy(i,jplus1)) then
355         sf1=sf01
356         sf3=max(sf03,0.01)   ! pour les fleuves de glace, un peu de Glen
357     
358      else if (ilemx(i,j).or.ilemx(iplus1,j).or.ilemy(i,j).or.ilemy(i,jplus1)) then
359         sf1=sf01
360         sf3=max(sf03,0.01)   ! pour les iles aussi
361
362      else
363!         sf1=1
364!         sf3=1
365         sf1=sf01             ! pour la viscosite anisotrope (ici en longitudinal)
366         sf3=sf03
367      endif
368
369
370      do k=1,nz 
371
372         BT2=BTT(i,j,k,1)*sf3    ! changement du sf
373         phiphi=BTT(i,j,k,2)*sf1 !  changement du sf
374
375
376
377         if (BT2.lt.1.e-25) then      ! pur newtonien
378            visc(i,j,k)=1./phiphi
379            ttau=2.*visc(i,j,k)*eps(i,j)
380         else                         ! polynomial
381
382
383!  en mettant Bt2 en facteur
384            d02=eps(i,j) 
385            discr=((phiphi/3.)**3.)/Bt2+d02**2
386            discr=discr**0.5
387
388            ttau=(d02+discr)**(1./3.)-(discr-d02)**(1./3.)
389
390
391            ttau=ttau*Bt2**(-1./3.)
392
393
394            visc(i,j,k)=Bt2*ttau*ttau+phiphi
395
396            if (visc(i,j,k).gt.1.e-15) then
397               visc(i,j,k)=1./visc(i,j,k)
398            else
399               visc(i,j,k)=1.e15
400            endif
401         endif
402         pvi(i,j)=pvi(i,j)+visc(i,j,k)
403         Abar(i,j) =(Bt2/2.)**(-1./3.) + Abar(i,j) 
404
405         Taushelf(i,j)=Taushelf(i,j)+ttau
406
407
408      end do
409     
410
411   
412      pvi(i,j)  = pvi(i,j)*H(i,j)/nz
413      Abar(i,j) = (Abar(i,j) /nz)**(-3.)
414     
415
416      Taushelf(i,j)=Taushelf(i,j)/nz
417   
418   
419   end do
420end do
421!$OMP END DO
422
423! cas des noeuds fictifs, si l'épaisseur est très petite
424! pvimin est très petit
425!$OMP WORKSHARE
426where (H(:,:).le.1.)
427   pvi(:,:) = pvimin
428end where
429
430where (ramollo(:,:).ge..5)
431   pvi(:,:) = pvimin
432end where
433
434
435debug_3D(:,:,27)=pvi(:,:)
436!$OMP END WORKSHARE
437! attention run 35
438!--------------------
439!!$if (time.gt.10.) then
440!!$   where (flot(:,:))
441!!$      pvi(:,:)=pvimin
442!!$   end where
443!!$end if
444
445!  calcul de la viscosite integree au milieu des mailles (pvm)
446!$OMP DO
447do i=2,nx
448   do j=2,ny
449
450! les lignes suivantes pour un pvm moyenne des pvi
451      pvm(i,j)=0.25*((pvi(i,j)+pvi(i-1,j-1))+    &   
452           (pvi(i,j-1)+pvi(i-1,j)))
453
454   end do
455end do
456!$OMP END DO
457!$OMP END PARALLEL
458
459end subroutine calc_pvi
460!------------------------------------------------------------------
461
462subroutine imx_imy_nx_ny
463
464! definition des masques
465! pour rempli_L2 : calcule les masques imx et imy qui
466! donnent les cas de conditions aux limites
467! version pour travailler sur tout le domaine nx ny
468!----------------------------------------------------
469
470
471
472!   -34                -3   Nord              -23   
473!     !----------------------------------------!
474!     !                                        !
475!     !              1 (prescrite)             !
476!  -4 !                   ou                   ! -2
477! West!              2 (L2)                    !  Est
478!     !                                        !
479!     !                                        !
480!     !----------------------------------------!
481!    -41               -1  Sud                -12
482
483!$OMP PARALLEL
484!$OMP WORKSHARE
485imx_diag(:,:)=0
486imy_diag(:,:)=0
487
488! a l'interieur du domaine
489!-------------------------
490
491where (flgzmx(:,:))
492   imx_diag(:,:)=2             ! shelf ou stream       
493elsewhere
494   imx_diag(:,:)=1             ! vitesse imposee
495end where
496
497where (flgzmy(:,:))     
498   imy_diag(:,:)=2             ! shelf ou stream
499elsewhere
500   imy_diag(:,:)=1             ! vitesse imposee
501end where
502
503! bord sud
504imx_diag(:,1)=-1
505imy_diag(:,2)=-1
506
507! bord nord
508imx_diag(:,ny)=-3
509imy_diag(:,ny)=-3
510
511! bord Est
512imx_diag(1,:)=0    ! hors domaine a cause des mailles alternees
513imx_diag(2,:)=-4
514imy_diag(1,:)=-4
515
516! bord West
517imx_diag(nx,:)=-2
518imy_diag(nx,:)=-2
519
520! Coins
521imx_diag(2,1)=-41       ! SW
522imy_diag(1,2)=-41
523
524imx_diag(nx,1)=-12      ! SE
525imy_diag(nx,2)=-12
526
527imx_diag(nx,ny)=-23     ! NE
528imy_diag(nx,ny)=-23
529
530imx_diag(2,ny)=-34      ! NW
531imy_diag(1,ny)=-34
532
533! hors domaine
534imx_diag(1,:)=0     ! hors domaine a cause des mailles alternees
535imy_diag(:,1)=0     ! hors domaine a cause des mailles alternees
536!$OMP END WORKSHARE
537!$OMP END PARALLEL
538 
539end subroutine imx_imy_nx_ny
540!___________________________________________________________________________
541! pour imposer les conditions de mismip sur les bords du fleuve
542! a appeler apres imx_imy_nx_ny
543
544subroutine mismip_boundary_cond
545if (itracebug.eq.1)  call tracebug(' Subroutine mismip_boundray_cond')
546
547! Condition pas de flux sur les bords nord et sud
548
549 imy_diag(:,2)      = 1
550 imy_diag(:,3)      = 1
551 imy_diag(:,ny-1)   = 1
552 imy_diag(:,ny)     = 1
553
554
555 Uybar(:,2)    = 0.
556 Uybar(:,3)    = 0.
557 Uybar(:,ny-1) = 0.
558 Uybar(:,ny)   = 0.
559
560
561! condition pas de cisaillement sur les bords nord et sud
562imx_diag(:,2)    = -1
563imx_diag(:,ny-1) = -3
564
565! coins
566imx_diag(2,2)     =  -41
567imx_diag(nx,2)    =  -12
568imx_diag(2,ny-1)  =  -34
569imx_diag(nx,ny-1) =  -23
570imx_diag(1,:)     =    0     ! ces points sont hors grille
571
572end subroutine mismip_boundary_cond
573
574!end module diagno_L2_mod
575end module diagno_mod
Note: See TracBrowser for help on using the repository browser.