source: branches/iLoveclim/SOURCES/bilan_eau_mod.f90 @ 146

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

Grisli-iLoveclim branch: merged to trunk at revision 145

File size: 4.9 KB
Line 
1!> \file bilan_eau.f90
2!! Clacul du bilan d'eau sur la calotte
3!<
4     
5
6!> MODULE: bilan_eau
7!! Calcule le bilan d'eau sur la grille GRISLI
8!! \author C. Dumas
9!! \date 20/02/2017
10!! @note Permet de vérifier que le bilan d'eau est ok et qu'il n'y a pas de fuite.
11!>
12
13! bilan d'eau :
14! ce qui tombe : Acc
15! ce qui sort : Bmelt, Abl, calving, ablbord
16! ce qui est stocké : masse de glace
17! le total de tous ces termes doit être constant (sur la grille, pas localement)
18
19module bilan_eau_mod
20
21
22use module3D_phy
23implicit none
24
25real :: sum_H
26
27
28real,dimension(nx,ny) :: tot_water    !< bilan d'eau
29real,dimension(nx,ny) :: H_beau_old, diff_H_2D, diff_H_water_bilan
30real,dimension(nx,ny) :: Bm_dtt       !< mass balance on ice points accumulated during dtt
31real,dimension(nx,ny) :: Bmelt_dtt    !< basal melting on ice points accumulated during dtt
32real,dimension(nx,ny) :: calv_dtt     !< calving sur dtt (pour calcul bilan d'eau)
33real,dimension(nx,ny) :: archimtab    ! point pose si > 0
34real,dimension(nx,ny) :: grline_dtt   ! grounding line flux during dtt
35
36real :: sum_H_old
37real :: diff_H
38real :: alpha_flot                      ! ro/row
39
40real,dimension(nx,ny) :: bm_dt,bmelt_dt
41
42
43contains
44
45subroutine init_bilan_eau
46 ! initialisation des variables
47  diff_H=0.
48  sum_H_old = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1)
49  tot_water(:,:)=0.
50  bm_dt(:,:)=0.
51  bmelt_dt(:,:)=0.
52  alpha_flot=ro/row
53! iLOVECLIM initialisation of water conservation related variables
54  trendWAC=0.
55  smbWAC(:,:)=0.
56  bmeltWAC(:,:)=0.
57  calvingWAC(:,:)=0.
58end subroutine init_bilan_eau
59
60
61
62
63subroutine bilan_eau
64
65tot_water(:,:)=0.
66
67bm_dt(:,:)=0.
68bmelt_dt(:,:)=0.
69
70bm_dt(2:nx-1,2:ny-1)=bm(2:nx-1,2:ny-1)*dt
71bmelt_dt(2:nx-1,2:ny-1)=bmelt(2:nx-1,2:ny-1)*dt
72!~ where (Bm(:,:).lt.0.)
73!~      bm_dt(:,:)=max(Bm(:,:)*dt,-H(:,:))
74!~ elsewhere
75!~      bm_dt(:,:)=bm(:,:)*dt
76!~ endwhere
77
78!~ where (Bmelt(:,:).lt.0.)
79!~      bmelt_dt(:,:)=max(Bmelt(:,:)*dt,-H(:,:))
80!~ elsewhere
81!~      bmelt_dt(:,:)=bmelt(:,:)*dt
82!~ endwhere
83
84
85! on fait la somme sur la grille en excluant les bords :
86
87sum_H = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1)
88
89diff_H = diff_H + (sum_H - sum_H_old) ! on calcul la variation de volume a chaque dt
90
91diff_H_2D(2:nx-1,2:ny-1)=H(2:nx-1,2:ny-1)-H_beau_old(2:nx-1,2:ny-1)
92
93where (ice(2:nx-1,2:ny-1).eq.1)
94   Bm_dtt(2:nx-1,2:ny-1) = Bm_dtt(2:nx-1,2:ny-1) + Bm_dt(2:nx-1,2:ny-1) !* dt ! somme Bm sur dt
95   bmelt_dtt(2:nx-1,2:ny-1) = bmelt_dtt(2:nx-1,2:ny-1) + bmelt_dt(2:nx-1,2:ny-1) ! * dt ! somme bmelt sur dt
96endwhere
97
98archimtab(:,:) = Bsoc(:,:)+H(:,:)*alpha_flot - sealevel
99gr_line(:,:)=0
100do j=1,ny
101  do i=1,nx
102     !afq    if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.).and.(Bsoc(i,j).LE.sealevel)) then ! grounded with ice
103     if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.)) then ! grounded with ice
104      if (archimtab(i-1,j).LT.0..and.Uxbar(i,j).LT.0..and..not.flot_marais(i-1,j)) gr_line(i,j)=1
105      if (archimtab(i+1,j).LT.0..and.Uxbar(i+1,j).GT.0..and..not.flot_marais(i+1,j)) gr_line(i,j)=1
106      if (archimtab(i,j-1).LT.0..and.Uybar(i,j).LT.0..and..not.flot_marais(i,j-1)) gr_line(i,j)=1
107      if (archimtab(i,j+1).LT.0..and.Uybar(i,j+1).GT.0..and..not.flot_marais(i,j+1)) gr_line(i,j)=1
108    endif
109  enddo
110enddo
111
112where (gr_line(:,:).eq.1)
113!~   grline_dtt(:,:)= (((uxbar(:,:)+eoshift(uxbar(:,:),shift=1,boundary=0.,dim=1))**2+ &
114!~                     (uybar(:,:)+eoshift(uybar(:,:),shift=1,boundary=0.,dim=2))**2)**0.5)*0.5 &
115!~                     *H(:,:) + grline_dtt(:,:)
116   grline_dtt(:,:)= - sqrt(                                                                        &
117                           ( (uxbar(:,:)+eoshift(uxbar(:,:),shift=1,boundary=0.,dim=1))*dy/2. )**2 +  &
118                           ( (uybar(:,:)+eoshift(uybar(:,:),shift=1,boundary=0.,dim=2))*dx/2. )**2 )  &
119                           * H(:,:) * dt + grline_dtt(:,:)
120endwhere
121
122
123if (isynchro.eq.1) then
124! on raisonne en bilan annuel pour simplifier :
125!~      where (ice(2:nx-1,2:ny-1).eq.1)
126!~              tot_water(2:nx-1,2:ny-1) = (Bm_dtt(2:nx-1,2:ny-1) - Bmelt_dtt(2:nx-1,2:ny-1) + calv_dtt(2:nx-1,2:ny-1) - ablbord_dtt(2:nx-1,2:ny-1)) / dtt
127!~              elsewhere
128!~              tot_water(2:nx-1,2:ny-1) = (calv_dtt(2:nx-1,2:ny-1) - ablbord_dtt(2:nx-1,2:ny-1)) / dtt
129!~      endwhere
130!cdc pas besoin du test sur ice ici, il a ete fait avant (et le masque ice varie a chaque dt)   
131  tot_water(2:nx-1,2:ny-1) = (Bm_dtt(2:nx-1,2:ny-1) - Bmelt_dtt(2:nx-1,2:ny-1) + calv_dtt(2:nx-1,2:ny-1) - ablbord_dtt(2:nx-1,2:ny-1)) / dtt
132   
133! bilan d'eau sur la grille :
134  water_bilan=sum(tot_water(:,:))
135  diff_H = diff_H/dtt
136
137!999 format(f0.2,1x,e15.8,1x,i10,8(1x,e15.8))
138!       write(6,999),time,sum_H,count(ice(:,:)==1),diff_H,water_bilan,sum(calv_dtt(:,:))/dtt,sum(ablbord_dtt(:,:))/dtt,sum(bmelt_dtt(:,:),mask=ice(:,:)==1)/dtt,sum(bm(:,:),mask=ice(:,:)==1),sum(Bm_dtt(:,:))/dtt,sum(bmelt_dtt(:,:))/dtt
139  diff_H_water_bilan(2:nx-1,2:ny-1)=tot_water(2:nx-1,2:ny-1)-diff_H_2D(2:nx-1,2:ny-1)
140
141endif
142sum_H_old=sum_H
143
144H_beau_old(:,:)=H(:,:)
145
146end subroutine bilan_eau
147
148end module bilan_eau_mod
Note: See TracBrowser for help on using the repository browser.