source: trunk/SOURCES/eaubasale-0.5_mod.f90 @ 170

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

Minor bug correction in flottab + compatibility between ant40 and ant16 geometries + get rid of unused variable in eaubasale.

File size: 13.9 KB
Line 
1!> \file eaubasale-0.5_mod.f90
2!! TOOOOOOOOOOO DOOOOOOOOOOOOO
3!<
4
5!> \namespace eau_basale
6!! TOOOOOOOOOOO DOOOOOOOOOOOOO
7!! \author ...
8!! \date ...
9!! @note Used modules
10!! @note   - use module3D_phy
11!! @note   - use eau_basale
12!! @note   - use param_phy_mod
13!! @note   - use relaxation_waterdif_mod
14!<
15module eau_basale
16
17use module3d_phy
18use param_phy_mod
19use relaxation_waterdif_mod ! module qui contient la routine relaxation
20                           ! pour l'eau avec interface explicite
21
22
23implicit none
24
25! dimensionnements
26!------------------------------------------------------------------------
27    LOGICAL :: ecoulement_eau
28
29    REAL :: KONDMAX
30    real :: kond0
31    REAL :: INFILTR
32    REAL :: hmax_till    !< épaisseur de la couche de till
33    REAL :: hmax_wat     !< épaisseur de la couche d'eau dans le till
34    REAL :: poro_till    !< porosité du till
35    REAL :: Zflot        !< hauteur d'eau donnant la flottaison
36    real :: keffmax      !< kondmax*hmax_wat
37    real :: nefflocal
38
39    REAL,dimension(NX,NY) :: limit_hw    !< conditions aux limites
40    integer,dimension(NX,NY) :: klimit    !< ou appliquer les conditions
41    REAL,dimension(NX,NY) :: pot_w             !< pour calculer le gradient de pression
42    REAL,dimension(NX,NY) :: pot_f             !< pour les points flottants
43    REAL,dimension(NX,NY) :: hw                !< hauteur d'eau dans le till, limite a hmax_wat
44                                                 !< c'est la hauteur sur laquelle peut se faire
45                                                 !< l'ecoulement de l'eau
46    REAL,dimension(nx,ny) :: keff              !< conductivite effective : Kond*hw
47
48
49    REAL,dimension(NX,NY) :: bmelt_w          !< fusion (terme source) exprimé en m d'eau
50    REAL,dimension(NX,NY) :: vieuxhwater      !< valeur de hwater au debut de l'appel
51
52
53    INTEGER :: NXlocal,NYlocal !< pour passer NX et NY en parametre a la routine relaxation
54
55
56contains
57!> SUBROUTINE: init_eaubasale
58!!Initialisation du block eaubasale
59!>
60subroutine init_eaubasale
61
62namelist/eaubasale1/ecoulement_eau,hwatermax,infiltr 
63namelist/param_hydr/hmax_till,poro_till,kond0
64
65! formats pour les ecritures dans 42
66428 format(A)
67
68! lecture des parametres du run                      block eaubasale1
69!--------------------------------------------------------------------
70
71
72rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
73read(num_param,eaubasale1)
74write(num_rep_42,428)'!___________________________________________________________' 
75write(num_rep_42,428) '&eaubasale1              ! nom du premier bloc eau basale '
76write(num_rep_42,*)
77write(num_rep_42,*) 'ecoulement_eau = ',ecoulement_eau
78write(num_rep_42,*) 'hwatermax      = ',hwatermax
79write(num_rep_42,*) 'infiltr        = ', infiltr
80write(num_rep_42,*)'/'                           
81write(num_rep_42,428) '! ecoulement eau : .false. -> modele bucket, sinon equ. diffusion'
82write(num_rep_42,428) '! hwatermax :  hauteur d eau basale maximum dans le sediment (m)'
83write(num_rep_42,428) '! infiltr est la quantite d eau qui peut s infiltrer dans le sol (m/an)'
84write(num_rep_42,*)
85
86
87!valeurs numeriques des parametres hydrauliques
88
89rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
90read(num_param,param_hydr)
91
92write(num_rep_42,428)'!___________________________________________________________' 
93write(num_rep_42,428) '&param_hydr             ! nom du  bloc parametres hydrauliques '
94write(num_rep_42,*)
95write(num_rep_42,*) 'hmax_till      = ',hmax_till
96write(num_rep_42,*) 'poro_till      = ',poro_till
97write(num_rep_42,*) 'kond0          = ',kond0 
98write(num_rep_42,*)'/'                           
99write(num_rep_42,428) '! hmax_till (m) : epaisseur max du sediment '
100write(num_rep_42,428) '! poro_till : porosite du sediment '
101write(num_rep_42,428) '! conductivite du sediment :  kond0 (m/s)'
102write(num_rep_42,*)
103
104
105
106
107hmax_wat=hmax_till*poro_till ! hauteur maxi que peut atteindre l'eau dans la couche de till
108
109
110! Conductivite hydraulique : cond passée en m/an ( car le dt est en années)
111kond(:,:)=kond0
112kond(:,:) = kond(:,:)*SECYEAR 
113kondmax   = 1.*SECYEAR 
114keffmax=kondmax*hmax_wat
115hdotwater(:,:)=0.
116
117
118NXlocal=NX
119NYlocal=NY
120
121end subroutine init_eaubasale
122
123!> SUBROUTINE: eaubasale
124!! to do
125!>
126subroutine eaubasale !(pwater)   version correspondant à la thèse de Vincent
127  ! A terme, il faudrait en faire un module
128!$ USE OMP_LIB
129!~   integer :: t1,t2,ir
130!~   real                           :: temps, t_cpu_0, t_cpu_1, t_cpu, norme 
131!~   
132!~    ! Temps CPU de calcul initial.
133!~    call cpu_time(t_cpu_0)
134!~    ! Temps elapsed de reference.
135!~    call system_clock(count=t1, count_rate=ir)
136
137
138
139
140  if (itracebug.eq.1)  call tracebug(' Entree dans routine eau basale')
141
142!$OMP PARALLEL
143!$OMP WORKSHARE
144  vieuxhwater(:,:) = hwater(:,:)
145  kond(:,:) = kond0*SECYEAR 
146
147
148  ! conditions aux limites
149  klimit(:,:)=0
150  limit_hw(:,:)=-9999.
151!$OMP END WORKSHARE
152!$OMP DO 
153  do j=1,ny
154     do i=1,nx
155
156
157        if (flot(i,j))then  ! points flottants
158           klimit(i,j)=1
159           limit_hw(i,j)=(sealevel-Bsoc(i,j))*rowg/rofreshg
160
161        else if (IBASE(I,J).eq.1) then ! base froide
162           klimit(i,j)=1
163           limit_hw(i,j)=0.
164
165        else if ((.not.flot(i,j)).and.(H(i,j).lt.1.)) then  ! bord de la calotte
166           klimit(i,j)=1
167           limit_hw(i,j)=10.    ! riviere de 10 m de profondeur
168        endif
169
170     end do
171  end do
172!$OMP END DO
173
174!$OMP DO
175!  do j=2,ny-1
176  do j=1,ny
177     do i=1,nx
178        bmelt_w(i,j)=bmelt(i,j)*rofresh/ro   
179        hwater(i,j)=max(hwater(i,j),0.)
180        hw(i,j)=min(hwater(i,j),hmax_wat) 
181     enddo
182  enddo
183!$OMP END DO
184!$OMP END PARALLEL
185
186  ecoul:  if (ecoulement_eau) then
187     !  print*,'===dans eaubasale t, dt',time,dt,'kond 1.0e-5'
188     !   write(6,*) 'entree ecoulement_eau'
189     !$OMP PARALLEL
190     !$OMP DO
191     do j=1,ny
192        do i=1,nx             
193
194           !   calcul des potentiels
195           pot_w(I,J)=rofreshg*B(I,J)  ! potentiel de gravite
196
197           ! on ajoute pression glace mais pas la pression d'eau qui est traitée comme diffusion
198
199           pot_w(I,J)=pot_w(I,J)+rog*H(I,J)
200
201           pot_f(I,J)=rowg*(sealevel-S(i,j)+H(I,J))  ! pression a la base de l'ice shelf
202        enddo
203     enddo
204!$OMP END DO
205
206     ! sorties debug 17 juillet 2007
207     debug_3D(:,:,5)=pot_w(:,:)
208     debug_3D(:,:,6)=pot_f(:,:)
209     debug_3D(:,:,7)=pot_w(:,:)+rofreshg*hwater(:,:)
210     debug_3D(:,:,8)=hwater(:,:)
211!$OMP DO
212     do j=2,ny
213        do i=2,nx
214           if (H(i,j).gt.25.) then
215              !           calcul du gradient de pression
216              if (flotmx(i,j)) then
217                 pgx(i,j)=(pot_f(i-1,j)-pot_f(i,j))/dx
218              else
219                 pgx(i,j)=(pot_w(i-1,j)-pot_w(i,j))/dx
220              endif
221
222              if (flotmy(i,j)) then
223                 pgy(i,j)=(pot_f(i,j-1)-pot_f(i,j))/dy
224              else
225                 pgy(i,j)=(pot_w(i,j-1)-pot_w(i,j))/dy
226              endif
227           endif
228           pgx(i,j)=pgx(i,j)/rofreshg   ! pour passer pgx sans unité
229           pgy(i,j)=pgy(i,j)/rofreshg     
230        end do
231     end do
232!$OMP END DO
233!$OMP END PARALLEL
234
235     if (nt.gt.0) then
236        if (dt.gt.0.)  then !!!!!!!!!!!!!!!!!!!!!!relax_water si dt>0
237           !-------------------------------------------------------------------------
238           ! les points de la grounding line ont une conductivité hydraulique élevée
239           ! même si la base est froide.  modif catritz 18 janvier 2005
240           !open(166,file='erreur_eau')
241!$OMP PARALLEL
242!$OMP DO
243           do j=2,Ny-1
244              do i=2,Nx-1
245                 ! cond=0 si glace froide et pas sur la grounding line
246                 if ((IBASE(i,j).eq.1).and.   &
247                      (.not.flot(i,j-1)).and.(.not.flot(i,j+1)).and.  &
248                      (.not.flot(i-1,j)).and.(.not.flot(i+1,j)))  KOND(i,j)=0.! 1.0e-5
249
250                 ! cond infinie quand epaisseur faible et glace flottante
251                 if (flot(i,j).or.H(i,j).le.1.5)  kond(i,j)= kondmax
252
253                 ! conductivite forte lorsque N est faible (croit à partir de 100 bars)
254                 nefflocal=0.91*H(i,j)-hwater(i,j)
255                 nefflocal=max(100.,nefflocal)
256                 if (nefflocal.le.1000.) then
257                    kond(i,j)=kond(i,j)*1000./nefflocal
258                 endif
259                 kond(i,j)=min(kondmax,kond(i,j)) 
260
261                 ! conductivite effective (conductivité * taille du tuyau en m2/an)
262                 keff(i,j)=kond(i,j)*hw(i,j)
263              end do
264           end do
265!$OMP END DO
266           ! condition sur les bords de la grille
267!$OMP WORKSHARE
268           kond(1,:)=kondmax
269           kond(nx,:)=kondmax
270           kond(:,1)=kondmax
271           kond(:,ny)=kondmax
272           vieuxhwater(:,:) = hwater(:,:)
273!$OMP END WORKSHARE
274!$OMP END PARALLEL
275!!$OMP SINGLE
276           call relaxation_waterdif(nxlocal,nylocal,dt,dx,vieuxhwater,limit_hw,klimit,bmelt_w,infiltr,pgx,pgy,keff,keffmax,hwater)
277!!$OMP END SINGLE
278        else
279           !         print*,'dt=',dt,'pas de relax_water'
280        endif!!!!!!!!!!!!!!!!!! fin relax_water si dt>0
281
282     endif
283
284
285
286
287     ! Apres relaxation, boundary conditions, extremum values
288     ! ================, ===================, ===============
289
290     !   ------------variation d'epaisseur entre 2 pas de temps ------------
291
292     ! on le fait avant les butoirs pour justement pouvoir les estimer
293!$OMP PARALLEL
294     if (dt.gt.0.) then
295        !         print*,'dt=',dt,'pas de relax_water'
296        !$OMP DO
297        do j=1,ny
298           do i=1,nx
299              hdotwater(i,j)=(hwater(i,j)-vieuxhwater(i,j))/dt 
300           end do
301        end do
302        !$OMP END DO
303     endif
304
305!$OMP DO PRIVATE(Zflot)
306     do i=1,nx
307        do j=1,ny
308
309
310           !  ______________ valeurs de hwater et pwater _____________________________
311           !
312           if (flot(I,J).or.H(I,J).le.1.5) then ! we are outside of the ice sheet
313
314              if (flot(i,j)) then  ! if flot > hwater=hwater in ocean
315                 hwater(i,j)= sealevel - bsoc(i,j)
316                 !             hwater(i,j)= max(0.,hwater(i,j))
317                 if (hwater(i,j).lt.0.) hwater(i,j)=0.
318                 pwater(i,j)= hwater(i,j)*rowg
319              else
320                 hwater(i,j) = 0. ! bare grounded land > no hwater
321                 pwater(i,j)=0.
322              endif
323
324           else          !            sous la  calotte ----------------------
325
326              ! Attention le bloc suivant est pour le run 20
327              !           Zflot=row/ro*(sealevel-Bsoc(i,j))-10.
328              Zflot=H(i,j)*rog/rofreshg
329
330              if (hwater(i,j).le.0.) then
331                 hwater(i,j)=0.
332
333              else if (hwater(i,j).gt.zflot) then
334                 hwater(i,j)=zflot
335                 hw(i,j)=min(hwater(i,j),hmax_wat)
336                 pwater(i,j)=rofreshg*Hwater(i,j)
337              endif
338              !            if ((i.eq.60).and.(j.eq.60)) write(6,*) hw(i,j),hwater(i,j)
339
340              ! sinon
341
342              !          hw(i,j)=min(hw(i,j),hmax_wat) 
343              !          Hwater(i,j)=hw(i,j)
344              !          pwater(i,j)=rog*H(I,J)*(hw(I,J)/hmax_wat)**(3.5)
345           endif
346
347           ! bloc qui pourrait servir pour mettre l'eau encore plus sous pression
348           ! -----------------------------------------------------------------------------
349           !            if (HWATER(i,j).gt.poro_till*hmax_till) then
350           !             pwater(i,j)=pwater(i,j)+(HWATER(i,j)-poro_till*hmax_till)/(compress_w*hmax_till)
351           !            endif
352        end do
353     end do
354!$OMP END DO
355
356     !   ************ valeurs de HWATER pour les coins ********
357
358     hwater(1,1)=(hwater(1,2)+hwater(2,1))/2.
359     hwater(1,ny)=(hwater(1,ny-1)+hwater(2,ny))/2.
360     hwater(nx,1)=(hwater(nx,2)+hwater(nx-1,1))/2.
361     hwater(nx,ny)=(hwater(nx,ny-1)+hwater(nx-1,ny))/2.
362
363     ! pour les sorties de flux d'eau
364     !$OMP DO
365     do j=2,ny
366        do i=2,nx
367           if  (keff(i,j)==0..or.keff(i-1,j)==0.) then
368              phiwx(i,j)=0. ! to avoid division by o             
369           else
370              phiwx(i,j)=(pgx(i,j)+(hwater(i-1,j)-hwater(i,j))/dx)
371
372              phiwx(i,j)=phiwx(i,j)*2*(keff(i,j)*keff(i-1,j))/(keff(i,j)+keff(i-1,j))
373           endif
374           ! ligne pour sortir les pgx
375           pgx(i,j)=(pgx(i,j)+(hwater(i-1,j)-hwater(i,j))/dx)
376        end do
377     end do
378     !$OMP END DO
379     !$OMP DO
380     do j=2,ny
381        do i=2,nx
382           if  (keff(i,j)==0..or.keff(i,j-1)==0.) then
383              phiWy(i,j)=0. ! to avoid division by o
384           else
385              phiWy(i,j)=(pgy(i,j)+(hwater(i,j-1)-hwater(i,j))/dx)
386              phiWy(i,j)=phiWy(i,j)*2*(keff(i,j)*keff(i,j-1))/(keff(i,j)+keff(i,j-1))
387           endif
388           pgy(i,j)=(pgy(i,j)+(hwater(i,j-1)-hwater(i,j))/dx)
389        enddo
390     enddo
391     !$OMP END DO
392     !$OMP END PARALLEL
393
394  else  ! partie originellement dans icetemp à mettre dans un autre module
395     ! (système module choix)     hauteur d'eau cumulee
396
397     if (ISYNCHRO.eq.1) then
398        !$OMP PARALLEL
399        !$OMP DO
400        do j=1,ny
401           do i=1,nx
402              if (.not.flot(i,j)) then
403                 hwater(i,j)=hwater(i,j)+(bmelt(i,j)*dtt)
404                 hwater(i,j)=hwater(i,j)-(infiltr*dtt)
405                 hwater(i,j)=max(hwater(i,j),0.)
406                 hwater(i,j)=min(hwater(i,j),hwatermax)
407              else
408                 hwater(i,j)=hwatermax
409              endif
410              !        if (IBASE(I,J).eq.1) HWATER(I,J)=0.
411           end do
412        end do
413        !$OMP END DO
414        !$OMP END PARALLEL
415     end if
416     
417  endif ecoul
418
419!~   ! Temps elapsed final
420!~   call system_clock(count=t2, count_rate=ir)
421!~   temps=real(t2 - t1,kind=4)/real(ir,kind=4)
422!~   ! Temps CPU de calcul final
423!~   call cpu_time(t_cpu_1)
424!~   t_cpu = t_cpu_1 - t_cpu_0
425
426!~   ! Impression du resultat.
427!~   print '(//,3X,"Valeurs de nx et ny : ",I5,I5/,              &
428!~            & 3X,"Temps elapsed       : ",1PE10.3," sec.",/, &
429!~            & 3X,"Temps CPU           : ",1PE10.3," sec.",/, &
430!~            & 3X,"Norme (PB si /= 0)  : ",1PE10.3,//)', &
431!~            nx,ny,temps,t_cpu,norme
432
433  return
434end subroutine eaubasale
435 end module eau_basale
Note: See TracBrowser for help on using the repository browser.