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

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

iLoveclim branch, further additions for water conservation

File size: 3.4 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)
33
34real :: sum_H_old
35real :: diff_H
36
37real,dimension(nx,ny) :: bm_dt,bmelt_dt
38
39
40contains
41
42subroutine init_bilan_eau
43 ! initialisation des variables
44        diff_H=0.
45        sum_H_old = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1)
46        tot_water(:,:)=0.
47        bm_dt(:,:)=0.
48        bmelt_dt(:,:)=0.
49! iLOVECLIM initialisation of water conservation related variables
50        trendWAC=0.
51        smbWAC(:,:)=0.
52        bmeltWAC(:,:)=0.
53        calvingWAC(:,:)=0.
54end subroutine init_bilan_eau
55
56       
57
58
59subroutine bilan_eau
60
61tot_water(:,:)=0.
62
63bm_dt(:,:)=0.
64bmelt_dt(:,:)=0.
65
66bm_dt(2:nx-1,2:ny-1)=bm(2:nx-1,2:ny-1)*dt
67bmelt_dt(2:nx-1,2:ny-1)=bmelt(2:nx-1,2:ny-1)*dt
68!~ where (Bm(:,:).lt.0.)
69!~      bm_dt(:,:)=max(Bm(:,:)*dt,-H(:,:))
70!~ elsewhere
71!~      bm_dt(:,:)=bm(:,:)*dt
72!~ endwhere
73
74!~ where (Bmelt(:,:).lt.0.)
75!~      bmelt_dt(:,:)=max(Bmelt(:,:)*dt,-H(:,:))
76!~ elsewhere
77!~      bmelt_dt(:,:)=bmelt(:,:)*dt
78!~ endwhere
79
80
81! on fait la somme sur la grille en excluant les bords :
82
83sum_H = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1)
84
85diff_H = diff_H + (sum_H - sum_H_old) ! on calcul la variation de volume a chaque dt
86
87diff_H_2D(2:nx-1,2:ny-1)=H(2:nx-1,2:ny-1)-H_beau_old(2:nx-1,2:ny-1)
88
89where (ice(2:nx-1,2:ny-1).eq.1)
90        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
91        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
92endwhere
93
94if (isynchro.eq.1) then
95! on raisonne en bilan annuel pour simplifier :
96!~      where (ice(2:nx-1,2:ny-1).eq.1)
97!~              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
98!~              elsewhere
99!~              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
100!~      endwhere
101!cdc pas besoin du test sur ice ici, il a ete fait avant (et le masque ice varie a chaque dt)   
102  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
103   
104! bilan d'eau sur la grille :
105        water_bilan=sum(tot_water(:,:))
106        diff_H = diff_H/dtt
107
108!999 format(f0.2,1x,e15.8,1x,i10,8(1x,e15.8))
109!       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
110        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)
111
112endif
113sum_H_old=sum_H
114
115H_beau_old(:,:)=H(:,:)
116
117end subroutine bilan_eau
118
119end module bilan_eau_mod
Note: See TracBrowser for help on using the repository browser.