source: branches/iLoveclim/SOURCES/dragging_neff_slope_mod.f90 @ 78

Last change on this file since 78 was 78, checked in by roche, 8 years ago

Corrected a few little issues to create libgrisli with gfortran. afq, dmr

File size: 14.4 KB
Line 
1!> \file dragging_neff_contmaj_mod.f90
2!! Defini les zones de stream avec 3 criteres
3!<
4
5!> \namespace  dragging_neff_contmaj
6!! Defini les zones de stream avec 3 criteres
7!! \author ...
8!! \date ...
9!! @note Les trois criteres sont:
10!! @note   * un critere sur la pression effective
11!! @note   * un critere de continuite depuis la cote
12!! @note   * un critere sur la courbure du socle (si negatif, vallees)
13!! @note Used module
14!! @note   - use module3D_phy
15!! @note   - use param_phy_mod
16!<
17
18module dragging_neff_slope
19
20! Defini les zones de stream avec :
21! * un critere sur la pression effective
22! * un critere de continuite depuis la cote
23! * un critere sur la courbure du socle (si negatif, vallees)
24
25use module3d_phy
26use param_phy_mod
27use interface_input
28use io_netcdf_grisli
29
30implicit none
31
32logical,dimension(nx,ny) :: fleuve
33logical,dimension(nx,ny) :: cote
34logical,dimension(nx,ny) :: slowssamx ! not actual stream, but ssa used as Ub
35logical,dimension(nx,ny) :: slowssamy ! not actual stream, but ssa used as Ub
36logical,dimension(nx,ny) :: slowssa   ! not actual stream, but ssa used as Ub
37
38real,dimension(nx,ny) :: hires_slope ! slope comupted on a high resolution topography
39character(len=100) :: slope_fich     ! fichier grille
40character(len=100) :: file_ncdf      !< fichier netcdf issue des fichiers .dat
41
42real :: valmax
43integer :: imax,jmax
44integer :: i_moins1,i_plus1,j_moins1,j_plus1
45integer :: lmax=20
46integer :: idep,jdep,iloc,jloc
47
48
49real :: tostick   ! pour la glace posee
50real :: betamin   ! betamin : (Pa) frottement mini sous les streams
51real :: tob_ile    ! pour les iles
52real :: cry_lim=50.  ! courbure limite pour le suivi des fleuves
53
54real,dimension(nx,ny) :: neff ! pression effective noeuds majeurs
55real :: seuil_neff    ! seuil sur la pression effective pour avoir glissement en zone sediment
56real :: coef_gz       ! coef frottement zones stream std  (10)
57real :: coef_ile      ! coef frottement zones iles   (0.1)
58
59real, dimension(nx,ny) :: Vcol_x           !< uniquement pour compatibilite avec spinup cat
60real, dimension(nx,ny) :: Vcol_y           !< uniquement pour compatibilite avec spinup cat
61real, dimension(nx,ny) :: Vsl_x            !< uniquement pour compatibilite avec spinup cat
62real, dimension(nx,ny) :: Vsl_y            !< uniquement pour compatibilite avec spinup cat
63logical :: corr_def = .false.              !< for deformation correction, pour compatibilite beta
64
65contains
66!-------------------------------------------------------------------------------
67
68!> SUBROUTINE: init_dragging
69!! Cette routine fait l'initialisation du dragging.
70!>
71subroutine init_dragging      ! Cette routine fait l'initialisation du dragging.
72
73implicit none
74
75! local variables, defining the rugosity-enhanced flow
76real :: expo_slope
77real :: pente_min, pente_max
78
79namelist/drag_neff_slope/cf,betamax,betamin,toblim,tostick,seuil_neff,coef_gz,coef_ile,slope_fich,expo_slope,pente_min,pente_max
80
81if (itracebug.eq.1)  call tracebug(' dragging avec neff et slope')
82
83
84! formats pour les ecritures dans 42
85428 format(A)
86
87! lecture des parametres du run                      block drag neff
88!--------------------------------------------------------------------
89
90rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
91read(num_param,drag_neff_slope)
92
93write(num_rep_42,428)'!___________________________________________________________'
94write(num_rep_42,428) '&drag_neff_slope          ! nom du bloc dragging neff slope'
95write(num_rep_42,*)
96write(num_rep_42,*) 'cf               = ',cf
97write(num_rep_42,*) 'betamax          = ', betamax
98write(num_rep_42,*) 'betamin          = ', betamin
99write(num_rep_42,*) 'toblim           = ', toblim
100write(num_rep_42,*) 'tostick          = ', tostick
101write(num_rep_42,*) 'seuil_neff       = ', seuil_neff
102write(num_rep_42,*) 'coef_gz          = ', coef_gz
103write(num_rep_42,*) 'coef_ile         = ', coef_ile
104write(num_rep_42,'(A,A)') 'slope_fich = ', slope_fich
105write(num_rep_42,*) 'expo_slope       = ', expo_slope
106write(num_rep_42,*) 'pente_min        = ', pente_min
107write(num_rep_42,*) 'pente_max        = ', pente_max
108write(num_rep_42,*)'/'
109write(num_rep_42,428) '! cf coefficient de la loi de frottement fonction Neff'
110write(num_rep_42,428) '! betamax : (Pa) frottement maxi sous les streams '
111write(num_rep_42,428) '! betamin : (Pa) frottement mini sous les streams '
112write(num_rep_42,428) '! toblim : (Pa)  pour les iles '
113write(num_rep_42,428) '! tostick : (Pa)  pour les points non flgzmx '
114write(num_rep_42,428) '! seuil_neff (Pa) seuil sur la pression effective pour avoir glissement'
115write(num_rep_42,428) '! coef_gz : coef frottement zones stream std'
116write(num_rep_42,428) '! coef_ile : coef frottement zones iles'
117write(num_rep_42,428) '! slope_fich : fichier pente bedrock'
118write(num_rep_42,428) '! expo_slope : exposant fonction pente'
119write(num_rep_42,428) '! pente_min : no flow enhancement below this'
120write(num_rep_42,428) '! pente_max : maximum flow enhancement above this'
121write(num_rep_42,*)
122
123!tostick=1.e5   ! valeurs pour les points non flgzmx
124tob_ile=betamax/2.
125moteurmax=toblim
126
127! betamax_2d depends on sub-grid slopes.
128slope_fich=trim(dirnameinp)//trim(slope_fich)
129call lect_input(1,'slope',1,hires_slope(:,:),slope_fich,file_ncdf)
130
131! from slopes, we create an index between 0 & 1
132! 1 is very mountainous, 0 is flat
133hires_slope(:,:)=(max(min(hires_slope(:,:),pente_max),pente_min)-pente_min)/(pente_max-pente_min)
134! now we compute the actual betamax used by the remplimat routines
135! /!\ the slope is used to modify the beta where we have a temperate base,
136! but NO ice stream... -> Slow SSA zone (SSA used to compute Ub)
137betamax_2d(:,:)=max ( tostick * (1. - (1 - betamax / tostick ) * hires_slope(:,:)**(1./expo_slope)) , betamax )
138!do j=1,ny
139!   do i=1,nx
140!      write(18745,*) betamax_2d (i,j)
141!   enddo
142!enddo
143
144!-------------------------------------------------------------------
145! masque stream
146      mstream_mx(:,:)=1
147      mstream_my(:,:)=1
148
149
150! coefficient permettant de modifier le basal drag.
151      drag_mx(:,:)=1.
152      drag_my(:,:)=1.
153
154where (socle_cry(:,:).lt.cry_lim)
155   debug_3D(:,:,25)=1
156elsewhere
157   debug_3D(:,:,25)=0
158endwhere
159
160
161      return
162      end subroutine init_dragging
163!________________________________________________________________________________
164
165!> SUBROUTINE: dragging
166!! Defini la localisation des streams et le frottement basal
167!>
168!-------------------------------------------------------------------------
169subroutine dragging   ! defini la localisation des streams et le frottement basal
170!$ USE OMP_LIB
171
172!         les iles n'ont pas de condition neff mais ont la condition toblim
173!         (ce bloc etait avant dans flottab)
174
175!$OMP PARALLEL
176!$OMP DO
177do j=2,ny
178   do i=2,nx
179      ilemx(i,j)=ilemx(i,j).and.(abs(rog*Hmx(i,j)*sdx(i,j)).lt.toblim)
180      ilemy(i,j)=ilemy(i,j).and.(abs(rog*Hmy(i,j)*sdy(i,j)).lt.toblim)
181   end do
182end do
183!$OMP END DO
184
185! le calcul des fleuves se fait sur les mailles majeures en partant de la cote
186
187
188
189
190! le gzmx initial a ete calculé dans flottab pour les points a cheval sur la grounding line
191
192! Partant de la cote, le fleuve est determine en remontant vers le point de hauteur d'eau max
193! tant que ce point est superieur a hwatermax.
194
195! Attention : ce systeme ne permet pas d'avoir des fleuves convergents
196!             et les fleuves n'ont une épaisseur que de 1 noeud.
197!$OMP WORKSHARE
198fleuvemx(:,:)=.false.
199fleuvemy(:,:)=.false.
200fleuve(:,:)=.false.
201cote(:,:)=.false.
202!$OMP END WORKSHARE
203
204! detection des cotes
205!$OMP DO
206do  j=2,ny-1
207   do i=2,nx-1
208      if ((.not.flot(i,j)).and. &
209      ((flot(i+1,j)).or.(flot(i,j+1)).or.(flot(i-1,j)).or.(flot(i,j-1)))) then
210         cote(i,j)=.true.
211      endif
212   end do
213end do
214!$OMP END DO
215
216! calcul de neff (pression effective sur noeuds majeurs)
217!$OMP DO
218do j=1,ny-1
219   do i=1,nx-1
220        neff(i,j)=(neffmx(i,j)+neffmx(i+1,j)+neffmy(i,j)+neffmy(i,j+1))/4
221   enddo
222enddo
223!$OMP END DO
224!aurel, for the borders:
225!$OMP WORKSHARE
226neff(:,ny)=1.e5
227neff(nx,:)=1.e5
228
229
230!!$
231!!$fleuve_maj: do j=2,ny-1
232!!$ifleuve:   do i=2,nx-1
233!!$
234!!$cote_detect :  if (cote(i,j)) then
235!!$         idep=i
236!!$         jdep=j
237!!$
238!!$         if (socle_cry(i,j).lt.0.) then    ! dans une vallee
239!!$            fleuve(i,j)=.true.
240!!$         else
241!!$            cote(i,j)=.false.
242!!$            cycle ifleuve
243!!$         endif
244!!$
245!!$suit : do l=1,lmax         ! debut de la boucle de suivi, lmax longueur maxi des fleuves
246!!$           i_moins1=max(idep-1,2)
247!!$           j_moins1=max(jdep-1,1)
248!!$           i_plus1=min(idep+1,nx)
249!!$           j_plus1=min(jdep+1,ny)
250!!$
251!!$! recherche du max en suivant le socle le plus profond
252!!$! * en excluant les points flottants
253!!$! * et ceux qui sont deja tagges fleuves
254!!$
255!!$           valmax=1000.
256!!$
257!!$           do jloc=j_moins1,j_plus1
258!!$              do iloc=i_moins1,i_plus1
259!!$
260!!$                 if ((B(iloc,jloc).lt.valmax)      &
261!!$                      .and.(.not.flot(iloc,jloc))  &
262!!$                      .and.(.not.fleuve(iloc,jloc)).and.(socle_cry(iloc,jloc).lt.cry_lim)) then
263!!$                    imax=iloc
264!!$                    jmax=jloc
265!!$                    valmax=B(iloc,jloc)
266!!$                 endif
267!!$              end do
268!!$           end do
269!!$
270!!$         if ((hwater(imax,jmax).gt.hwatstream).and.(socle_cry(i,j).lt.cry_lim)) then
271!!$            fleuve(imax,jmax)=.true.
272!!$            idep=imax
273!!$            jdep=jmax
274!!$         else
275!!$            fleuve(imax,jmax)=.false.
276!!$            exit suit
277!!$         end if
278!!$
279!!$      end do suit
280!!$
281!!$   end if cote_detect
282!!$
283!!$end do ifleuve
284!!$end do fleuve_maj
285
286! aurel, we add the neff threshold:
287where ((neff(:,:).le.seuil_neff).and.(.not.flot(:,:)).and.(H(:,:).gt.1.)) fleuve(:,:)=.true.
288!$OMP END WORKSHARE
289
290!$OMP DO
291do j=1,ny-1
292   do i=1,nx-1
293      if (fleuve(i,j)) then
294         fleuvemx(i,j)=.true.
295         fleuvemx(i+1,j)=.true.
296         fleuvemy(i,j)=.true.
297         fleuvemy(i,j+1)=.true.
298      end if
299   end do
300end do
301!$OMP END DO
302
303! we look for the warm based points that will not be treated as stream (ub from SSA):
304!$OMP WORKSHARE
305slowssa(:,:)=.false.
306slowssamx(:,:)=.false.
307slowssamy(:,:)=.false.
308!$OMP END WORKSHARE
309!$OMP DO
310do  j=1,ny
311   do i=1,nx
312      !if ((not(flot(i,j))).and.(hwater(i,j).gt.0.1)) slowssa(i,j)=.true.
313      if ((.not.(flot(i,j))).and.(ibase(i,j).ne.1).and.(H(i,j).gt.1.)) then
314        slowssa(i,j)=.true.
315      endif
316   end do
317end do
318!$OMP END DO
319!$OMP DO
320do j=1,ny-1
321   do i=1,nx-1
322      if (slowssa(i,j)) then
323         slowssamx(i,j)=.true.
324         slowssamx(i+1,j)=.true.
325         slowssamy(i,j)=.true.
326         slowssamy(i,j+1)=.true.
327      end if
328   end do
329end do
330!$OMP END DO
331!$OMP DO
332do j=1,ny
333   do i=1,nx
334
335      ! the actual streams and the warm based points are gzmx now:
336      if ( ((.not.ilemx(i,j)).and.(fleuvemx(i,j))) .or. ((.not.ilemx(i,j)).and.(slowssamx(i,j))) ) gzmx(i,j)=.true.
337
338
339! calcul du frottement basal (ce bloc etait avant dans neffect)
340
341      if (cotemx(i,j)) then                        ! point cotier
342         betamx(i,j)=cf*neffmx(i,j)
343         betamx(i,j)=min(betamx(i,j),betamax)
344
345      else if ((gzmx(i,j)).and.(.not.cotemx(i,j))) then ! tous les points SSA
346
347         if (fleuvemx(i,j)) then                 ! the actual streams
348            betamx(i,j)=cf*neffmx(i,j)*coef_gz
349            betamx(i,j)=min(betamx(i,j),betamax)
350            betamx(i,j)=max(betamx(i,j),betamin)
351
352            if (cf*neffmx(i,j).gt.betamax*2.) then  ! a stream that's becoming grounded...
353               if (slowssamx(i,j)) then
354                  betamx(i,j)=betamax_2d(i,j)
355               else
356                  gzmx(i,j)=.false.
357                  betamx(i,j)=tostick
358               endif
359            endif
360
361         else                    ! not an actual stream, SSA is used to compute Ub
362            betamx(i,j)=betamax_2d(i,j)
363         endif
364
365      else if (ilemx(i,j)) then
366         betamx(i,j)=cf*neffmx(i,j)*coef_ile
367         betamx(i,j)=min(betamx(i,j),tob_ile)
368      else if (flotmx(i,j)) then     ! flottant ou ile
369         betamx(i,j)=0.
370      else                                         ! grounded, SIA
371         betamx(i,j)=tostick                       ! frottement glace posee (1 bar)
372      endif
373
374   end do
375end do
376!$OMP END DO
377
378!$OMP DO
379do j=1,ny
380   do i=1,nx
381
382      ! the actual streams and the warm based points are gzmx now:
383      if ( ((.not.ilemy(i,j)).and.(fleuvemy(i,j))) .or. ((.not.ilemy(i,j)).and.(slowssamy(i,j))) ) gzmy(i,j)=.true.
384
385
386! calcul du frottement basal (ce bloc etait avant dans neffect)
387
388      if (cotemy(i,j)) then                        ! point cotier
389         betamy(i,j)=cf*neffmy(i,j)
390         betamy(i,j)=min(betamy(i,j),betamax)
391
392      else if ((gzmy(i,j)).and.(.not.cotemy(i,j))) then ! tous les points SSA
393
394         if (fleuvemy(i,j)) then                 ! the actual streams
395            betamy(i,j)=cf*neffmy(i,j)*coef_gz
396            betamy(i,j)=min(betamy(i,j),betamax)
397            betamy(i,j)=max(betamy(i,j),betamin)
398
399            if (cf*neffmy(i,j).gt.betamax*2.) then  ! a stream that's becoming grounded...
400               if (slowssamy(i,j)) then
401                  betamy(i,j)=betamax_2d(i,j)
402               else
403                  gzmy(i,j)=.false.
404                  betamy(i,j)=tostick
405               endif
406            endif
407
408         else                    ! not an actual stream, SSA is used to compute Ub
409            betamy(i,j)=betamax_2d(i,j)
410         endif
411
412      else if (ilemy(i,j)) then
413         betamy(i,j)=cf*neffmy(i,j)*coef_ile
414         betamy(i,j)=min(betamy(i,j),tob_ile)
415      else if (flotmy(i,j)) then     ! flottant ou ile
416         betamy(i,j)=0.
417      else                                         ! grounded, SIA
418         betamy(i,j)=tostick                       ! frottement glace posee (1 bar)
419      endif
420
421   end do
422end do
423!$OMP END DO
424
425!$OMP DO
426do j=2,ny-1
427   do i=2,nx-1
428      beta_centre(i,j) = ((betamx(i,j)+betamx(i+1,j)) &
429          + (betamy(i,j)+betamy(i,j+1)))*0.25
430   end do
431end do
432!$OMP END DO
433!$OMP END PARALLEL
434
435!~ where (fleuve(:,:))
436!~    debug_3D(:,:,1)=1
437!~ elsewhere (flot(:,:))
438!~    debug_3D(:,:,1)=2
439!~ elsewhere
440!~    debug_3D(:,:,1)=0
441!~ endwhere
442!~
443!~ where (cote(:,:))
444!~    debug_3D(:,:,2)=1
445!~ elsewhere
446!~    debug_3D(:,:,2)=0
447!~ endwhere
448!~
449!~ where (fleuvemx(:,:))
450!~    debug_3D(:,:,3)=1
451!~ elsewhere
452!~    debug_3D(:,:,3)=0
453!~ endwhere
454!~
455!~ where (flotmx(:,:))
456!~    debug_3D(:,:,3)=-1
457!~ endwhere
458
459!_____________________
460
461
462!~ where (fleuvemy(:,:))
463!~    debug_3D(:,:,4)=1
464!~ elsewhere
465!~    debug_3D(:,:,4)=0
466!~ endwhere
467!~
468!~ where (flotmy(:,:))
469!~    debug_3D(:,:,4)=-1
470!~ end where
471!~
472!~ debug_3D(:,:,23)= abs(RO*G*HMX(:,:)*sdx(:,:)*1.e-5)
473!~ debug_3D(:,:,24)= abs(RO*G*HMY(:,:)*sdy(:,:)*1.e-5)
474
475return
476end subroutine dragging
477
478end module dragging_neff_slope
479
Note: See TracBrowser for help on using the repository browser.