SURFEX v8.1
General documentation of Surfex
trip_gw_buffer_tank.F90
Go to the documentation of this file.
1 ! #########
2  SUBROUTINE trip_gw_buffer_tank(PTSTEP,OPRINT,PAREA,OMASK_GW,PGROUND_STO,PGROUND_STO2, &
3  PDRAIN,PTAUG,PGOUT,PGSTO_ALL,PGSTO2_ALL,PGIN_ALL,PGOUT_ALL )
4 ! #############################################################################
5 !
6 !!**** *TRIP_GW_BUFFER_TANK*
7 !!
8 !! PURPOSE
9 !! -------
10 !
11 ! Calculate the storage in the next time step based on the storage
12 ! of current time step. The deep drainage is constant during the time step.
13 !
14 !
15 !!** METHOD
16 !! ------
17 !
18 ! Direct calculation
19 !
20 !! EXTERNAL
21 !! --------
22 !
23 ! None
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !! AUTHOR
33 !! ------
34 !! B. Decharme
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !! Original 01/02/05
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 USE modd_trip_par, ONLY : xundef
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 declarations of arguments
52 !
53 REAL, INTENT(IN) :: PTSTEP
54 ! KTSTEP = timestep value (=FRC) [s]
55 ! = 10800s
56 !
57 LOGICAL, INTENT(IN) :: OPRINT !Printable budget key
58 !
59 REAL, DIMENSION(:,:), INTENT(IN) :: PAREA ! Grid-cell area [mē]
60 LOGICAL, DIMENSION(:,:), INTENT(IN) :: OMASK_GW !Groundwater mask
61 !
62 REAL, DIMENSION(:,:), INTENT(IN) :: PDRAIN, PTAUG
63 ! PDRAIN = Surface runoff from ISBA [kg/s]
64 ! PTAUG = ground water transfer time [s]
65 !
66 REAL, DIMENSION(:,:), INTENT(IN ) :: PGROUND_STO
67 REAL, DIMENSION(:,:), INTENT(INOUT) :: PGROUND_STO2
68 ! PGROUND_STO = ground water storage at t [kg]
69 ! PGROUND_STO2 = ground water storage at t+1 [kg]
70 !
71 REAL, DIMENSION(:,:), INTENT(OUT) :: PGOUT
72 ! PGOUT = Outflow from the ground reservoir
73 !
74 REAL, INTENT(OUT) :: PGSTO_ALL,PGSTO2_ALL,PGIN_ALL,PGOUT_ALL
75 ! Final budget variable
76 !
77 !* 0.2 declarations of local variables
78 !
79 REAL, DIMENSION(SIZE(PGROUND_STO,1),SIZE(PGROUND_STO,2)) :: ZGSTOMAX
80 REAL, DIMENSION(SIZE(PGROUND_STO,1),SIZE(PGROUND_STO,2)) :: ZGOUT
81 REAL, DIMENSION(SIZE(PGROUND_STO,1),SIZE(PGROUND_STO,2)) :: ZDRAIN
82 REAL, DIMENSION(SIZE(PGROUND_STO,1),SIZE(PGROUND_STO,2)) :: ZDRAIN_NEG
83 !
84 INTEGER :: ILON, ILAT, JLON, JLAT
85 !
86 REAL(KIND=JPRB) :: ZHOOK_HANDLE
87 !
88 !-------------------------------------------------------------------------------
89 !-------------------------------------------------------------------------------
90 !
91 IF (lhook) CALL dr_hook('TRIP_GW_BUFFER_TANK',0,zhook_handle)
92 !
93 ilon = SIZE(parea,1)
94 ilat = SIZE(parea,2)
95 !
96 pground_sto2(:,:) = 0.0
97 pgout(:,:) = 0.0
98 !
99 zgstomax(:,:) = 0.0
100 zgout(:,:) = 0.0
101 !
102 zdrain(:,:) = max(0.0,pdrain(:,:))
103 zdrain_neg(:,:) = min(0.0,pdrain(:,:))
104 !
105 !-------------------------------------------------------------------------------
106 ! * Groundwater case
107 !-------------------------------------------------------------------------------
108 !
109 DO jlat=1,ilat
110  DO jlon=1,ilon
111 !
112  IF(omask_gw(jlon,jlat))THEN
113 !
114 ! ground water storage calculation dG/dt = Drain - G/tau
115  pground_sto2(jlon,jlat) = pground_sto(jlon,jlat)*exp(-ptstep/ptaug(jlon,jlat)) &
116  + (1.0-exp(-ptstep/ptaug(jlon,jlat)))*zdrain(jlon,jlat)&
117  * ptaug(jlon,jlat)
118 !
119 ! supress numerical artifacs
120  zgstomax(jlon,jlat)=pground_sto(jlon,jlat)+zdrain(jlon,jlat)*ptstep
121  pground_sto2(jlon,jlat)=min(zgstomax(jlon,jlat),pground_sto2(jlon,jlat))
122 !
123 ! ground water discharge calculation
124  zgout(jlon,jlat)=(pground_sto(jlon,jlat)-pground_sto2(jlon,jlat))/ptstep+zdrain(jlon,jlat)
125 !
126 ! supress numerical artifacs
127  pgout(jlon,jlat)=max(0.0,zgout(jlon,jlat))
128  pground_sto2(jlon,jlat) = pground_sto2(jlon,jlat) + (pgout(jlon,jlat)-zgout(jlon,jlat))
129 !
130 ! account for negative drainage
131  pground_sto2(jlon,jlat) = pground_sto2(jlon,jlat) + zdrain_neg(jlon,jlat)*ptstep
132 !
133  ENDIF
134 !
135  ENDDO
136 ENDDO
137 !
138 !-------------------------------------------------------------------------------
139 ! * No groundwater case
140 !-------------------------------------------------------------------------------
141 !
142 WHERE(.NOT.omask_gw(:,:)) pgout(:,:)=zdrain(:,:)
143 !
144 !-------------------------------------------------------------------------------
145 ! * Budget calculation
146 !-------------------------------------------------------------------------------
147 !
148 IF(oprint)THEN
149 !
150  pgsto_all = 0.0
151  pgsto2_all = 0.0
152  pgin_all = 0.0
153  pgout_all = 0.0
154 !
155  WHERE(omask_gw(:,:)) zdrain(:,:)=zdrain(:,:)+zdrain_neg(:,:)
156 !
157  DO jlat=1,ilat
158  DO jlon=1,ilon
159  IF(omask_gw(jlon,jlat))THEN
160  pgsto_all = pgsto_all + pground_sto(jlon,jlat) / parea(jlon,jlat)
161  pgsto2_all = pgsto2_all + pground_sto2(jlon,jlat) / parea(jlon,jlat)
162  pgin_all = pgin_all + zdrain(jlon,jlat) / parea(jlon,jlat)
163  pgout_all = pgout_all + pgout(jlon,jlat) / parea(jlon,jlat)
164  ENDIF
165  ENDDO
166  ENDDO
167 !
168 ENDIF
169 !
170 IF (lhook) CALL dr_hook('TRIP_GW_BUFFER_TANK',1,zhook_handle)
171 !
172 !-------------------------------------------------------------------------------
173 !-------------------------------------------------------------------------------
174 END SUBROUTINE trip_gw_buffer_tank
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
real, save xundef
subroutine trip_gw_buffer_tank(PTSTEP, OPRINT, PAREA, OMASK_GW, PGROUN