source: tags/ORCHIDEE_2_0/ORCHIDEE/src_sechiba/hydrol.f90 @ 5110

Last change on this file since 5110 was 5091, checked in by josefine.ghattas, 6 years ago

Change unit for output variable snowliq and snowliqtot from m to kg/m2 and take into acount contfrac.

  • Property svn:keywords set to Revision Date HeadURL Date Author Revision
File size: 367.1 KB
Line 
1! ===================================================================================================\n
2! MODULE        : hydrol
3!
4! CONTACT       : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE       : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module computes the soil moisture processes on continental points.
10!!
11!!\n DESCRIPTION : contains hydrol_main, hydrol_initialize, hydrol_finalise, hydrol_init,
12!!                 hydrol_var_init, hydrol_waterbal, hydrol_alma,
13!!                 hydrol_snow, hydrol_vegupd, hydrol_canop, hydrol_flood, hydrol_soil.
14!!                 The assumption in this module is that very high vertical resolution is
15!!                 needed in order to properly resolve the vertical diffusion of water in
16!!                 the soils. Furthermore we have taken into account the sub-grid variability
17!!                 of soil properties and vegetation cover by allowing the co-existence of
18!!                 different soil moisture columns in the same grid box.
19!!                 This routine was originaly developed by Patricia deRosnay.
20!!
21!! RECENT CHANGE(S) : None
22!!
23!! REFERENCE(S) :
24!! - de Rosnay, P., J. Polcher, M. Bruen, and K. Laval, Impact of a physically based soil
25!! water flow and soil-plant interaction representation for modeling large-scale land surface
26!! processes, J. Geophys. Res, 107 (10.1029), 2002. \n
27!! - de Rosnay, P. and Polcher J. (1998) Modeling root water uptake in a complex land surface scheme coupled
28!! to a GCM. Hydrology and Earth System Sciences, 2(2-3):239-256. \n
29!! - de Rosnay, P., M. Bruen, and J. Polcher, Sensitivity of surface fluxes to the number of layers in the soil
30!! model used in GCMs, Geophysical research letters, 27 (20), 3329 - 3332, 2000. \n
31!! - d’Orgeval, T., J. Polcher, and P. De Rosnay, Sensitivity of the West African hydrological
32!! cycle in ORCHIDEE to infiltration processes, Hydrol. Earth Syst. Sci. Discuss, 5, 2251 - 2292, 2008. \n
33!! - Carsel, R., and R. Parrish, Developing joint probability distributions of soil water retention
34!! characteristics, Water Resources Research, 24 (5), 755 - 769, 1988. \n
35!! - Mualem, Y., A new model for predicting the hydraulic conductivity of unsaturated porous
36!! media, Water Resources Research, 12 (3), 513 - 522, 1976. \n
37!! - Van Genuchten, M., A closed-form equation for predicting the hydraulic conductivity of
38!! unsaturated soils, Soil Science Society of America Journal, 44 (5), 892 - 898, 1980. \n
39!! - Campoy, A., Ducharne, A., Cheruy, F., Hourdin, F., Polcher, J., and Dupont, J.-C., Response
40!! of land surface fluxes and precipitation to different soil bottom hydrological conditions in a
41!! general circulation model,  J. Geophys. Res, in press, 2013. \n
42!! - Gouttevin, I., Krinner, G., Ciais, P., Polcher, J., and Legout, C. , 2012. Multi-scale validation
43!! of a new soil freezing scheme for a land-surface model with physically-based hydrology.
44!! The Cryosphere, 6, 407-430, doi: 10.5194/tc-6-407-2012. \n
45!!
46!! SVN          :
47!! $HeadURL$
48!! $Date$
49!! $Revision$
50!! \n
51!_ ===============================================================================================\n
52MODULE hydrol
53
54  USE ioipsl
55  USE xios_orchidee
56  USE constantes
57  USE time, ONLY : one_day, dt_sechiba, julian_diff
58  USE constantes_soil
59  USE pft_parameters
60  USE sechiba_io_p
61  USE grid
62  USE explicitsnow
63
64  IMPLICIT NONE
65
66  PRIVATE
67  PUBLIC :: hydrol_main, hydrol_initialize, hydrol_finalize, hydrol_clear
68
69  !
70  ! variables used inside hydrol module : declaration and initialisation
71  !
72  LOGICAL, SAVE                                   :: doponds=.FALSE.           !! Reinfiltration flag (true/false)
73!$OMP THREADPRIVATE(doponds)
74  REAL(r_std), SAVE                               :: froz_frac_corr            !! Coefficient for water frozen fraction correction
75!$OMP THREADPRIVATE(froz_frac_corr)
76  REAL(r_std), SAVE                               :: max_froz_hydro            !! Coefficient for water frozen fraction correction
77!$OMP THREADPRIVATE(max_froz_hydro)
78  REAL(r_std), SAVE                               :: smtot_corr                !! Coefficient for water frozen fraction correction
79!$OMP THREADPRIVATE(smtot_corr)
80  LOGICAL, SAVE                                   :: do_rsoil=.FALSE.          !! Flag to calculate rsoil for bare soile evap
81                                                                               !! (true/false)
82!$OMP THREADPRIVATE(do_rsoil)
83  LOGICAL, SAVE                                   :: ok_dynroot                !! Flag to activate dynamic root profile to optimize soil 
84                                                                               !! moisture usage, similar to Beer et al.2007
85!$OMP THREADPRIVATE(ok_dynroot)
86  CHARACTER(LEN=80) , SAVE                        :: var_name                  !! To store variables names for I/O
87!$OMP THREADPRIVATE(var_name)
88  !
89  REAL(r_std), PARAMETER                          :: allowed_err =  2.0E-8_r_std
90  REAL(r_std), PARAMETER                          :: EPS1 = EPSILON(un)      !! A small number
91  ! one dimension array allocated, computed, saved and got in hydrol module
92  ! Values per soil type
93  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: nvan                !! Van Genuchten coeficients n (unitless)
94                                                                          ! RK: 1/n=1-m
95!$OMP THREADPRIVATE(nvan)                                                 
96  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: avan                !! Van Genuchten coeficients a
97                                                                         !!  @tex $(mm^{-1})$ @endtex
98!$OMP THREADPRIVATE(avan)                                               
99  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcr                 !! Residual volumetric water content
100                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
101!$OMP THREADPRIVATE(mcr)                                                 
102  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcs                 !! Saturated volumetric water content
103                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
104!$OMP THREADPRIVATE(mcs)                                                 
105  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: ks                  !! Hydraulic conductivity at saturation
106                                                                         !!  @tex $(mm d^{-1})$ @endtex
107!$OMP THREADPRIVATE(ks)                                                 
108  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: pcent               !! Fraction of saturated volumetric soil moisture above
109                                                                         !! which transpir is max (0-1, unitless)
110!$OMP THREADPRIVATE(pcent)
111  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcfc                !! Volumetric water content at field capacity
112                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
113!$OMP THREADPRIVATE(mcfc)                                                 
114  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcw                 !! Volumetric water content at wilting point
115                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
116!$OMP THREADPRIVATE(mcw)                                                 
117  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_awet             !! Vol. wat. cont. above which albedo is cst
118                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
119!$OMP THREADPRIVATE(mc_awet)                                             
120  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_adry             !! Vol. wat. cont. below which albedo is cst
121                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
122!$OMP THREADPRIVATE(mc_adry)                                             
123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watveg_beg   !! Total amount of water on vegetation at start of time
124                                                                         !! step @tex $(kg m^{-2})$ @endtex
125!$OMP THREADPRIVATE(tot_watveg_beg)                                     
126  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watveg_end   !! Total amount of water on vegetation at end of time step
127                                                                         !!  @tex $(kg m^{-2})$ @endtex
128!$OMP THREADPRIVATE(tot_watveg_end)                                     
129  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watsoil_beg  !! Total amount of water in the soil at start of time step
130                                                                         !!  @tex $(kg m^{-2})$ @endtex
131!$OMP THREADPRIVATE(tot_watsoil_beg)                                     
132  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watsoil_end  !! Total amount of water in the soil at end of time step
133                                                                         !!  @tex $(kg m^{-2})$ @endtex
134!$OMP THREADPRIVATE(tot_watsoil_end)                                     
135  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snow_beg         !! Total amount of snow at start of time step
136                                                                         !!  @tex $(kg m^{-2})$ @endtex
137!$OMP THREADPRIVATE(snow_beg)                                           
138  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snow_end         !! Total amount of snow at end of time step
139                                                                         !!  @tex $(kg m^{-2})$ @endtex
140!$OMP THREADPRIVATE(snow_end)                                           
141  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delsoilmoist     !! Change in soil moisture @tex $(kg m^{-2})$ @endtex
142!$OMP THREADPRIVATE(delsoilmoist)                                         
143  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delintercept     !! Change in interception storage
144                                                                         !!  @tex $(kg m^{-2})$ @endtex
145!$OMP THREADPRIVATE(delintercept)                                       
146  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delswe           !! Change in SWE @tex $(kg m^{-2})$ @endtex
147!$OMP THREADPRIVATE(delswe)
148  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:)       :: undermcr         !! Nb of tiles under mcr for a given time step
149!$OMP THREADPRIVATE(undermcr)
150  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mask_veget       !! zero/one when veget fraction is zero/higher (1)
151!$OMP THREADPRIVATE(mask_veget)
152  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mask_soiltile    !! zero/one where soil tile is zero/higher (1)
153!$OMP THREADPRIVATE(mask_soiltile)
154  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: humrelv          !! Water stress index for transpiration
155                                                                         !! for each soiltile x PFT couple (0-1, unitless)
156!$OMP THREADPRIVATE(humrelv)
157  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: vegstressv       !! Water stress index for vegetation growth
158                                                                         !! for each soiltile x PFT couple (0-1, unitless)
159!$OMP THREADPRIVATE(vegstressv)
160  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:,:):: us               !! Water stress index for transpiration
161                                                                         !! (by soil layer and PFT) (0-1, unitless)
162!$OMP THREADPRIVATE(us)
163  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: precisol         !! Throughfall+Totmelt per PFT
164                                                                         !!  @tex $(kg m^{-2})$ @endtex
165!$OMP THREADPRIVATE(precisol)
166  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: throughfall      !! Throughfall per PFT
167                                                                         !!  @tex $(kg m^{-2})$ @endtex
168!$OMP THREADPRIVATE(throughfall)
169  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: precisol_ns      !! Throughfall per soiltile
170                                                                         !!  @tex $(kg m^{-2})$ @endtex
171!$OMP THREADPRIVATE(precisol_ns)
172  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ae_ns            !! Bare soil evaporation per soiltile
173                                                                         !!  @tex $(kg m^{-2})$ @endtex
174!$OMP THREADPRIVATE(ae_ns)
175  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: evap_bare_lim_ns !! Limitation factor (beta) for bare soil evaporation
176                                                                         !! per soiltile (used to deconvoluate vevapnu) 
177                                                                         !!  (0-1, unitless)
178!$OMP THREADPRIVATE(evap_bare_lim_ns)
179  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: free_drain_coef  !! Coefficient for free drainage at bottom
180                                                                         !!  (0-1, unitless)
181!$OMP THREADPRIVATE(free_drain_coef)
182  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: zwt_force        !! Prescribed water table depth (m)
183!$OMP THREADPRIVATE(zwt_force)
184  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: frac_bare_ns     !! Evaporating bare soil fraction per soiltile
185                                                                         !!  (0-1, unitless)
186!$OMP THREADPRIVATE(frac_bare_ns)
187  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: rootsink         !! Transpiration sink by soil layer and soiltile
188                                                                         !! @tex $(kg m^{-2})$ @endtex
189!$OMP THREADPRIVATE(rootsink)
190  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: subsnowveg       !! Sublimation of snow on vegetation
191                                                                         !!  @tex $(kg m^{-2})$ @endtex
192!$OMP THREADPRIVATE(subsnowveg)
193  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: subsnownobio     !! Sublimation of snow on other surface types 
194                                                                         !! (ice, lakes,...) @tex $(kg m^{-2})$ @endtex
195!$OMP THREADPRIVATE(subsnownobio)
196  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: icemelt          !! Ice melt @tex $(kg m^{-2})$ @endtex
197!$OMP THREADPRIVATE(icemelt)
198  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: subsinksoil      !! Excess of sublimation as a sink for the soil
199                                                                         !! @tex $(kg m^{-2})$ @endtex
200!$OMP THREADPRIVATE(subsinksoil)
201  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: vegtot           !! Total Total fraction of grid-cell covered by PFTs
202                                                                         !! (bare soil + vegetation) (1; 1)
203!$OMP THREADPRIVATE(vegtot)
204  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: resdist          !! Soiltile values from previous time-step (1; 1)
205!$OMP THREADPRIVATE(resdist)
206  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: vegtot_old       !! Total Total fraction of grid-cell covered by PFTs
207                                                                         !! from previous time-step (1; 1)
208!$OMP THREADPRIVATE(vegtot_old)
209  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: mx_eau_var       !! Maximum water content of the soil @tex $(kg m^{-2})$ @endtex
210!$OMP THREADPRIVATE(mx_eau_var)
211
212  ! arrays used by cwrr scheme
213  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: nroot            !! Normalized root length fraction in each soil layer
214                                                                         !! (0-1, unitless)
215                                                                         !! DIM = kjpindex * nvm * nslm
216!$OMP THREADPRIVATE(nroot)
217  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: kfact_root       !! Factor to increase Ks towards the surface
218                                                                         !! (unitless)
219                                                                         !! DIM = kjpindex * nslm * nstm
220!$OMP THREADPRIVATE(kfact_root)
221  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: kfact            !! Factor to reduce Ks with depth (unitless)
222                                                                         !! DIM = nslm * nscm
223!$OMP THREADPRIVATE(kfact)
224  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: zz               !! Depth of nodes [znh in vertical_soil] transformed into (mm)
225!$OMP THREADPRIVATE(zz)
226  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: dz               !! Internode thickness [dnh in vertical_soil] transformed into (mm)
227!$OMP THREADPRIVATE(dz)
228  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: dh               !! Layer thickness [dlh in vertical_soil] transformed into (mm)
229!$OMP THREADPRIVATE(dh)
230  INTEGER(i_std), SAVE                               :: itopmax          !! Number of layers where the node is above 0.1m depth
231!$OMP THREADPRIVATE(itopmax)
232  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: mc_lin   !! 50 Vol. Wat. Contents to linearize K and D, for each texture
233                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
234                                                                 !! DIM = imin:imax * nscm
235!$OMP THREADPRIVATE(mc_lin)
236  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: k_lin    !! 50 values of unsaturated K, for each soil layer and texture
237                                                                 !!  @tex $(mm d^{-1})$ @endtex
238                                                                 !! DIM = imin:imax * nslm * nscm
239!$OMP THREADPRIVATE(k_lin)
240  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: d_lin    !! 50 values of diffusivity D, for each soil layer and texture
241                                                                 !!  @tex $(mm^2 d^{-1})$ @endtex
242                                                                 !! DIM = imin:imax * nslm * nscm
243!$OMP THREADPRIVATE(d_lin)
244  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: a_lin    !! 50 values of the slope in K=a*mc+b, for each soil layer and texture
245                                                                 !!  @tex $(mm d^{-1})$ @endtex
246                                                                 !! DIM = imin:imax * nslm * nscm
247!$OMP THREADPRIVATE(a_lin)
248  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: b_lin    !! 50 values of y-intercept in K=a*mc+b, for each soil layer and texture
249                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
250                                                                 !! DIM = imin:imax * nslm * nscm
251!$OMP THREADPRIVATE(b_lin)
252
253  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: humtot   !! Total Soil Moisture @tex $(kg m^{-2})$ @endtex
254!$OMP THREADPRIVATE(humtot)
255  LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:)          :: resolv   !! Mask of land points where to solve the diffusion equation
256                                                                 !! (true/false)
257!$OMP THREADPRIVATE(resolv)
258
259!! for output
260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: kk_moy   !! Mean hydraulic conductivity over soiltiles (mm/d)
261!$OMP THREADPRIVATE(kk_moy)
262  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: kk       !! Hydraulic conductivity for each soiltiles (mm/d)
263!$OMP THREADPRIVATE(kk)
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: avan_mod_tab  !! VG parameter a modified from  exponantial profile
265                                                                      !! @tex $(mm^{-1})$ @endtex !! DIMENSION (nslm,nscm)
266!$OMP THREADPRIVATE(avan_mod_tab) 
267  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: nvan_mod_tab  !! VG parameter n  modified from  exponantial profile
268                                                                      !! (unitless) !! DIMENSION (nslm,nscm) 
269!$OMP THREADPRIVATE(nvan_mod_tab)
270 
271!! linarization coefficients of hydraulic conductivity K (hydrol_soil_coef)
272  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: k        !! Hydraulic conductivity K for each soil layer
273                                                                 !!  @tex $(mm d^{-1})$ @endtex
274                                                                 !! DIM = (:,nslm)
275!$OMP THREADPRIVATE(k)
276  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: a        !! Slope in K=a*mc+b(:,nslm)
277                                                                 !!  @tex $(mm d^{-1})$ @endtex
278                                                                 !! DIM = (:,nslm)
279!$OMP THREADPRIVATE(a)
280  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: b        !! y-intercept in K=a*mc+b
281                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
282                                                                 !! DIM = (:,nslm)
283!$OMP THREADPRIVATE(b)
284!! linarization coefficients of hydraulic diffusivity D (hydrol_soil_coef)
285  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: d        !! Diffusivity D for each soil layer
286                                                                 !!  @tex $(mm^2 d^{-1})$ @endtex
287                                                                 !! DIM = (:,nslm)
288!$OMP THREADPRIVATE(d)
289!! matrix coefficients (hydrol_soil_tridiag and hydrol_soil_setup), see De Rosnay (1999), p155-157
290  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: e        !! Left-hand tridiagonal matrix coefficients
291!$OMP THREADPRIVATE(e)
292  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: f        !! Left-hand tridiagonal matrix coefficients
293!$OMP THREADPRIVATE(f)
294  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: g1       !! Left-hand tridiagonal matrix coefficients
295!$OMP THREADPRIVATE(g1)
296
297  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ep       !! Right-hand matrix coefficients
298!$OMP THREADPRIVATE(ep)
299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: fp       !! Right-hand atrix coefficients
300!$OMP THREADPRIVATE(fp)
301  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: gp       !! Right-hand atrix coefficients
302!$OMP THREADPRIVATE(gp)
303  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: rhs      !! Right-hand system
304!$OMP THREADPRIVATE(rhs)
305  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: srhs     !! Temporarily stored rhs
306!$OMP THREADPRIVATE(srhs)
307  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: tmat             !! Left-hand tridiagonal matrix
308!$OMP THREADPRIVATE(tmat)
309  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: stmat            !! Temporarily stored tmat
310  !$OMP THREADPRIVATE(stmat)
311  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: water2infilt     !! Water to be infiltrated
312                                                                         !! @tex $(kg m^{-2})$ @endtex
313!$OMP THREADPRIVATE(water2infilt)
314  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc              !! Total moisture content per soiltile
315                                                                         !!  @tex $(kg m^{-2})$ @endtex
316!$OMP THREADPRIVATE(tmc)
317  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcr             !! Total moisture content at residual per soiltile
318                                                                         !!  @tex $(kg m^{-2})$ @endtex
319!$OMP THREADPRIVATE(tmcr)
320  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcs             !! Total moisture content at saturation per soiltile
321                                                                         !!  @tex $(kg m^{-2})$ @endtex
322!$OMP THREADPRIVATE(tmcs)
323  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcfc            !! Total moisture content at field capacity per soiltile
324                                                                         !!  @tex $(kg m^{-2})$ @endtex
325!$OMP THREADPRIVATE(tmcfc)
326  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcw             !! Total moisture content at wilting point per soiltile
327                                                                         !!  @tex $(kg m^{-2})$ @endtex
328!$OMP THREADPRIVATE(tmcw)
329  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter       !! Total moisture in the litter per soiltile
330                                                                         !!  @tex $(kg m^{-2})$ @endtex
331!$OMP THREADPRIVATE(tmc_litter)
332  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_mea     !! Total moisture in the litter over the grid
333                                                                         !!  @tex $(kg m^{-2})$ @endtex
334!$OMP THREADPRIVATE(tmc_litt_mea)
335  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_wilt  !! Total moisture of litter at wilt point per soiltile
336                                                                         !!  @tex $(kg m^{-2})$ @endtex
337!$OMP THREADPRIVATE(tmc_litter_wilt)
338  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_field !! Total moisture of litter at field cap. per soiltile
339                                                                         !!  @tex $(kg m^{-2})$ @endtex
340!$OMP THREADPRIVATE(tmc_litter_field)
341!!! A CHANGER DANS TOUT HYDROL: tmc_litter_res et sat ne devraient pas dependre de ji - tdo
342  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_res   !! Total moisture of litter at residual moisture per soiltile
343                                                                         !!  @tex $(kg m^{-2})$ @endtex
344!$OMP THREADPRIVATE(tmc_litter_res)
345  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_sat   !! Total moisture of litter at saturation per soiltile
346                                                                         !!  @tex $(kg m^{-2})$ @endtex
347!$OMP THREADPRIVATE(tmc_litter_sat)
348  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_awet  !! Total moisture of litter at mc_awet per soiltile
349                                                                         !!  @tex $(kg m^{-2})$ @endtex
350!$OMP THREADPRIVATE(tmc_litter_awet)
351  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_adry  !! Total moisture of litter at mc_adry per soiltile
352                                                                         !!  @tex $(kg m^{-2})$ @endtex
353!$OMP THREADPRIVATE(tmc_litter_adry)
354  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_wet_mea !! Total moisture in the litter over the grid below which
355                                                                         !! albedo is fixed constant
356                                                                         !!  @tex $(kg m^{-2})$ @endtex
357!$OMP THREADPRIVATE(tmc_litt_wet_mea)
358  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_dry_mea !! Total moisture in the litter over the grid above which
359                                                                         !! albedo is constant
360                                                                         !!  @tex $(kg m^{-2})$ @endtex
361!$OMP THREADPRIVATE(tmc_litt_dry_mea)
362  LOGICAL, SAVE                                      :: tmc_init_updated = .FALSE. !! Flag allowing to determine if tmc is initialized.
363!$OMP THREADPRIVATE(tmc_init_updated)
364
365  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: v1               !! Temporary variable (:)
366!$OMP THREADPRIVATE(v1)
367
368  !! par type de sol :
369  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ru_ns            !! Surface runoff per soiltile
370                                                                         !!  @tex $(kg m^{-2})$ @endtex
371!$OMP THREADPRIVATE(ru_ns)
372  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: dr_ns            !! Drainage per soiltile
373                                                                         !!  @tex $(kg m^{-2})$ @endtex
374!$OMP THREADPRIVATE(dr_ns)
375  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tr_ns            !! Transpiration per soiltile
376!$OMP THREADPRIVATE(tr_ns)
377  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: vegetmax_soil    !! (:,nvm,nstm) percentage of each veg. type on each soil
378                                                                         !! of each grid point
379!$OMP THREADPRIVATE(vegetmax_soil)
380  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: mc               !! Total volumetric water content at the calculation nodes
381                                                                         !! (eg : liquid + frozen)
382                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
383!$OMP THREADPRIVATE(mc)
384
385   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mc_read_prev       !! Soil moisture from file at previous timestep in the file
386!$OMP THREADPRIVATE(mc_read_prev)
387   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mc_read_next       !! Soil moisture from file at next time step in the file
388!$OMP THREADPRIVATE(mc_read_next)
389   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mask_mc_interp     !! Mask of valid data in soil moisture nudging file
390!$OMP THREADPRIVATE(mask_mc_interp)
391   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowdz_read_prev   !! snowdz read from file at previous timestep in the file
392!$OMP THREADPRIVATE(snowdz_read_prev)
393   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowdz_read_next   !! snowdz read from file at next time step in the file
394!$OMP THREADPRIVATE(snowdz_read_next)
395   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowrho_read_prev  !! snowrho read from file at previous timestep in the file
396!$OMP THREADPRIVATE(snowrho_read_prev)
397   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowrho_read_next  !! snowrho read from file at next time step in the file
398!$OMP THREADPRIVATE(snowrho_read_next)
399   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowtemp_read_prev !! snowtemp read from file at previous timestep in the file
400!$OMP THREADPRIVATE(snowtemp_read_prev)
401   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowtemp_read_next !! snowtemp read from file at next time step in the file
402!$OMP THREADPRIVATE(snowtemp_read_next)
403   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: mask_snow_interp   !! Mask of valid data in snow nudging file
404!$OMP THREADPRIVATE(mask_snow_interp)
405
406   REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: mcl              !! Liquid water content
407                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
408!$OMP THREADPRIVATE(mcl)
409  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soilmoist        !! (:,nslm) Mean of each soil layer's moisture
410                                                                         !! across soiltiles
411                                                                         !!  @tex $(kg m^{-2})$ @endtex
412!$OMP THREADPRIVATE(soilmoist)
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soilmoist_liquid !! (:,nslm) Mean of each soil layer's liquid moisture
414                                                                         !! across soiltiles
415                                                                         !!  @tex $(kg m^{-2})$ @endtex
416!$OMP THREADPRIVATE(soilmoist_liquid)
417  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: soil_wet_ns      !! Soil wetness above mcw (0-1, unitless)
418!$OMP THREADPRIVATE(soil_wet_ns)
419  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soil_wet_litter  !! Soil wetness aove mvw in the litter (0-1, unitless)
420!$OMP THREADPRIVATE(soil_wet_litter)
421  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: qflux            !! Diffusive water fluxes between soil layers
422!$OMP THREADPRIVATE(qflux)
423  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: profil_froz_hydro     !! Frozen fraction for each hydrological soil layer
424!$OMP THREADPRIVATE(profil_froz_hydro)
425  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: profil_froz_hydro_ns  !! As  profil_froz_hydro per soiltile
426!$OMP THREADPRIVATE(profil_froz_hydro_ns)
427  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: temp_hydro            !! Temp profile on hydrological levels
428!$OMP THREADPRIVATE(temp_hydro)
429
430
431CONTAINS
432
433!! ================================================================================================================================
434!! SUBROUTINE   : hydrol_initialize
435!!
436!>\BRIEF         Allocate module variables, read from restart file or initialize with default values
437!!
438!! DESCRIPTION :
439!!
440!! MAIN OUTPUT VARIABLE(S) :
441!!
442!! REFERENCE(S) :
443!!
444!! FLOWCHART    : None
445!! \n
446!_ ================================================================================================================================
447
448  SUBROUTINE hydrol_initialize ( kjit,           kjpindex,  index,         rest_id,          &
449                                 njsc,           soiltile,  veget,         veget_max,        &
450                                 humrel,         vegstress, drysoil_frac,                    &
451                                 shumdiag_perma,    qsintveg,                        &
452                                 evap_bare_lim,  snow,      snow_age,      snow_nobio,       &
453                                 snow_nobio_age, snowrho,   snowtemp,      snowgrain,        &
454                                 snowdz,         snowheat,  &
455                                 mc_layh,        mcl_layh,  soilmoist_out)
456
457    !! 0. Variable and parameter declaration
458    !! 0.1 Input variables
459    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number
460    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size
461    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map
462    INTEGER(i_std),INTENT (in)                         :: rest_id          !! Restart file identifier
463    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
464    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
465    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type           
466    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty)
467
468    !! 0.2 Output variables
469    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: humrel         !! Relative humidity
470    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: vegstress      !! Veg. moisture stress (only for vegetation growth)
471    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: drysoil_frac   !! function of litter wetness
472    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: shumdiag_perma !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
473    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: qsintveg       !! Water on vegetation due to interception
474    REAL(r_std),DIMENSION (kjpindex), INTENT(out)        :: evap_bare_lim  !! Limitation factor for bare soil evaporation
475    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: snow           !! Snow mass [Kg/m^2]
476    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: snow_age       !! Snow age
477    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out):: snow_nobio     !! Water balance on ice, lakes, .. [Kg/m^2]
478    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out):: snow_nobio_age !! Snow age on ice, lakes, ...
479    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowrho        !! Snow density
480    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowtemp       !! Snow temperature
481    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowgrain      !! Snow grainsize
482    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowdz         !! Snow layer thickness
483    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowheat       !! Snow heat content
484    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: mc_layh        !! Volumetric moisture content for each layer in hydrol (liquid+ice) m3/m3
485    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: mcl_layh       !! Volumetric moisture content for each layer in hydrol (liquid) m3/m3
486    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: soilmoist_out  !! Total soil moisture content for each layer in hydrol (liquid+ice), mm
487    REAL(r_std),DIMENSION (kjpindex)                     :: soilwetdummy   !! Temporary variable never used
488
489
490    !! 0.4 Local variables
491    INTEGER(i_std)                                       :: jsl
492!_ ================================================================================================================================
493
494    CALL hydrol_init (kjit, kjpindex, index, rest_id, veget_max, soiltile, &
495         humrel, vegstress, snow,       snow_age,   snow_nobio, snow_nobio_age, qsintveg, &
496         snowdz, snowgrain, snowrho,    snowtemp,   snowheat, &
497         drysoil_frac, evap_bare_lim)
498   
499    CALL hydrol_var_init (kjpindex, veget, veget_max, &
500         soiltile, njsc, mx_eau_var, shumdiag_perma, &
501         drysoil_frac, qsintveg, mc_layh, mcl_layh) 
502
503    !! Initialize hydrol_alma routine if the variables were not found in the restart file. This is done in the end of
504    !! hydrol_initialize so that all variables(humtot,..) that will be used are initialized.
505    IF (ALL(tot_watveg_beg(:)==val_exp) .OR.  ALL(tot_watsoil_beg(:)==val_exp) .OR. ALL(snow_beg(:)==val_exp)) THEN
506       ! The output variable soilwetdummy is not calculated at first call to hydrol_alma.
507       CALL hydrol_alma(kjpindex, index, .TRUE., qsintveg, snow, snow_nobio, soilwetdummy)
508    END IF
509   
510    !! Calculate itopmax indicating the number of layers where the node is above 0.1m depth
511    itopmax=1
512    DO jsl = 1, nslm
513       ! znh : depth of nodes
514       IF (znh(jsl) <= 0.1) THEN
515          itopmax=jsl
516       END IF
517    END DO
518    IF (printlev>=3) WRITE(numout,*) "Number of layers where the node is above 0.1m depth: itopmax=",itopmax
519
520    ! Copy soilmoist into a local variable to be sent to thermosoil
521    soilmoist_out(:,:) = soilmoist(:,:)
522
523  END SUBROUTINE hydrol_initialize
524
525
526!! ================================================================================================================================
527!! SUBROUTINE   : hydrol_main
528!!
529!>\BRIEF         
530!!
531!! DESCRIPTION :
532!! - called every time step
533!! - initialization and finalization part are not done in here
534!!
535!! - 1 computes snow  ==> hydrol_snow
536!! - 2 computes vegetations reservoirs  ==> hydrol_vegupd
537!! - 3 computes canopy  ==> hydrol_canop
538!! - 4 computes surface reservoir  ==> hydrol_flood
539!! - 5 computes soil hydrology ==> hydrol_soil
540!!
541!! IMPORTANT NOTICE : The water fluxes are used in their integrated form, over the time step
542!! dt_sechiba, with a unit of kg m^{-2}.
543!!
544!! RECENT CHANGE(S) : None
545!!
546!! MAIN OUTPUT VARIABLE(S) :
547!!
548!! REFERENCE(S) :
549!!
550!! FLOWCHART    : None
551!! \n
552!_ ================================================================================================================================
553
554  SUBROUTINE hydrol_main (kjit, kjpindex, &
555       & index, indexveg, indexsoil, indexlayer, indexnslm, &
556       & temp_sol_new, floodout, runoff, drainage, frac_nobio, totfrac_nobio, vevapwet, veget, veget_max, njsc, &
557       & qsintmax, qsintveg, vevapnu, vevapsno, vevapflo, snow, snow_age, snow_nobio, snow_nobio_age,  &
558       & tot_melt, transpir, precip_rain, precip_snow, returnflow, reinfiltration, irrigation, &
559       & humrel, vegstress, drysoil_frac, evapot, evapot_penm, evap_bare_lim, flood_frac, flood_res, &
560       & shumdiag,shumdiag_perma, k_litt, litterhumdiag, soilcap, soiltile, fraclut, reinf_slope, rest_id, hist_id, hist2_id,&
561       & contfrac, stempdiag, &
562       & temp_air, pb, u, v, tq_cdrag, swnet, pgflux, &
563       & snowrho,snowtemp,snowgrain,snowdz,snowheat,snowliq, &
564       & grndflux,gtemp,tot_bare_soil, &
565       & lambda_snow,cgrnd_snow,dgrnd_snow,frac_snow_veg,temp_sol_add, &
566       & mc_layh, mcl_layh, soilmoist_out )
567
568    !! 0. Variable and parameter declaration
569
570    !! 0.1 Input variables
571 
572    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number
573    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size
574    INTEGER(i_std),INTENT (in)                         :: rest_id,hist_id  !! _Restart_ file and _history_ file identifier
575    INTEGER(i_std),INTENT (in)                         :: hist2_id         !! _history_ file 2 identifier
576    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map
577    INTEGER(i_std),DIMENSION (kjpindex*nvm), INTENT (in):: indexveg        !! Indeces of the points on the 3D map for veg
578    INTEGER(i_std),DIMENSION (kjpindex*nstm), INTENT (in):: indexsoil      !! Indeces of the points on the 3D map for soil
579    INTEGER(i_std),DIMENSION (kjpindex*nslm), INTENT (in):: indexlayer     !! Indeces of the points on the 3D map for soil layers
580    INTEGER(i_std),DIMENSION (kjpindex*nslm), INTENT (in):: indexnslm      !! Indeces of the points on the 3D map for of diagnostic soil layers
581
582    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_rain      !! Rain precipitation
583    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_snow      !! Snow precipitation
584    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: returnflow       !! Routed water which comes back into the soil (from the
585                                                                           !! bottom)
586    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinfiltration   !! Routed water which comes back into the soil (at the
587                                                                           !! top)
588    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: irrigation       !! Water from irrigation returning to soil moisture 
589    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: temp_sol_new     !! New soil temperature
590
591    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
592    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: frac_nobio     !! Fraction of ice, lakes, ...
593    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: totfrac_nobio    !! Total fraction of ice+lakes+...
594    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: soilcap          !! Soil capacity
595    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
596    REAL(r_std),DIMENSION (kjpindex,nlut), INTENT (in) :: fraclut          !! Fraction of each landuse tile (0-1, unitless)
597    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: vevapwet         !! Interception loss
598    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type           
599    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty)
600    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintmax         !! Maximum water on vegetation for interception
601    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: transpir         !! Transpiration
602    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinf_slope      !! Slope coef
603    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot           !! Soil Potential Evaporation
604    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot_penm      !! Soil Potential Evaporation Correction
605    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: flood_frac       !! flood fraction
606    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: contfrac         !! Fraction of continent in the grid
607    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in) :: stempdiag        !! Diagnostic temp profile from thermosoil
608    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: temp_air         !! Air temperature
609    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: u,v              !! Horizontal wind speed
610    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: tq_cdrag         !! Surface drag coefficient (-)
611    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: pb               !! Surface pressure
612    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: swnet            !! Net shortwave radiation
613    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: pgflux           !! Net energy into snowpack
614    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: gtemp            !! First soil layer temperature
615    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: tot_bare_soil    !! Total evaporating bare soil fraction
616    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: lambda_snow      !! Coefficient of the linear extrapolation of surface temperature
617    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in):: cgrnd_snow       !! Integration coefficient for snow numerical scheme
618    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in):: dgrnd_snow       !! Integration coefficient for snow numerical scheme
619    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: frac_snow_veg    !! Snow cover fraction on vegetation   
620
621    !! 0.2 Output variables
622
623    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: vegstress        !! Veg. moisture stress (only for vegetation growth)
624    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: drysoil_frac     !! function of litter wetness
625    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out):: shumdiag         !! Relative soil moisture in each soil layer
626                                                                           !! with respect to (mcfc-mcw)
627                                                                           !! (unitless; can be out of 0-1)
628    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out):: shumdiag_perma   !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
629    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: k_litt           !! litter approximate conductivity
630    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: litterhumdiag    !! litter humidity
631    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: tot_melt         !! Total melt   
632    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: floodout         !! Flux out of floodplains
633   
634    !! 0.3 Modified variables
635
636    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout):: qsintveg         !! Water on vegetation due to interception
637    REAL(r_std),DIMENSION (kjpindex), INTENT(inout)    :: evap_bare_lim    !! Limitation factor (beta) for bare soil evaporation   
638    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout):: humrel           !! Relative humidity
639    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapnu          !! Bare soil evaporation
640    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapsno         !! Snow evaporation
641    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapflo         !! Floodplain evaporation
642    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: flood_res        !! flood reservoir estimate
643    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: snow             !! Snow mass [kg/m^2]
644    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: snow_age         !! Snow age
645    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (inout) :: snow_nobio  !! Water balance on ice, lakes, .. [Kg/m^2]
646    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (inout) :: snow_nobio_age !! Snow age on ice, lakes, ...
647    !! We consider that any water on the ice is snow and we only peforme a water balance to have consistency.
648    !! The water balance is limite to + or - 10^6 so that accumulation is not endless
649
650    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: runoff       !! Complete surface runoff
651    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: drainage     !! Drainage
652    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowrho      !! Snow density
653    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowtemp     !! Snow temperature
654    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowgrain    !! Snow grainsize
655    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowdz       !! Snow layer thickness
656    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowheat     !! Snow heat content
657    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out)   :: snowliq      !! Snow liquid content (m)
658    REAL(r_std), DIMENSION (kjpindex), INTENT(out)         :: grndflux     !! Net flux into soil W/m2
659    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: mc_layh      !! Volumetric moisture content for each layer in hydrol(liquid + ice) [m3/m3)]
660    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: mcl_layh     !! Volumetric moisture content for each layer in hydrol(liquid) [m3/m3]
661    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: soilmoist_out!! Total soil moisture content for each layer in hydrol(liquid + ice) [mm]
662    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)       :: temp_sol_add !! additional surface temperature due to the melt of first layer
663                                                                           !! at the present time-step @tex ($K$) @endtex
664
665
666    !! 0.4 Local variables
667
668    INTEGER(i_std)                                     :: jst              !! Index of soil tiles (unitless, 1-3)
669    INTEGER(i_std)                                     :: jsl              !! Index of soil layers (unitless)
670    INTEGER(i_std)                                     :: ji, jv
671    REAL(r_std),DIMENSION (kjpindex)                   :: soilwet          !! A temporary diagnostic of soil wetness
672    REAL(r_std),DIMENSION (kjpindex)                   :: snowdepth        !! Depth of snow layer, only for diagnostics with ok_explicitsnow=n
673    REAL(r_std),DIMENSION (kjpindex)                   :: snowdepth_diag   !! Depth of snow layer containing default values, only for diagnostics
674    REAL(r_std),DIMENSION (kjpindex, nsnow)            :: snowdz_diag      !! Depth of snow layer on all layers containing default values, only for diagnostics
675    REAL(r_std),DIMENSION (kjpindex)                   :: njsc_tmp         !! Temporary REAL value for njsc to write it
676    REAL(r_std), DIMENSION (kjpindex)                  :: snowmelt         !! Snow melt [mm/dt_sechiba]
677    REAL(r_std), DIMENSION (kjpindex,nstm)             :: tmc_top          !! Moisture content in the itopmax upper layers, per tile
678    REAL(r_std), DIMENSION (kjpindex)                  :: humtot_top       !! Moisture content in the itopmax upper layers, for diagnistics
679    REAL(r_std), DIMENSION(kjpindex)                   :: histvar          !! Temporary variable when computations are needed
680    REAL(r_std), DIMENSION (kjpindex,nvm)              :: frac_bare        !! Fraction(of veget_max) of bare soil in each vegetation type
681    INTEGER(i_std), DIMENSION(kjpindex*imax)           :: mc_lin_axis_index
682    REAL(r_std), DIMENSION(kjpindex)                   :: twbr             !! Grid-cell mean of TWBR Total Water Budget Residu[kg/m2/dt]
683    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_nroot       !! To ouput the grid-cell mean of nroot
684    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_dlh         !! To ouput the soil layer thickness on all grid points [m]
685    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcs         !! To ouput the mean of mcs
686    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcfc        !! To ouput the mean of mcfc
687    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcw         !! To ouput the mean of mcw
688    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcr         !! To ouput the mean of mcr
689    REAL(r_std),DIMENSION (kjpindex)                   :: land_tmcs        !! To ouput the grid-cell mean of tmcs
690    REAL(r_std),DIMENSION (kjpindex)                   :: land_tmcfc       !! To ouput the grid-cell mean of tmcfc
691    REAL(r_std),DIMENSION (kjpindex)                   :: drain_upd        !! Change in drainage due to decrease in vegtot
692                                                                           !! on mc [kg/m2/dt]
693    REAL(r_std),DIMENSION (kjpindex)                   :: runoff_upd       !! Change in runoff due to decrease in vegtot
694                                                                           !! on water2infilt[kg/m2/dt]
695    REAL(r_std),DIMENSION (kjpindex)                   :: mrsow            !! Soil wetness above wilting point for CMIP6 (humtot-WP)/(SAT-WP)
696    REAL(r_std), DIMENSION (kjpindex,nlut)             :: humtot_lut       !! Moisture content on landuse tiles, for diagnostics
697    REAL(r_std), DIMENSION (kjpindex,nlut)             :: humtot_top_lut   !! Moisture content in upper layers on landuse tiles, for diagnostics
698    REAL(r_std), DIMENSION (kjpindex,nlut)             :: mrro_lut         !! Total runoff from landuse tiles, for diagnostics
699
700!_ ================================================================================================================================
701    !! 1. Update vegtot_old and recalculate vegtot
702    vegtot_old(:) = vegtot(:)
703
704    DO ji = 1, kjpindex
705       vegtot(ji) = SUM(veget_max(ji,:))
706    ENDDO
707
708
709    !! 2. Applay nudging for soil moisture and/or snow variables
710    IF (ok_nudge_mc .OR. ok_nudge_snow) THEN
711       CALL hydrol_nudge(kjit, kjpindex, mc, snowdz, snowrho, snowtemp, soiltile)
712    END IF
713
714
715    !! 3. Shared time step
716    IF (printlev>=3) WRITE (numout,*) 'hydrol pas de temps = ',dt_sechiba
717
718    !
719    !! 3.1 Calculate snow processes with explicit method or bucket snow model
720    IF (ok_explicitsnow) THEN
721       ! Explicit snow model
722       IF (printlev>=3) WRITE (numout,*) ' ok_explicitsnow : use multi-snow layer '
723       CALL explicitsnow_main(kjpindex,    precip_rain,  precip_snow,   temp_air,    pb,       &
724                              u,           v,            temp_sol_new,  soilcap,     pgflux,   &
725                              frac_nobio,  totfrac_nobio,gtemp,                                &
726                              lambda_snow, cgrnd_snow,   dgrnd_snow,    contfrac,              & 
727                              vevapsno,    snow_age,     snow_nobio_age,snow_nobio,  snowrho,  &
728                              snowgrain,   snowdz,       snowtemp,      snowheat,    snow,     &
729                              temp_sol_add,                                                    &
730                              snowliq,     subsnownobio, grndflux,      snowmelt,    tot_melt, &
731                              subsinksoil)           
732    ELSE
733       ! Bucket snow model
734       CALL hydrol_snow(kjpindex, precip_rain, precip_snow, temp_sol_new, soilcap, &
735            frac_nobio, totfrac_nobio, vevapsno, snow, snow_age, snow_nobio, snow_nobio_age, &
736            tot_melt, snowdepth,snowmelt)
737    END IF
738       
739    !
740    !! 3.2 computes vegetations reservoirs  ==>hydrol_vegupd
741! Modif temp vuichard
742    CALL hydrol_vegupd(kjpindex, veget, veget_max, soiltile, qsintveg, frac_bare, drain_upd, runoff_upd)
743
744    !! Calculate kfact_root
745    !! An exponential factor is used to increase ks near the surface depending on the amount of roots in the soil
746    !! through a geometric average over the vegets
747    !! This comes from the PhD thesis of d'Orgeval, 2006, p82; d'Orgeval et al. 2008, Eqs. 3-4
748    !! (Calibrated against Hapex-Sahel measurements)
749    !! Since rev 2916: veget_max/2 is used instead of veget
750    kfact_root(:,:,:) = un
751    DO jsl = 1, nslm
752       DO jv = 2, nvm
753          jst = pref_soil_veg(jv)
754          DO ji = 1, kjpindex
755             IF(soiltile(ji,jst) .GT. min_sechiba) THEN
756                kfact_root(ji,jsl,jst) = kfact_root(ji,jsl,jst) * &
757                     & MAX((MAXVAL(ks_usda)/ks(njsc(ji)))**(- vegetmax_soil(ji,jv,jst)/2 * (humcste(jv)*zz(jsl)/mille - un)/deux), &
758                     un) 
759             ENDIF
760          ENDDO
761       ENDDO
762    ENDDO
763
764    !
765    !! 3.3 computes canopy  ==>hydrol_canop
766    CALL hydrol_canop(kjpindex, precip_rain, vevapwet, veget_max, veget, qsintmax, qsintveg,precisol,tot_melt)
767
768    !
769    !! 3.4 computes surface reservoir  ==>hydrol_flood
770    CALL hydrol_flood(kjpindex,  vevapflo, flood_frac, flood_res, floodout)
771
772    !
773    !! 3.5 computes soil hydrology ==>hydrol_soil
774
775    CALL hydrol_soil(kjpindex, veget_max, soiltile, njsc, reinf_slope,  &
776         transpir, vevapnu, evapot, evapot_penm, runoff, drainage, & 
777         returnflow, reinfiltration, irrigation, &
778         tot_melt,evap_bare_lim, shumdiag, shumdiag_perma, &
779         k_litt, litterhumdiag, humrel, vegstress, drysoil_frac,&
780         stempdiag,snow,snowdz, tot_bare_soil,  u, v, tq_cdrag, &
781         mc_layh, mcl_layh)
782
783    ! The update fluxes come from hydrol_vegupd
784    drainage(:) =  drainage(:) +  drain_upd(:)
785    runoff(:) =  runoff(:) +  runoff_upd(:)
786
787
788    !! 4 write out file  ==> hydrol_alma/histwrite(*)
789    !
790    ! If we use the ALMA standards
791    CALL hydrol_alma(kjpindex, index, .FALSE., qsintveg, snow, snow_nobio, soilwet)
792   
793
794    ! Calculate the moisture in the upper itopmax layers corresponding to 0.1m (humtot_top):
795    ! For ORCHIDEE with nslm=11 and zmaxh=2, itopmax=6.
796    ! We compute tmc_top as tmc but only for the first itopmax layers. Then we compute a humtot with this variable.
797    DO jst=1,nstm
798       DO ji=1,kjpindex
799          tmc_top(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
800          DO jsl = 2, itopmax
801             tmc_top(ji,jst) = tmc_top(ji,jst) + dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
802                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
803          ENDDO
804       ENDDO
805    ENDDO
806 
807    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
808    humtot_top(:) = zero
809    DO jst=1,nstm
810       DO ji=1,kjpindex
811          humtot_top(ji) = humtot_top(ji) + soiltile(ji,jst) * tmc_top(ji,jst) * vegtot(ji)
812       ENDDO
813    ENDDO
814
815    ! Calculate the Total Water Budget Residu (in kg/m2 over dt_sechiba)
816    ! All the delstocks and fluxes below are averaged over the mesh
817    ! snow_nobio included in delswe
818    ! Does not include the routing reservoirs, although the flux to/from routing are integrated
819    DO ji=1,kjpindex
820       twbr(ji) = (delsoilmoist(ji) + delintercept(ji) + delswe(ji)) &
821            - ( precip_rain(ji) + precip_snow(ji) + irrigation(ji) + floodout(ji) &
822            + returnflow(ji) + reinfiltration(ji) ) &
823            + ( runoff(ji) + drainage(ji) + SUM(vevapwet(ji,:)) &
824            + SUM(transpir(ji,:)) + vevapnu(ji) + vevapsno(ji) + vevapflo(ji) ) 
825    ENDDO
826    ! Transform unit from kg/m2/dt to kg/m2/s (or mm/s)
827    CALL xios_orchidee_send_field("twbr",twbr/dt_sechiba)
828    CALL xios_orchidee_send_field("undermcr",undermcr) ! nb of tiles undermcr at end of timestep
829
830    ! Calculate land_nroot : grid-cell mean of nroot
831    ! Do not treat PFT1 because it has no roots
832    land_nroot(:,:) = zero
833    DO jsl=1,nslm
834       DO jv=2,nvm
835          DO ji=1,kjpindex
836               IF ( vegtot(ji) > min_sechiba ) THEN
837               land_nroot(ji,jsl) = land_nroot(ji,jsl) + veget_max(ji,jv) * nroot(ji,jv,jsl) / vegtot(ji) 
838            END IF
839          END DO
840       ENDDO
841    ENDDO
842    CALL xios_orchidee_send_field("nroot",land_nroot)   
843
844    DO jsl=1,nslm
845       land_dlh(:,jsl)=dlh(jsl)
846    ENDDO
847    CALL xios_orchidee_send_field("dlh",land_dlh)
848
849    ! Particular soil moisture values, spatially averaged over the grid-cell
850    ! (a) total SM in kg/m2
851    !     we average the total values of each soiltile and multiply by vegtot to transform to a grid-cell mean (over total land)
852    land_tmcs(:) = zero
853    land_tmcfc(:) = zero
854    DO jst=1,nstm
855       DO ji=1,kjpindex
856          land_tmcs(ji) = land_tmcs(ji) + soiltile(ji,jst) * tmcs(ji,jst) * vegtot(ji)
857          land_tmcfc(ji) = land_tmcfc(ji) + soiltile(ji,jst) * tmcfc(ji,jst) * vegtot(ji)
858       ENDDO
859    ENDDO
860    CALL xios_orchidee_send_field("tmcs",land_tmcs) ! in kg/m2
861    CALL xios_orchidee_send_field("tmcfc",land_tmcfc) ! in kg/m2
862
863    ! (b) volumetric moisture content by layers in m3/m3
864    !     mcs etc are identical in all layers (no normalization by vegtot to be comparable to mc)
865    DO jsl=1,nslm
866       land_mcs(:,jsl) = mcs(njsc(:))
867       land_mcfc(:,jsl) = mcfc(njsc(:))
868       land_mcw(:,jsl) = mcw(njsc(:))
869       land_mcr(:,jsl) = mcr(njsc(:))
870    ENDDO
871    CALL xios_orchidee_send_field("mcs",land_mcs) ! in m3/m3
872    CALL xios_orchidee_send_field("mcfc",land_mcfc) ! in m3/m3
873    CALL xios_orchidee_send_field("mcw",land_mcw) ! in m3/m3
874    CALL xios_orchidee_send_field("mcr",land_mcr) ! in m3/m3
875         
876    CALL xios_orchidee_send_field("water2infilt",water2infilt)   
877    CALL xios_orchidee_send_field("mc",mc)
878    CALL xios_orchidee_send_field("kfact_root",kfact_root)
879    CALL xios_orchidee_send_field("vegetmax_soil",vegetmax_soil)
880    CALL xios_orchidee_send_field("evapnu_soil",ae_ns/dt_sechiba)
881    CALL xios_orchidee_send_field("drainage_soil",dr_ns/dt_sechiba)
882    CALL xios_orchidee_send_field("transpir_soil",tr_ns/dt_sechiba)
883    CALL xios_orchidee_send_field("runoff_soil",ru_ns/dt_sechiba)
884    CALL xios_orchidee_send_field("humrel",humrel)     
885    CALL xios_orchidee_send_field("drainage",drainage/dt_sechiba) ! [kg m-2 s-1]
886    CALL xios_orchidee_send_field("runoff",runoff/dt_sechiba) ! [kg m-2 s-1]
887    CALL xios_orchidee_send_field("precisol",precisol/dt_sechiba)
888    CALL xios_orchidee_send_field("throughfall",throughfall/dt_sechiba)
889    CALL xios_orchidee_send_field("precip_rain",precip_rain/dt_sechiba)
890    CALL xios_orchidee_send_field("precip_snow",precip_snow/dt_sechiba)
891    CALL xios_orchidee_send_field("qsintmax",qsintmax)
892    CALL xios_orchidee_send_field("qsintveg",qsintveg)
893    CALL xios_orchidee_send_field("qsintveg_tot",SUM(qsintveg(:,:),dim=2))
894    histvar(:)=(precip_rain(:)-SUM(throughfall(:,:),dim=2))
895    CALL xios_orchidee_send_field("prveg",histvar/dt_sechiba)
896
897    IF ( do_floodplains ) THEN
898       CALL xios_orchidee_send_field("floodout",floodout/dt_sechiba)
899    END IF
900
901    CALL xios_orchidee_send_field("snowmelt",snowmelt/dt_sechiba)
902    CALL xios_orchidee_send_field("tot_melt",tot_melt/dt_sechiba)
903
904    CALL xios_orchidee_send_field("soilmoist",soilmoist)
905    CALL xios_orchidee_send_field("soilmoist_liquid",soilmoist_liquid)
906    CALL xios_orchidee_send_field("humtot_frozen",SUM(soilmoist(:,:),2)-SUM(soilmoist_liquid(:,:),2))
907    CALL xios_orchidee_send_field("tmc",tmc)
908    CALL xios_orchidee_send_field("humtot",humtot)
909    CALL xios_orchidee_send_field("humtot_top",humtot_top)
910
911    ! For the soil wetness above wilting point for CMIP6 (mrsow)
912    mrsow(:) = MAX( zero,humtot(:) - zmaxh*mille*mcw(njsc(:)) ) &
913         / ( zmaxh*mille*( mcs(njsc(:)) - mcw(njsc(:)) ) )
914    CALL xios_orchidee_send_field("mrsow",mrsow)
915
916
917   
918    ! Prepare diagnostic snow variables depending on snow scheme
919    IF (ok_explicitsnow) THEN
920       !  Add XIOS default value where no snow
921       DO ji=1,kjpindex
922          IF (snow(ji) > 0) THEN
923             snowdz_diag(ji,:) = snowdz(ji,:)
924             snowdepth_diag(ji) = SUM(snowdz(ji,:))*(1-totfrac_nobio(ji))*frac_snow_veg(ji)
925          ELSE
926             snowdz_diag(ji,:) = xios_default_val
927             snowdepth_diag(ji) = xios_default_val             
928          END IF
929       END DO
930       CALL xios_orchidee_send_field("snowdz",snowdz_diag)
931       CALL xios_orchidee_send_field("snowdepth",snowdepth_diag)
932    ELSE
933       ! Add XIOS default value where no snow
934       DO ji=1,kjpindex
935          IF (snow(ji) > 0) THEN
936             snowdz_diag(ji,:) = snowdepth(ji)
937             snowdepth_diag(ji) = snowdepth(ji)*(1-totfrac_nobio(ji))
938          ELSE
939             snowdz_diag(ji,:) = xios_default_val
940             snowdepth_diag(ji) = xios_default_val             
941          END IF
942       END DO
943       CALL xios_orchidee_send_field("snowdz",snowdz_diag(:,1))
944       CALL xios_orchidee_send_field("snowdepth",snowdepth_diag)
945    END IF
946
947    CALL xios_orchidee_send_field("frac_bare",frac_bare)
948
949    CALL xios_orchidee_send_field("soilwet",soilwet)
950    CALL xios_orchidee_send_field("delsoilmoist",delsoilmoist)
951    CALL xios_orchidee_send_field("delswe",delswe)
952    CALL xios_orchidee_send_field("delintercept",delintercept) 
953
954    IF (ok_freeze_cwrr) THEN
955       CALL xios_orchidee_send_field("profil_froz_hydro",profil_froz_hydro)
956       CALL xios_orchidee_send_field("temp_hydro",temp_hydro)
957    END IF
958    CALL xios_orchidee_send_field("profil_froz_hydro_ns", profil_froz_hydro_ns)
959    CALL xios_orchidee_send_field("kk_moy",kk_moy) ! in mm/d
960
961
962    !! Calculate diagnostic variables on Landuse tiles for LUMIP/CMIP6
963    humtot_lut(:,:)=0
964    humtot_top_lut(:,:)=0
965    mrro_lut(:,:)=0
966    DO jv=1,nvm
967       jst=pref_soil_veg(jv) ! soil tile index
968       IF (natural(jv)) THEN
969          humtot_lut(:,id_psl) = humtot_lut(:,id_psl) + tmc(:,jst)*veget_max(:,jv)
970          humtot_top_lut(:,id_psl) = humtot_top_lut(:,id_psl) + tmc_top(:,jst)*veget_max(:,jv)
971          mrro_lut(:,id_psl) = mrro_lut(:,id_psl) + (dr_ns(:,jst)+ru_ns(:,jst))*veget_max(:,jv)
972       ELSE
973          humtot_lut(:,id_crp) = humtot_lut(:,id_crp) + tmc(:,jst)*veget_max(:,jv)
974          humtot_top_lut(:,id_crp) = humtot_top_lut(:,id_crp) + tmc_top(:,jst)*veget_max(:,jv)
975          mrro_lut(:,id_crp) = mrro_lut(:,id_crp) + (dr_ns(:,jst)+ru_ns(:,jst))*veget_max(:,jv)
976       ENDIF
977    END DO
978
979    WHERE (fraclut(:,id_psl)>min_sechiba)
980       humtot_lut(:,id_psl) = humtot_lut(:,id_psl)/fraclut(:,id_psl)
981       humtot_top_lut(:,id_psl) = humtot_top_lut(:,id_psl)/fraclut(:,id_psl)
982       mrro_lut(:,id_psl) = mrro_lut(:,id_psl)/fraclut(:,id_psl)/dt_sechiba
983    ELSEWHERE
984       humtot_lut(:,id_psl) = val_exp
985       humtot_top_lut(:,id_psl) = val_exp
986       mrro_lut(:,id_psl) = val_exp
987    END WHERE
988    WHERE (fraclut(:,id_crp)>min_sechiba)
989       humtot_lut(:,id_crp) = humtot_lut(:,id_crp)/fraclut(:,id_crp)
990       humtot_top_lut(:,id_crp) = humtot_top_lut(:,id_crp)/fraclut(:,id_crp)
991       mrro_lut(:,id_crp) = mrro_lut(:,id_crp)/fraclut(:,id_crp)/dt_sechiba
992    ELSEWHERE
993       humtot_lut(:,id_crp) = val_exp
994       humtot_top_lut(:,id_crp) = val_exp
995       mrro_lut(:,id_crp) = val_exp
996    END WHERE
997
998    humtot_lut(:,id_pst) = val_exp
999    humtot_lut(:,id_urb) = val_exp
1000    humtot_top_lut(:,id_pst) = val_exp
1001    humtot_top_lut(:,id_urb) = val_exp
1002    mrro_lut(:,id_pst) = val_exp
1003    mrro_lut(:,id_urb) = val_exp
1004
1005    CALL xios_orchidee_send_field("humtot_lut",humtot_lut)
1006    CALL xios_orchidee_send_field("humtot_top_lut",humtot_top_lut)
1007    CALL xios_orchidee_send_field("mrro_lut",mrro_lut)
1008
1009
1010    IF ( .NOT. almaoutput ) THEN
1011       CALL histwrite_p(hist_id, 'frac_bare', kjit, frac_bare, kjpindex*nvm, indexveg)
1012
1013       DO jst=1,nstm
1014          ! var_name= "mc_1" ... "mc_3"
1015          WRITE (var_name,"('moistc_',i1)") jst
1016          CALL histwrite_p(hist_id, TRIM(var_name), kjit,mc(:,:,jst), kjpindex*nslm, indexlayer)
1017
1018          ! var_name= "kfactroot_1" ... "kfactroot_3"
1019          WRITE (var_name,"('kfactroot_',i1)") jst
1020          CALL histwrite_p(hist_id, TRIM(var_name), kjit, kfact_root(:,:,jst), kjpindex*nslm, indexlayer)
1021
1022          ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1023          WRITE (var_name,"('vegetsoil_',i1)") jst
1024          CALL histwrite_p(hist_id, TRIM(var_name), kjit,vegetmax_soil(:,:,jst), kjpindex*nvm, indexveg)
1025       ENDDO
1026       CALL histwrite_p(hist_id, 'evapnu_soil', kjit, ae_ns, kjpindex*nstm, indexsoil)
1027       CALL histwrite_p(hist_id, 'drainage_soil', kjit, dr_ns, kjpindex*nstm, indexsoil)
1028       CALL histwrite_p(hist_id, 'transpir_soil', kjit, tr_ns, kjpindex*nstm, indexsoil)
1029       CALL histwrite_p(hist_id, 'runoff_soil', kjit, ru_ns, kjpindex*nstm, indexsoil)
1030       CALL histwrite_p(hist_id, 'humtot_soil', kjit, tmc, kjpindex*nstm, indexsoil)
1031       ! mrso is a perfect duplicate of humtot
1032       CALL histwrite_p(hist_id, 'humtot', kjit, humtot, kjpindex, index)
1033       CALL histwrite_p(hist_id, 'mrso', kjit, humtot, kjpindex, index)
1034       CALL histwrite_p(hist_id, 'mrsos', kjit, humtot_top, kjpindex, index)
1035       njsc_tmp(:)=njsc(:)
1036       CALL histwrite_p(hist_id, 'soilindex', kjit, njsc_tmp, kjpindex, index)
1037       CALL histwrite_p(hist_id, 'humrel',   kjit, humrel,   kjpindex*nvm, indexveg)
1038       CALL histwrite_p(hist_id, 'drainage', kjit, drainage, kjpindex, index)
1039       ! NB! According to histdef in intersurf, the variables 'runoff' and 'mrros' have different units
1040       CALL histwrite_p(hist_id, 'runoff', kjit, runoff, kjpindex, index)
1041       CALL histwrite_p(hist_id, 'mrros', kjit, runoff, kjpindex, index)
1042       histvar(:)=(runoff(:)+drainage(:))
1043       CALL histwrite_p(hist_id, 'mrro', kjit, histvar, kjpindex, index)
1044       CALL histwrite_p(hist_id, 'precisol', kjit, precisol, kjpindex*nvm, indexveg)
1045       CALL histwrite_p(hist_id, 'rain', kjit, precip_rain, kjpindex, index)
1046
1047       histvar(:)=(precip_rain(:)-SUM(throughfall(:,:),dim=2))
1048       CALL histwrite_p(hist_id, 'prveg', kjit, histvar, kjpindex, index)
1049
1050       CALL histwrite_p(hist_id, 'snowf', kjit, precip_snow, kjpindex, index)
1051       CALL histwrite_p(hist_id, 'qsintmax', kjit, qsintmax, kjpindex*nvm, indexveg)
1052       CALL histwrite_p(hist_id, 'qsintveg', kjit, qsintveg, kjpindex*nvm, indexveg)
1053       CALL histwrite_p(hist_id, 'snowmelt',kjit,snowmelt,kjpindex,index)
1054       CALL histwrite_p(hist_id, 'shumdiag_perma',kjit,shumdiag_perma,kjpindex*nslm,indexnslm)
1055
1056       IF ( do_floodplains ) THEN
1057          CALL histwrite_p(hist_id, 'floodout', kjit, floodout, kjpindex, index)
1058       ENDIF
1059       !
1060       IF ( hist2_id > 0 ) THEN
1061          DO jst=1,nstm
1062             ! var_name= "mc_1" ... "mc_3"
1063             WRITE (var_name,"('moistc_',i1)") jst
1064             CALL histwrite_p(hist2_id, TRIM(var_name), kjit,mc(:,:,jst), kjpindex*nslm, indexlayer)
1065
1066             ! var_name= "kfactroot_1" ... "kfactroot_3"
1067             WRITE (var_name,"('kfactroot_',i1)") jst
1068             CALL histwrite_p(hist2_id, TRIM(var_name), kjit, kfact_root(:,:,jst), kjpindex*nslm, indexlayer)
1069
1070             ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1071             WRITE (var_name,"('vegetsoil_',i1)") jst
1072             CALL histwrite_p(hist2_id, TRIM(var_name), kjit,vegetmax_soil(:,:,jst), kjpindex*nvm, indexveg)
1073          ENDDO
1074          CALL histwrite_p(hist2_id, 'evapnu_soil', kjit, ae_ns, kjpindex*nstm, indexsoil)
1075          CALL histwrite_p(hist2_id, 'drainage_soil', kjit, dr_ns, kjpindex*nstm, indexsoil)
1076          CALL histwrite_p(hist2_id, 'transpir_soil', kjit, tr_ns, kjpindex*nstm, indexsoil)
1077          CALL histwrite_p(hist2_id, 'runoff_soil', kjit, ru_ns, kjpindex*nstm, indexsoil)
1078          CALL histwrite_p(hist2_id, 'humtot_soil', kjit, tmc, kjpindex*nstm, indexsoil)
1079          ! mrso is a perfect duplicate of humtot
1080          CALL histwrite_p(hist2_id, 'humtot', kjit, humtot, kjpindex, index)
1081          CALL histwrite_p(hist2_id, 'mrso', kjit, humtot, kjpindex, index)
1082          CALL histwrite_p(hist2_id, 'mrsos', kjit, humtot_top, kjpindex, index)
1083          njsc_tmp(:)=njsc(:)
1084          CALL histwrite_p(hist2_id, 'soilindex', kjit, njsc_tmp, kjpindex, index)
1085          CALL histwrite_p(hist2_id, 'humrel',   kjit, humrel,   kjpindex*nvm, indexveg)
1086          CALL histwrite_p(hist2_id, 'drainage', kjit, drainage, kjpindex, index)
1087          ! NB! According to histdef in intersurf, the variables 'runoff' and 'mrros' have different units
1088          CALL histwrite_p(hist2_id, 'runoff', kjit, runoff, kjpindex, index)
1089          CALL histwrite_p(hist2_id, 'mrros', kjit, runoff, kjpindex, index)
1090          histvar(:)=(runoff(:)+drainage(:))
1091          CALL histwrite_p(hist2_id, 'mrro', kjit, histvar, kjpindex, index)
1092
1093          IF ( do_floodplains ) THEN
1094             CALL histwrite_p(hist2_id, 'floodout', kjit, floodout, kjpindex, index)
1095          ENDIF
1096          CALL histwrite_p(hist2_id, 'precisol', kjit, precisol, kjpindex*nvm, indexveg)
1097          CALL histwrite_p(hist2_id, 'rain', kjit, precip_rain, kjpindex, index)
1098          CALL histwrite_p(hist2_id, 'snowf', kjit, precip_snow, kjpindex, index)
1099          CALL histwrite_p(hist2_id, 'snowmelt',kjit,snowmelt,kjpindex,index)
1100          CALL histwrite_p(hist2_id, 'qsintmax', kjit, qsintmax, kjpindex*nvm, indexveg)
1101          CALL histwrite_p(hist2_id, 'qsintveg', kjit, qsintveg, kjpindex*nvm, indexveg)
1102       ENDIF
1103    ELSE
1104       CALL histwrite_p(hist_id, 'Snowf', kjit, precip_snow, kjpindex, index)
1105       CALL histwrite_p(hist_id, 'Rainf', kjit, precip_rain, kjpindex, index)
1106       CALL histwrite_p(hist_id, 'Qs', kjit, runoff, kjpindex, index)
1107       CALL histwrite_p(hist_id, 'Qsb', kjit, drainage, kjpindex, index)
1108       CALL histwrite_p(hist_id, 'Qsm', kjit, snowmelt, kjpindex, index)
1109       CALL histwrite_p(hist_id, 'DelSoilMoist', kjit, delsoilmoist, kjpindex, index)
1110       CALL histwrite_p(hist_id, 'DelSWE', kjit, delswe, kjpindex, index)
1111       CALL histwrite_p(hist_id, 'DelIntercept', kjit, delintercept, kjpindex, index)
1112       !
1113       CALL histwrite_p(hist_id, 'SoilMoist', kjit, soilmoist, kjpindex*nslm, indexlayer)
1114       CALL histwrite_p(hist_id, 'SoilWet', kjit, soilwet, kjpindex, index)
1115       !
1116       CALL histwrite_p(hist_id, 'RootMoist', kjit, tot_watsoil_end, kjpindex, index)
1117       CALL histwrite_p(hist_id, 'SubSnow', kjit, vevapsno, kjpindex, index)
1118       !
1119       IF (.NOT. ok_explicitsnow) CALL histwrite_p(hist_id, 'SnowDepth', kjit, snowdepth, kjpindex, index)
1120       !
1121       IF ( hist2_id > 0 ) THEN
1122          CALL histwrite_p(hist2_id, 'Snowf', kjit, precip_snow, kjpindex, index)
1123          CALL histwrite_p(hist2_id, 'Rainf', kjit, precip_rain, kjpindex, index)
1124          CALL histwrite_p(hist2_id, 'Qs', kjit, runoff, kjpindex, index)
1125          CALL histwrite_p(hist2_id, 'Qsb', kjit, drainage, kjpindex, index)
1126          CALL histwrite_p(hist2_id, 'Qsm', kjit, snowmelt, kjpindex, index)
1127          CALL histwrite_p(hist2_id, 'DelSoilMoist', kjit, delsoilmoist, kjpindex, index)
1128          CALL histwrite_p(hist2_id, 'DelSWE', kjit, delswe, kjpindex, index)
1129          CALL histwrite_p(hist2_id, 'DelIntercept', kjit, delintercept, kjpindex, index)
1130          !
1131          CALL histwrite_p(hist2_id, 'SoilMoist', kjit, soilmoist, kjpindex*nslm, indexlayer)
1132          CALL histwrite_p(hist2_id, 'SoilWet', kjit, soilwet, kjpindex, index)
1133          !
1134          CALL histwrite_p(hist2_id, 'RootMoist', kjit, tot_watsoil_end, kjpindex, index)
1135          CALL histwrite_p(hist2_id, 'SubSnow', kjit, vevapsno, kjpindex, index)
1136          !
1137          IF (.NOT. ok_explicitsnow) CALL histwrite_p(hist2_id, 'SnowDepth', kjit, snowdepth, kjpindex, index)
1138       ENDIF
1139    ENDIF
1140
1141    IF (ok_freeze_cwrr) THEN
1142       CALL histwrite_p(hist_id, 'profil_froz_hydro', kjit,profil_froz_hydro , kjpindex*nslm, indexlayer)
1143       
1144       CALL histwrite_p(hist_id, 'temp_hydro', kjit,temp_hydro , kjpindex*nslm, indexlayer)
1145    ENDIF
1146    CALL histwrite_p(hist_id, 'kk_moy', kjit, kk_moy,kjpindex*nslm, indexlayer) ! averaged over soiltiles
1147    DO jst=1,nstm
1148       WRITE (var_name,"('profil_froz_hydro_',i1)") jst
1149       CALL histwrite_p(hist_id, TRIM(var_name), kjit, profil_froz_hydro_ns(:,:,jst), kjpindex*nslm, indexlayer)
1150    ENDDO
1151
1152    ! Copy soilmoist into a local variable to be sent to thermosoil
1153    soilmoist_out(:,:) = soilmoist(:,:)
1154
1155    IF (printlev>=3) WRITE (numout,*) ' hydrol_main Done '
1156
1157  END SUBROUTINE hydrol_main
1158
1159
1160!! ================================================================================================================================
1161!! SUBROUTINE   : hydrol_finalize
1162!!
1163!>\BRIEF         
1164!!
1165!! DESCRIPTION : This subroutine writes the module variables and variables calculated in hydrol to restart file
1166!!
1167!! MAIN OUTPUT VARIABLE(S) :
1168!!
1169!! REFERENCE(S) :
1170!!
1171!! FLOWCHART    : None
1172!! \n
1173!_ ================================================================================================================================
1174
1175  SUBROUTINE hydrol_finalize( kjit,           kjpindex,   rest_id,  vegstress,  &
1176                              qsintveg,       humrel,     snow,     snow_age, snow_nobio, &
1177                              snow_nobio_age, snowrho,    snowtemp, snowdz,     &
1178                              snowheat,       snowgrain,  &
1179                              drysoil_frac, evap_bare_lim)
1180
1181    !! 0. Variable and parameter declaration
1182    !! 0.1 Input variables
1183    INTEGER(i_std), INTENT(in)                           :: kjit           !! Time step number
1184    INTEGER(i_std), INTENT(in)                           :: kjpindex       !! Domain size
1185    INTEGER(i_std),INTENT (in)                           :: rest_id        !! Restart file identifier
1186    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: vegstress      !! Veg. moisture stress (only for vegetation growth)
1187    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: qsintveg       !! Water on vegetation due to interception
1188    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: humrel
1189    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow           !! Snow mass [Kg/m^2]
1190    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow_age       !! Snow age
1191    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio     !! Water balance on ice, lakes, .. [Kg/m^2]
1192    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio_age !! Snow age on ice, lakes, ...
1193    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowrho        !! Snow density
1194    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowtemp       !! Snow temperature
1195    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowdz         !! Snow layer thickness
1196    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowheat       !! Snow heat content
1197    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowgrain      !! Snow grainsize
1198    REAL(r_std),DIMENSION (kjpindex),INTENT(in)          :: drysoil_frac   !! function of litter wetness
1199    REAL(r_std),DIMENSION (kjpindex),INTENT(in)          :: evap_bare_lim
1200
1201    !! 0.4 Local variables
1202    INTEGER(i_std)                                       :: jst, jsl
1203   
1204!_ ================================================================================================================================
1205
1206
1207    IF (printlev>=3) WRITE (numout,*) 'Write restart file with HYDROLOGIC variables '
1208
1209    DO jst=1,nstm
1210       ! var_name= "mc_1" ... "mc_3"
1211       WRITE (var_name,"('moistc_',i1)") jst
1212       CALL restput_p(rest_id, var_name, nbp_glo,  nslm, 1, kjit, mc(:,:,jst), 'scatter',  nbp_glo, index_g)
1213    END DO
1214
1215    DO jst=1,nstm
1216       ! var_name= "mcl_1" ... "mcl_3"
1217       WRITE (var_name,"('moistcl_',i1)") jst
1218       CALL restput_p(rest_id, var_name, nbp_glo,  nslm, 1, kjit, mcl(:,:,jst), 'scatter',  nbp_glo, index_g)
1219    END DO
1220   
1221    IF (ok_nudge_mc) THEN
1222       DO jst=1,nstm
1223          WRITE (var_name,"('mc_read_next_',i1)") jst
1224          CALL restput_p(rest_id, var_name, nbp_glo,  nslm, 1, kjit, mc_read_next(:,:,jst), 'scatter',  nbp_glo, index_g)
1225       END DO
1226    END IF
1227
1228    IF (ok_nudge_snow) THEN
1229       CALL restput_p(rest_id, 'snowdz_read_next', nbp_glo,  nsnow, 1, kjit, snowdz_read_next(:,:), &
1230            'scatter',  nbp_glo, index_g)
1231       CALL restput_p(rest_id, 'snowrho_read_next', nbp_glo,  nsnow, 1, kjit, snowrho_read_next(:,:), &
1232            'scatter',  nbp_glo, index_g)
1233       CALL restput_p(rest_id, 'snowtemp_read_next', nbp_glo,  nsnow, 1, kjit, snowtemp_read_next(:,:), &
1234            'scatter',  nbp_glo, index_g)
1235    END IF
1236
1237
1238           
1239    DO jst=1,nstm
1240       DO jsl=1,nslm
1241          ! var_name= "us_1_01" ... "us_3_11"
1242          WRITE (var_name,"('us_',i1,'_',i2.2)") jst,jsl
1243          CALL restput_p(rest_id, var_name, nbp_glo,nvm, 1,kjit,us(:,:,jst,jsl),'scatter',nbp_glo,index_g)
1244       END DO
1245    END DO
1246   
1247    CALL restput_p(rest_id, 'free_drain_coef', nbp_glo,   nstm, 1, kjit,  free_drain_coef, 'scatter',  nbp_glo, index_g)
1248    CALL restput_p(rest_id, 'zwt_force', nbp_glo,   nstm, 1, kjit,  zwt_force, 'scatter',  nbp_glo, index_g)
1249    CALL restput_p(rest_id, 'water2infilt', nbp_glo,   nstm, 1, kjit,  water2infilt, 'scatter',  nbp_glo, index_g)
1250    CALL restput_p(rest_id, 'ae_ns', nbp_glo,   nstm, 1, kjit,  ae_ns, 'scatter',  nbp_glo, index_g)
1251    CALL restput_p(rest_id, 'vegstress', nbp_glo,   nvm, 1, kjit,  vegstress, 'scatter',  nbp_glo, index_g)
1252    CALL restput_p(rest_id, 'snow', nbp_glo,   1, 1, kjit,  snow, 'scatter',  nbp_glo, index_g)
1253    CALL restput_p(rest_id, 'snow_age', nbp_glo,   1, 1, kjit,  snow_age, 'scatter',  nbp_glo, index_g)
1254    CALL restput_p(rest_id, 'snow_nobio', nbp_glo,   nnobio, 1, kjit,  snow_nobio, 'scatter', nbp_glo, index_g)
1255    CALL restput_p(rest_id, 'snow_nobio_age', nbp_glo,   nnobio, 1, kjit,  snow_nobio_age, 'scatter', nbp_glo, index_g)
1256    CALL restput_p(rest_id, 'qsintveg', nbp_glo, nvm, 1, kjit,  qsintveg, 'scatter',  nbp_glo, index_g)
1257    CALL restput_p(rest_id, 'evap_bare_lim_ns', nbp_glo, nstm, 1, kjit,  evap_bare_lim_ns, 'scatter',  nbp_glo, index_g)
1258    CALL restput_p(rest_id, 'evap_bare_lim', nbp_glo, 1, 1, kjit,  evap_bare_lim, 'scatter',  nbp_glo, index_g)
1259    CALL restput_p(rest_id, 'resdist', nbp_glo, nstm, 1, kjit,  resdist, 'scatter',  nbp_glo, index_g) 
1260    CALL restput_p(rest_id, 'vegtot_old', nbp_glo, 1, 1, kjit,  vegtot_old, 'scatter',  nbp_glo, index_g)           
1261    CALL restput_p(rest_id, 'drysoil_frac', nbp_glo,   1, 1, kjit, drysoil_frac, 'scatter', nbp_glo, index_g)
1262    CALL restput_p(rest_id, 'humrel', nbp_glo,   nvm, 1, kjit,  humrel, 'scatter',  nbp_glo, index_g)
1263
1264    CALL restput_p(rest_id, 'tot_watveg_beg', nbp_glo,  1, 1, kjit,  tot_watveg_beg, 'scatter',  nbp_glo, index_g)
1265    CALL restput_p(rest_id, 'tot_watsoil_beg', nbp_glo, 1, 1, kjit,  tot_watsoil_beg, 'scatter',  nbp_glo, index_g)
1266    CALL restput_p(rest_id, 'snow_beg', nbp_glo,        1, 1, kjit,  snow_beg, 'scatter',  nbp_glo, index_g)
1267   
1268   
1269    ! Write variables for explictsnow module to restart file
1270    IF (ok_explicitsnow) THEN
1271       CALL explicitsnow_finalize ( kjit,     kjpindex, rest_id,    snowrho,   &
1272                                    snowtemp, snowdz,   snowheat,   snowgrain)
1273    END IF
1274
1275  END SUBROUTINE hydrol_finalize
1276
1277
1278!! ================================================================================================================================
1279!! SUBROUTINE   : hydrol_init
1280!!
1281!>\BRIEF        Initializations and memory allocation   
1282!!
1283!! DESCRIPTION  :
1284!! - 1 Some initializations
1285!! - 2 make dynamic allocation with good dimension
1286!! - 2.1 array allocation for soil textur
1287!! - 2.2 Soil texture choice
1288!! - 3 Other array allocation
1289!! - 4 Open restart input file and read data for HYDROLOGIC process
1290!! - 5 get restart values if none were found in the restart file
1291!! - 6 Vegetation array     
1292!! - 7 set humrelv from us
1293!!
1294!! RECENT CHANGE(S) : None
1295!!
1296!! MAIN OUTPUT VARIABLE(S) :
1297!!
1298!! REFERENCE(S) :
1299!!
1300!! FLOWCHART    : None
1301!! \n
1302!_ ================================================================================================================================
1303!!_ hydrol_init
1304
1305  SUBROUTINE hydrol_init(kjit, kjpindex, index, rest_id, veget_max, soiltile, &
1306       humrel,  vegstress, snow,       snow_age,   snow_nobio, snow_nobio_age, qsintveg, &
1307       snowdz,  snowgrain, snowrho,    snowtemp,   snowheat, &
1308       drysoil_frac, evap_bare_lim)
1309   
1310
1311    !! 0. Variable and parameter declaration
1312
1313    !! 0.1 Input variables
1314
1315    INTEGER(i_std), INTENT (in)                         :: kjit               !! Time step number
1316    INTEGER(i_std), INTENT (in)                         :: kjpindex           !! Domain size
1317    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: index              !! Indeces of the points on the map
1318    INTEGER(i_std), INTENT (in)                         :: rest_id            !! _Restart_ file identifier
1319    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max          !! Carte de vegetation max
1320    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in)  :: soiltile           !! Fraction of each soil tile within vegtot (0-1, unitless)
1321
1322    !! 0.2 Output variables
1323
1324    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: humrel             !! Stress hydrique, relative humidity
1325    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: vegstress          !! Veg. moisture stress (only for vegetation growth)
1326    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: snow               !! Snow mass [Kg/m^2]
1327    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: snow_age           !! Snow age
1328    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out) :: snow_nobio       !! Snow on ice, lakes, ...
1329    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out) :: snow_nobio_age   !! Snow age on ice, lakes, ...
1330    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)    :: qsintveg         !! Water on vegetation due to interception
1331    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowdz           !! Snow depth
1332    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowgrain        !! Snow grain size
1333    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowheat         !! Snow heat content
1334    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowtemp         !! Snow temperature
1335    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowrho          !! Snow density
1336    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: drysoil_frac     !! function of litter wetness
1337    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: evap_bare_lim
1338
1339    !! 0.4 Local variables
1340
1341    INTEGER(i_std)                                     :: ier                   !! Error code
1342    INTEGER(i_std)                                     :: ji                    !! Index of land grid cells (1)
1343    INTEGER(i_std)                                     :: jv                    !! Index of PFTs (1)
1344    INTEGER(i_std)                                     :: jst                   !! Index of soil tiles (1)
1345    INTEGER(i_std)                                     :: jsl                   !! Index of soil layers (1)
1346    INTEGER(i_std)                                     :: jsc                   !! Index of soil texture (1)
1347    INTEGER(i_std), PARAMETER                          :: error_level = 3       !! Error level for consistency check
1348                                                                                !! Switch to 2 tu turn fatal errors into warnings 
1349    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: free_drain_max        !! Temporary var for initialization of free_drain_coef
1350    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: zwt_default           !! Temporary variable for initialization of zwt_force
1351    LOGICAL                                            :: zforce                !! To test if we force the WT in any of the soiltiles
1352
1353!_ ================================================================================================================================
1354
1355    !! 1 Some initializations
1356    !
1357    !Config Key   = DO_PONDS
1358    !Config Desc  = Should we include ponds
1359    !Config Def   = n
1360    !Config If    = HYDROL_CWRR
1361    !Config Help  = This parameters allows the user to ask the model
1362    !Config         to take into account the ponds and return
1363    !Config         the water into the soil moisture. If this is
1364    !Config         activated, then there is no reinfiltration
1365    !Config         computed inside the hydrol module.
1366    !Config Units = [FLAG]
1367    !
1368    doponds = .FALSE.
1369    CALL getin_p('DO_PONDS', doponds)
1370
1371    !Config Key   = FROZ_FRAC_CORR
1372    !Config Desc  = Coefficient for the frozen fraction correction
1373    !Config Def   = 1.0
1374    !Config If    = HYDROL_CWRR and OK_FREEZE
1375    !Config Help  =
1376    !Config Units = [-]
1377    froz_frac_corr = 1.0
1378    CALL getin_p("FROZ_FRAC_CORR", froz_frac_corr)
1379
1380    !Config Key   = MAX_FROZ_HYDRO
1381    !Config Desc  = Coefficient for the frozen fraction correction
1382    !Config Def   = 1.0
1383    !Config If    = HYDROL_CWRR and OK_FREEZE
1384    !Config Help  =
1385    !Config Units = [-]
1386    max_froz_hydro = 1.0
1387    CALL getin_p("MAX_FROZ_HYDRO", max_froz_hydro)
1388
1389    !Config Key   = SMTOT_CORR
1390    !Config Desc  = Coefficient for the frozen fraction correction
1391    !Config Def   = 2.0
1392    !Config If    = HYDROL_CWRR and OK_FREEZE
1393    !Config Help  =
1394    !Config Units = [-]
1395    smtot_corr = 2.0
1396    CALL getin_p("SMTOT_CORR", smtot_corr)
1397
1398    !Config Key   = DO_RSOIL
1399    !Config Desc  = Should we reduce soil evaporation with a soil resistance
1400    !Config Def   = n
1401    !Config If    = HYDROL_CWRR
1402    !Config Help  = This parameters allows the user to ask the model
1403    !Config         to calculate a soil resistance to reduce the soil evaporation
1404    !Config Units = [FLAG]
1405    !
1406    do_rsoil = .FALSE.
1407    CALL getin_p('DO_RSOIL', do_rsoil) 
1408
1409    !Config Key   = OK_DYNROOT
1410    !Config Desc  = Calculate dynamic root profile to optimize soil moisture usage 
1411    !Config Def   = n
1412    !Config If    = HYDROL_CWRR
1413    !Config Help  =
1414    !Config Units = [FLAG]
1415    ok_dynroot = .FALSE.
1416    CALL getin_p('OK_DYNROOT',ok_dynroot)
1417
1418    !! 2 make dynamic allocation with good dimension
1419
1420    !! 2.1 array allocation for soil texture
1421
1422    ALLOCATE (nvan(nscm),stat=ier)
1423    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nvan','','')
1424
1425    ALLOCATE (avan(nscm),stat=ier)
1426    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable avan','','')
1427
1428    ALLOCATE (mcr(nscm),stat=ier)
1429    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcr','','')
1430
1431    ALLOCATE (mcs(nscm),stat=ier)
1432    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcs','','')
1433
1434    ALLOCATE (ks(nscm),stat=ier)
1435    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ks','','')
1436
1437    ALLOCATE (pcent(nscm),stat=ier)
1438    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable pcent','','')
1439
1440    ALLOCATE (mcfc(nscm),stat=ier)
1441    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcfc','','')
1442
1443    ALLOCATE (mcw(nscm),stat=ier)
1444    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcw','','')
1445   
1446    ALLOCATE (mc_awet(nscm),stat=ier)
1447    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_awet','','')
1448
1449    ALLOCATE (mc_adry(nscm),stat=ier)
1450    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_adry','','')
1451       
1452    !!__2.2 Soil texture choose
1453
1454    SELECTCASE (nscm)
1455    CASE (3)
1456             
1457       nvan(:) = nvan_fao(:)       
1458       avan(:) = avan_fao(:)
1459       mcr(:) = mcr_fao(:)
1460       mcs(:) = mcs_fao(:)
1461       ks(:) = ks_fao(:)
1462       pcent(:) = pcent_fao(:)
1463       mcfc(:) = mcf_fao(:)
1464       mcw(:) = mcw_fao(:)
1465       mc_awet(:) = mc_awet_fao(:)
1466       mc_adry(:) = mc_adry_fao(:)
1467    CASE (12)
1468       
1469       nvan(:) = nvan_usda(:)
1470       avan(:) = avan_usda(:)
1471       mcr(:) = mcr_usda(:)
1472       mcs(:) = mcs_usda(:)
1473       ks(:) = ks_usda(:)
1474       pcent(:) = pcent_usda(:)
1475       mcfc(:) = mcf_usda(:)
1476       mcw(:) = mcw_usda(:)
1477       mc_awet(:) = mc_awet_usda(:)
1478       mc_adry(:) = mc_adry_usda(:)
1479       
1480    CASE DEFAULT
1481       WRITE (numout,*) 'Unsupported soil type classification. Choose between zobler and usda according to the map'
1482       CALL ipslerr_p(3,'hydrol_init','Unsupported soil type classification. ',&
1483            'Choose between zobler and usda according to the map','')
1484    ENDSELECT
1485
1486
1487    !! 2.3 Read in the run.def the parameters values defined by the user
1488
1489    !Config Key   = CWRR_N_VANGENUCHTEN
1490    !Config Desc  = Van genuchten coefficient n
1491    !Config If    = HYDROL_CWRR
1492    !Config Def   = 1.89, 1.56, 1.31
1493    !Config Help  = This parameter will be constant over the entire
1494    !Config         simulated domain, thus independent from soil
1495    !Config         texture.   
1496    !Config Units = [-]
1497    CALL getin_p("CWRR_N_VANGENUCHTEN",nvan)
1498
1499    !! Check parameter value (correct range)
1500    IF ( ANY(nvan(:) <= zero) ) THEN
1501       CALL ipslerr_p(error_level, "hydrol_init.", &
1502            &     "Wrong parameter value for CWRR_N_VANGENUCHTEN.", &
1503            &     "This parameter should be positive. ", &
1504            &     "Please, check parameter value in run.def. ")
1505    END IF
1506
1507
1508    !Config Key   = CWRR_A_VANGENUCHTEN
1509    !Config Desc  = Van genuchten coefficient a
1510    !Config If    = HYDROL_CWRR
1511    !Config Def   = 0.0075, 0.0036, 0.0019
1512    !Config Help  = This parameter will be constant over the entire
1513    !Config         simulated domain, thus independent from soil
1514    !Config         texture.   
1515    !Config Units = [1/mm] 
1516    CALL getin_p("CWRR_A_VANGENUCHTEN",avan)
1517
1518    !! Check parameter value (correct range)
1519    IF ( ANY(avan(:) <= zero) ) THEN
1520       CALL ipslerr_p(error_level, "hydrol_init.", &
1521            &     "Wrong parameter value for CWRR_A_VANGENUCHTEN.", &
1522            &     "This parameter should be positive. ", &
1523            &     "Please, check parameter value in run.def. ")
1524    END IF
1525
1526
1527    !Config Key   = VWC_RESIDUAL
1528    !Config Desc  = Residual soil water content
1529    !Config If    = HYDROL_CWRR
1530    !Config Def   = 0.065, 0.078, 0.095
1531    !Config Help  = This parameter will be constant over the entire
1532    !Config         simulated domain, thus independent from soil
1533    !Config         texture.   
1534    !Config Units = [m3/m3] 
1535    CALL getin_p("VWC_RESIDUAL",mcr)
1536
1537    !! Check parameter value (correct range)
1538    IF ( ANY(mcr(:) < zero) .OR. ANY(mcr(:) > 1.)  ) THEN
1539       CALL ipslerr_p(error_level, "hydrol_init.", &
1540            &     "Wrong parameter value for VWC_RESIDUAL.", &
1541            &     "This parameter is ranged between 0 and 1. ", &
1542            &     "Please, check parameter value in run.def. ")
1543    END IF
1544
1545   
1546    !Config Key   = VWC_SAT
1547    !Config Desc  = Saturated soil water content
1548    !Config If    = HYDROL_CWRR
1549    !Config Def   = 0.41, 0.43, 0.41
1550    !Config Help  = This parameter will be constant over the entire
1551    !Config         simulated domain, thus independent from soil
1552    !Config         texture.   
1553    !Config Units = [m3/m3] 
1554    CALL getin_p("VWC_SAT",mcs)
1555
1556    !! Check parameter value (correct range)
1557    IF ( ANY(mcs(:) < zero) .OR. ANY(mcs(:) > 1.) .OR. ANY(mcs(:) <= mcr(:)) ) THEN
1558       CALL ipslerr_p(error_level, "hydrol_init.", &
1559            &     "Wrong parameter value for VWC_SAT.", &
1560            &     "This parameter should be greater than VWC_RESIDUAL and less than 1. ", &
1561            &     "Please, check parameter value in run.def. ")
1562    END IF
1563
1564
1565    !Config Key   = CWRR_KS
1566    !Config Desc  = Hydraulic conductivity Saturation
1567    !Config If    = HYDROL_CWRR
1568    !Config Def   = 1060.8, 249.6, 62.4
1569    !Config Help  = This parameter will be constant over the entire
1570    !Config         simulated domain, thus independent from soil
1571    !Config         texture.   
1572    !Config Units = [mm/d]   
1573    CALL getin_p("CWRR_KS",ks)
1574
1575    !! Check parameter value (correct range)
1576    IF ( ANY(ks(:) <= zero) ) THEN
1577       CALL ipslerr_p(error_level, "hydrol_init.", &
1578            &     "Wrong parameter value for CWRR_KS.", &
1579            &     "This parameter should be positive. ", &
1580            &     "Please, check parameter value in run.def. ")
1581    END IF
1582
1583
1584    !Config Key   = WETNESS_TRANSPIR_MAX
1585    !Config Desc  = Soil moisture above which transpir is max
1586    !Config If    = HYDROL_CWRR
1587    !Config Def   = 0.5, 0.5, 0.5
1588    !Config Help  = This parameter is independent from soil texture for
1589    !Config         the time being.
1590    !Config Units = [-]   
1591    CALL getin_p("WETNESS_TRANSPIR_MAX",pcent)
1592
1593    !! Check parameter value (correct range)
1594    IF ( ANY(pcent(:) <= zero) .OR. ANY(pcent(:) > 1.) ) THEN
1595       CALL ipslerr_p(error_level, "hydrol_init.", &
1596            &     "Wrong parameter value for WETNESS_TRANSPIR_MAX.", &
1597            &     "This parameter should be positive and less or equals than 1. ", &
1598            &     "Please, check parameter value in run.def. ")
1599    END IF
1600
1601
1602    !Config Key   = VWC_FC
1603    !Config Desc  = Volumetric water content field capacity
1604    !Config If    = HYDROL_CWRR
1605    !Config Def   = 0.32, 0.32, 0.32
1606    !Config Help  = This parameter is independent from soil texture for
1607    !Config         the time being.
1608    !Config Units = [m3/m3]   
1609    CALL getin_p("VWC_FC",mcfc)
1610
1611    !! Check parameter value (correct range)
1612    IF ( ANY(mcfc(:) > mcs(:)) ) THEN
1613       CALL ipslerr_p(error_level, "hydrol_init.", &
1614            &     "Wrong parameter value for VWC_FC.", &
1615            &     "This parameter should be less than VWC_SAT. ", &
1616            &     "Please, check parameter value in run.def. ")
1617    END IF
1618
1619
1620    !Config Key   = VWC_WP
1621    !Config Desc  = Volumetric water content Wilting pt
1622    !Config If    = HYDROL_CWRR
1623    !Config Def   = 0.10, 0.10, 0.10
1624    !Config Help  = This parameter is independent from soil texture for
1625    !Config         the time being.
1626    !Config Units = [m3/m3]   
1627    CALL getin_p("VWC_WP",mcw)
1628
1629    !! Check parameter value (correct range)
1630    IF ( ANY(mcw(:) > mcfc(:)) .OR. ANY(mcw(:) < mcr(:)) ) THEN
1631       CALL ipslerr_p(error_level, "hydrol_init.", &
1632            &     "Wrong parameter value for VWC_WP.", &
1633            &     "This parameter should be greater or equal than VWC_RESIDUAL and less or equal than VWC_SAT.", &
1634            &     "Please, check parameter value in run.def. ")
1635    END IF
1636
1637
1638    !Config Key   = VWC_MIN_FOR_WET_ALB
1639    !Config Desc  = Vol. wat. cont. above which albedo is cst
1640    !Config If    = HYDROL_CWRR
1641    !Config Def   = 0.25, 0.25, 0.25
1642    !Config Help  = This parameter is independent from soil texture for
1643    !Config         the time being.
1644    !Config Units = [m3/m3] 
1645    CALL getin_p("VWC_MIN_FOR_WET_ALB",mc_awet)
1646
1647    !! Check parameter value (correct range)
1648    IF ( ANY(mc_awet(:) < 0) ) THEN
1649       CALL ipslerr_p(error_level, "hydrol_init.", &
1650            &     "Wrong parameter value for VWC_MIN_FOR_WET_ALB.", &
1651            &     "This parameter should be positive. ", &
1652            &     "Please, check parameter value in run.def. ")
1653    END IF
1654
1655
1656    !Config Key   = VWC_MAX_FOR_DRY_ALB
1657    !Config Desc  = Vol. wat. cont. below which albedo is cst
1658    !Config If    = HYDROL_CWRR
1659    !Config Def   = 0.1, 0.1, 0.1
1660    !Config Help  = This parameter is independent from soil texture for
1661    !Config         the time being.
1662    !Config Units = [m3/m3]   
1663    CALL getin_p("VWC_MAX_FOR_DRY_ALB",mc_adry)
1664
1665    !! Check parameter value (correct range)
1666    IF ( ANY(mc_adry(:) < 0) .OR. ANY(mc_adry(:) > mc_awet(:)) ) THEN
1667       CALL ipslerr_p(error_level, "hydrol_init.", &
1668            &     "Wrong parameter value for VWC_MAX_FOR_DRY_ALB.", &
1669            &     "This parameter should be positive and not greater than VWC_MIN_FOR_WET_ALB.", &
1670            &     "Please, check parameter value in run.def. ")
1671    END IF
1672
1673
1674    !! 3 Other array allocation
1675
1676
1677    ALLOCATE (mask_veget(kjpindex,nvm),stat=ier)
1678    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_veget','','')
1679
1680    ALLOCATE (mask_soiltile(kjpindex,nstm),stat=ier)
1681    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_soiltile','','')
1682
1683    ALLOCATE (humrelv(kjpindex,nvm,nstm),stat=ier)
1684    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable humrelv','','')
1685
1686    ALLOCATE (vegstressv(kjpindex,nvm,nstm),stat=ier) 
1687    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegstressv','','')
1688
1689    ALLOCATE (us(kjpindex,nvm,nstm,nslm),stat=ier) 
1690    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable us','','')
1691
1692    ALLOCATE (precisol(kjpindex,nvm),stat=ier) 
1693    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable precisol','','')
1694
1695    ALLOCATE (throughfall(kjpindex,nvm),stat=ier) 
1696    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable throughfall','','')
1697
1698    ALLOCATE (precisol_ns(kjpindex,nstm),stat=ier) 
1699    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable precisol_nc','','')
1700
1701    ALLOCATE (free_drain_coef(kjpindex,nstm),stat=ier) 
1702    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable free_drain_coef','','')
1703
1704    ALLOCATE (zwt_force(kjpindex,nstm),stat=ier) 
1705    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zwt_force','','')
1706
1707    ALLOCATE (frac_bare_ns(kjpindex,nstm),stat=ier) 
1708    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable frac_bare_ns','','')
1709
1710    ALLOCATE (water2infilt(kjpindex,nstm),stat=ier)
1711    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable water2infilt','','')
1712
1713    ALLOCATE (ae_ns(kjpindex,nstm),stat=ier) 
1714    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ae_ns','','')
1715
1716    ALLOCATE (evap_bare_lim_ns(kjpindex,nstm),stat=ier) 
1717    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable evap_bare_lim_ns','','')
1718
1719    ALLOCATE (rootsink(kjpindex,nslm,nstm),stat=ier) 
1720    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable rootsink','','')
1721
1722    ALLOCATE (subsnowveg(kjpindex),stat=ier) 
1723    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsnowveg','','')
1724
1725    ALLOCATE (subsnownobio(kjpindex,nnobio),stat=ier) 
1726    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsnownobio','','')
1727
1728    ALLOCATE (icemelt(kjpindex),stat=ier) 
1729    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable icemelt','','')
1730
1731    ALLOCATE (subsinksoil(kjpindex),stat=ier) 
1732    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsinksoil','','')
1733
1734    ALLOCATE (mx_eau_var(kjpindex),stat=ier)
1735    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mx_eau_var','','')
1736
1737    ALLOCATE (vegtot(kjpindex),stat=ier) 
1738    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegtot','','')
1739
1740    ALLOCATE (vegtot_old(kjpindex),stat=ier) 
1741    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegtot_old','','')
1742
1743    ALLOCATE (resdist(kjpindex,nstm),stat=ier)
1744    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable resdist','','')
1745
1746    ALLOCATE (humtot(kjpindex),stat=ier)
1747    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable humtot','','')
1748
1749    ALLOCATE (resolv(kjpindex),stat=ier) 
1750    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable resolv','','')
1751
1752    ALLOCATE (k(kjpindex,nslm),stat=ier) 
1753    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable k','','')
1754
1755    ALLOCATE (kk_moy(kjpindex,nslm),stat=ier) 
1756    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kk_moy','','')
1757    kk_moy(:,:) = 276.48
1758   
1759    ALLOCATE (kk(kjpindex,nslm,nstm),stat=ier) 
1760    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kk','','')
1761    kk(:,:,:) = 276.48
1762   
1763    ALLOCATE (avan_mod_tab(nslm,nscm),stat=ier) 
1764    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable avan_mod_tab','','')
1765   
1766    ALLOCATE (nvan_mod_tab(nslm,nscm),stat=ier) 
1767    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nvan_mod_tab','','')
1768
1769    ALLOCATE (a(kjpindex,nslm),stat=ier) 
1770    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable a','','')
1771
1772    ALLOCATE (b(kjpindex,nslm),stat=ier)
1773    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable b','','')
1774
1775    ALLOCATE (d(kjpindex,nslm),stat=ier)
1776    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable d','','')
1777
1778    ALLOCATE (e(kjpindex,nslm),stat=ier) 
1779    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable e','','')
1780
1781    ALLOCATE (f(kjpindex,nslm),stat=ier) 
1782    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable f','','')
1783
1784    ALLOCATE (g1(kjpindex,nslm),stat=ier) 
1785    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable g1','','')
1786
1787    ALLOCATE (ep(kjpindex,nslm),stat=ier)
1788    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ep','','')
1789
1790    ALLOCATE (fp(kjpindex,nslm),stat=ier)
1791    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fp','','')
1792
1793    ALLOCATE (gp(kjpindex,nslm),stat=ier)
1794    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable gp','','')
1795
1796    ALLOCATE (rhs(kjpindex,nslm),stat=ier)
1797    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable rhs','','')
1798
1799    ALLOCATE (srhs(kjpindex,nslm),stat=ier)
1800    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable srhs','','')
1801
1802    ALLOCATE (tmc(kjpindex,nstm),stat=ier)
1803    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc','','')
1804
1805    ALLOCATE (tmcs(kjpindex,nstm),stat=ier)
1806    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcs','','')
1807
1808    ALLOCATE (tmcr(kjpindex,nstm),stat=ier)
1809    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcr','','')
1810
1811    ALLOCATE (tmcfc(kjpindex,nstm),stat=ier)
1812    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcfc','','')
1813
1814    ALLOCATE (tmcw(kjpindex,nstm),stat=ier)
1815    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcw','','')
1816
1817    ALLOCATE (tmc_litter(kjpindex,nstm),stat=ier)
1818    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter','','')
1819
1820    ALLOCATE (tmc_litt_mea(kjpindex),stat=ier)
1821    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_mea','','')
1822
1823    ALLOCATE (tmc_litter_res(kjpindex,nstm),stat=ier)
1824    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_res','','')
1825
1826    ALLOCATE (tmc_litter_wilt(kjpindex,nstm),stat=ier)
1827    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_wilt','','')
1828
1829    ALLOCATE (tmc_litter_field(kjpindex,nstm),stat=ier)
1830    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_field','','')
1831
1832    ALLOCATE (tmc_litter_sat(kjpindex,nstm),stat=ier)
1833    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_sat','','')
1834
1835    ALLOCATE (tmc_litter_awet(kjpindex,nstm),stat=ier)
1836    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_awet','','')
1837
1838    ALLOCATE (tmc_litter_adry(kjpindex,nstm),stat=ier)
1839    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_adry','','')
1840
1841    ALLOCATE (tmc_litt_wet_mea(kjpindex),stat=ier)
1842    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_wet_mea','','')
1843
1844    ALLOCATE (tmc_litt_dry_mea(kjpindex),stat=ier)
1845    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_dry_mea','','')
1846
1847    ALLOCATE (v1(kjpindex,nstm),stat=ier)
1848    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable v1','','')
1849
1850    ALLOCATE (ru_ns(kjpindex,nstm),stat=ier)
1851    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ru_ns','','')
1852    ru_ns(:,:) = zero
1853
1854    ALLOCATE (dr_ns(kjpindex,nstm),stat=ier)
1855    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dr_ns','','')
1856    dr_ns(:,:) = zero
1857
1858    ALLOCATE (tr_ns(kjpindex,nstm),stat=ier)
1859    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tr_ns','','')
1860
1861    ALLOCATE (vegetmax_soil(kjpindex,nvm,nstm),stat=ier)
1862    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegetmax_soil','','')
1863
1864    ALLOCATE (mc(kjpindex,nslm,nstm),stat=ier)
1865    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc','','')
1866
1867
1868    ! Variables for nudging of soil moisture
1869    IF (ok_nudge_mc) THEN
1870       ALLOCATE (mc_read_prev(kjpindex,nslm,nstm),stat=ier)
1871       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_read_prev','','')
1872       ALLOCATE (mc_read_next(kjpindex,nslm,nstm),stat=ier)
1873       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_read_next','','')
1874       ALLOCATE (mask_mc_interp(kjpindex,nslm,nstm),stat=ier)
1875       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_mc_interp','','')
1876    END IF
1877
1878    ! Variables for nudging of snow variables
1879    IF (ok_nudge_snow) THEN
1880       ALLOCATE (snowdz_read_prev(kjpindex,nsnow),stat=ier)
1881       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowdz_read_prev','','')
1882       ALLOCATE (snowdz_read_next(kjpindex,nsnow),stat=ier)
1883       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowdz_read_next','','')
1884       
1885       ALLOCATE (snowrho_read_prev(kjpindex,nsnow),stat=ier)
1886       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowrho_read_prev','','')
1887       ALLOCATE (snowrho_read_next(kjpindex,nsnow),stat=ier)
1888       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowrho_read_next','','')
1889       
1890       ALLOCATE (snowtemp_read_prev(kjpindex,nsnow),stat=ier)
1891       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowtemp_read_prev','','')
1892       ALLOCATE (snowtemp_read_next(kjpindex,nsnow),stat=ier)
1893       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowtemp_read_next','','')
1894       
1895       ALLOCATE (mask_snow_interp(kjpindex,nsnow),stat=ier)
1896       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_snow_interp','','')
1897    END IF
1898
1899    ALLOCATE (mcl(kjpindex, nslm, nstm),stat=ier)
1900    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcl','','')
1901
1902    IF (ok_freeze_cwrr) THEN
1903       ALLOCATE (profil_froz_hydro(kjpindex, nslm),stat=ier)
1904       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydrol','','')
1905       profil_froz_hydro(:,:) = zero
1906       
1907       ALLOCATE (temp_hydro(kjpindex, nslm),stat=ier)
1908       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable temp_hydro','','')
1909       temp_hydro(:,:) = 280.
1910    ENDIF
1911   
1912    ALLOCATE (profil_froz_hydro_ns(kjpindex, nslm, nstm),stat=ier)
1913    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydro_ns','','')
1914    profil_froz_hydro_ns(:,:,:) = zero
1915   
1916    ALLOCATE (soilmoist(kjpindex,nslm),stat=ier)
1917    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soilmoist','','')
1918
1919    ALLOCATE (soilmoist_liquid(kjpindex,nslm),stat=ier)
1920    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soilmoist_liquid','','')
1921
1922    ALLOCATE (soil_wet_ns(kjpindex,nslm,nstm),stat=ier)
1923    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soil_wet_ns','','')
1924
1925    ALLOCATE (soil_wet_litter(kjpindex,nstm),stat=ier)
1926    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soil_wet_litter','','')
1927
1928    ALLOCATE (qflux(kjpindex,nslm,nstm),stat=ier) 
1929    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable qflux','','')
1930
1931    ALLOCATE (tmat(kjpindex,nslm,3),stat=ier)
1932    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmat','','')
1933
1934    ALLOCATE (stmat(kjpindex,nslm,3),stat=ier)
1935    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable stmat','','')
1936
1937    ALLOCATE (nroot(kjpindex,nvm, nslm),stat=ier)
1938    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nroot','','')
1939
1940    ALLOCATE (kfact_root(kjpindex, nslm, nstm), stat=ier)
1941    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kfact_root','','')
1942
1943    ALLOCATE (kfact(nslm, nscm),stat=ier)
1944    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kfact','','')
1945
1946    ALLOCATE (zz(nslm),stat=ier)
1947    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zz','','')
1948
1949    ALLOCATE (dz(nslm),stat=ier)
1950    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dz','','')
1951   
1952    ALLOCATE (dh(nslm),stat=ier)
1953    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dh','','')
1954
1955    ALLOCATE (mc_lin(imin:imax, nscm),stat=ier)
1956    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_lin','','')
1957
1958    ALLOCATE (k_lin(imin:imax, nslm, nscm),stat=ier)
1959    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable k_lin','','')
1960
1961    ALLOCATE (d_lin(imin:imax, nslm, nscm),stat=ier)
1962    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable d_lin','','')
1963
1964    ALLOCATE (a_lin(imin:imax, nslm, nscm),stat=ier)
1965    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable a_lin','','')
1966
1967    ALLOCATE (b_lin(imin:imax, nslm, nscm),stat=ier)
1968    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable b_lin','','')
1969
1970    ALLOCATE (undermcr(kjpindex),stat=ier)
1971    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable undermcr','','')
1972
1973    ALLOCATE (tot_watveg_beg(kjpindex),stat=ier)
1974    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watveg_beg','','')
1975   
1976    ALLOCATE (tot_watveg_end(kjpindex),stat=ier)
1977    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watvag_end','','')
1978   
1979    ALLOCATE (tot_watsoil_beg(kjpindex),stat=ier)
1980    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watsoil_beg','','')
1981   
1982    ALLOCATE (tot_watsoil_end(kjpindex),stat=ier)
1983    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watsoil_end','','')
1984   
1985    ALLOCATE (delsoilmoist(kjpindex),stat=ier)
1986    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delsoilmoist','','')
1987   
1988    ALLOCATE (delintercept(kjpindex),stat=ier)
1989    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delintercept','','')
1990   
1991    ALLOCATE (delswe(kjpindex),stat=ier)
1992    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delswe','','')
1993   
1994    ALLOCATE (snow_beg(kjpindex),stat=ier)
1995    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snow_beg','','')
1996   
1997    ALLOCATE (snow_end(kjpindex),stat=ier)
1998    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snow_end','','')
1999   
2000    !! 4 Open restart input file and read data for HYDROLOGIC process
2001       IF (printlev>=3) WRITE (numout,*) ' we have to read a restart file for HYDROLOGIC variables'
2002
2003       IF (is_root_prc) CALL ioconf_setatt_p('UNITS', '-')
2004       !
2005       DO jst=1,nstm
2006          ! var_name= "mc_1" ... "mc_3"
2007           WRITE (var_name,"('moistc_',I1)") jst
2008           IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME',var_name)
2009           CALL restget_p (rest_id, var_name, nbp_glo, nslm , 1, kjit, .TRUE., mc(:,:,jst), "gather", nbp_glo, index_g)
2010       END DO
2011
2012       IF (ok_nudge_mc) THEN
2013          DO jst=1,nstm
2014             WRITE (var_name,"('mc_read_next_',I1)") jst
2015             IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME','Soil moisture read from nudging file')
2016             CALL restget_p (rest_id, var_name, nbp_glo, nslm , 1, kjit, .TRUE., mc_read_next(:,:,jst), &
2017                  "gather", nbp_glo, index_g)
2018          END DO
2019       END IF
2020
2021       IF (ok_nudge_snow) THEN
2022          IF (is_root_prc) THEN
2023             CALL ioconf_setatt_p('UNITS', 'm')
2024             CALL ioconf_setatt_p('LONG_NAME','Snow layer thickness read from nudging file')
2025          ENDIF
2026          CALL restget_p (rest_id, 'snowdz_read_next', nbp_glo, nsnow, 1, kjit, .TRUE., snowdz_read_next, &
2027               "gather", nbp_glo, index_g)
2028
2029          IF (is_root_prc) THEN
2030             CALL ioconf_setatt_p('UNITS', 'kg/m^3')
2031             CALL ioconf_setatt_p('LONG_NAME','Snow density profile read from nudging file')
2032          ENDIF
2033          CALL restget_p (rest_id, 'snowrho_read_next', nbp_glo, nsnow, 1, kjit, .TRUE., snowrho_read_next, &
2034               "gather", nbp_glo, index_g)
2035
2036          IF (is_root_prc) THEN
2037             CALL ioconf_setatt_p('UNITS', 'K')
2038             CALL ioconf_setatt_p('LONG_NAME','Snow temperature read from nudging file')
2039          ENDIF
2040          CALL restget_p (rest_id, 'snowtemp_read_next', nbp_glo, nsnow, 1, kjit, .TRUE., snowtemp_read_next, &
2041               "gather", nbp_glo, index_g)
2042       END IF
2043     
2044       DO jst=1,nstm
2045          ! var_name= "mcl_1" ... "mcl_3"
2046           WRITE (var_name,"('moistcl_',I1)") jst
2047           IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME',var_name)
2048           CALL restget_p (rest_id, var_name, nbp_glo, nslm , 1, kjit, .TRUE., mcl(:,:,jst), "gather", nbp_glo, index_g)
2049       END DO
2050
2051       IF (is_root_prc) CALL ioconf_setatt_p('UNITS', '-')
2052       DO jst=1,nstm
2053          DO jsl=1,nslm
2054             ! var_name= "us_1_01" ... "us_3_11"
2055             WRITE (var_name,"('us_',i1,'_',i2.2)") jst,jsl
2056             IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME',var_name)
2057             CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., us(:,:,jst,jsl), "gather", nbp_glo, index_g)
2058          END DO
2059       END DO
2060       !
2061       var_name= 'free_drain_coef'
2062       IF (is_root_prc) THEN
2063          CALL ioconf_setatt_p('UNITS', '-')
2064          CALL ioconf_setatt_p('LONG_NAME','Coefficient for free drainage at bottom of soil')
2065       ENDIF
2066       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., free_drain_coef, "gather", nbp_glo, index_g)
2067       !
2068       var_name= 'zwt_force'
2069       IF (is_root_prc) THEN
2070          CALL ioconf_setatt_p('UNITS', 'm')
2071          CALL ioconf_setatt_p('LONG_NAME','Prescribed water table depth')
2072       ENDIF
2073       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., zwt_force, "gather", nbp_glo, index_g)
2074       !
2075       var_name= 'water2infilt'
2076       IF (is_root_prc) THEN
2077          CALL ioconf_setatt_p('UNITS', '-')
2078          CALL ioconf_setatt_p('LONG_NAME','Remaining water to be infiltrated on top of the soil')
2079       ENDIF
2080       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., water2infilt, "gather", nbp_glo, index_g)
2081       !
2082       var_name= 'ae_ns'
2083       IF (is_root_prc) THEN
2084          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2085          CALL ioconf_setatt_p('LONG_NAME','Bare soil evap on each soil type')
2086       ENDIF
2087       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., ae_ns, "gather", nbp_glo, index_g)
2088       !
2089       var_name= 'snow'       
2090       IF (is_root_prc) THEN
2091          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2092          CALL ioconf_setatt_p('LONG_NAME','Snow mass')
2093       ENDIF
2094       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., snow, "gather", nbp_glo, index_g)
2095       !
2096       var_name= 'snow_age'
2097       IF (is_root_prc) THEN
2098          CALL ioconf_setatt_p('UNITS', 'd')
2099          CALL ioconf_setatt_p('LONG_NAME','Snow age')
2100       ENDIF
2101       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., snow_age, "gather", nbp_glo, index_g)
2102       !
2103       var_name= 'snow_nobio'
2104       IF (is_root_prc) THEN
2105          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2106          CALL ioconf_setatt_p('LONG_NAME','Snow on other surface types')
2107       ENDIF
2108       CALL restget_p (rest_id, var_name, nbp_glo, nnobio  , 1, kjit, .TRUE., snow_nobio, "gather", nbp_glo, index_g)
2109       !
2110       var_name= 'snow_nobio_age'
2111       IF (is_root_prc) THEN
2112          CALL ioconf_setatt_p('UNITS', 'd')
2113          CALL ioconf_setatt_p('LONG_NAME','Snow age on other surface types')
2114       ENDIF
2115       CALL restget_p (rest_id, var_name, nbp_glo, nnobio  , 1, kjit, .TRUE., snow_nobio_age, "gather", nbp_glo, index_g)
2116       !
2117       var_name= 'qsintveg'
2118       IF (is_root_prc) THEN
2119          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2120          CALL ioconf_setatt_p('LONG_NAME','Intercepted moisture')
2121       ENDIF
2122       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., qsintveg, "gather", nbp_glo, index_g)
2123
2124       var_name= 'evap_bare_lim_ns'
2125       IF (is_root_prc) THEN
2126          CALL ioconf_setatt_p('UNITS', '?')
2127          CALL ioconf_setatt_p('LONG_NAME','?')
2128       ENDIF
2129       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., evap_bare_lim_ns, "gather", nbp_glo, index_g)
2130       CALL setvar_p (evap_bare_lim_ns, val_exp, 'NO_KEYWORD', 0.0)
2131
2132       var_name= 'resdist'
2133       IF (is_root_prc) THEN
2134          CALL ioconf_setatt_p('UNITS', '-')
2135          CALL ioconf_setatt_p('LONG_NAME','soiltile values from previous time-step')
2136       ENDIF
2137       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., resdist, "gather", nbp_glo, index_g)
2138
2139       var_name= 'vegtot_old'
2140       IF (is_root_prc) THEN
2141          CALL ioconf_setatt_p('UNITS', '-')
2142          CALL ioconf_setatt_p('LONG_NAME','vegtot from previous time-step')
2143       ENDIF
2144       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., vegtot_old, "gather", nbp_glo, index_g)       
2145       
2146       ! Read drysoil_frac. It will be initalized later in hydrol_var_init if the varaible is not find in restart file.
2147       IF (is_root_prc) THEN
2148          CALL ioconf_setatt_p('UNITS', '')
2149          CALL ioconf_setatt_p('LONG_NAME','Function of litter wetness')
2150       ENDIF
2151       CALL restget_p (rest_id, 'drysoil_frac', nbp_glo, 1  , 1, kjit, .TRUE., drysoil_frac, "gather", nbp_glo, index_g)
2152
2153
2154    !! 5 get restart values if none were found in the restart file
2155       !
2156       !Config Key   = HYDROL_MOISTURE_CONTENT
2157       !Config Desc  = Soil moisture on each soil tile and levels
2158       !Config If    = HYDROL_CWRR       
2159       !Config Def   = 0.3
2160       !Config Help  = The initial value of mc if its value is not found
2161       !Config         in the restart file. This should only be used if the model is
2162       !Config         started without a restart file.
2163       !Config Units = [m3/m3]
2164       !
2165       CALL setvar_p (mc, val_exp, 'HYDROL_MOISTURE_CONTENT', 0.3_r_std)
2166
2167       ! Initialize mcl as mc if it is not found in the restart file
2168       IF ( ALL(mcl(:,:,:)==val_exp) ) THEN
2169          mcl(:,:,:) = mc(:,:,:)
2170       END IF
2171
2172
2173       
2174       !Config Key   = US_INIT
2175       !Config Desc  = US_NVM_NSTM_NSLM
2176       !Config If    = HYDROL_CWRR       
2177       !Config Def   = 0.0
2178       !Config Help  = The initial value of us (relative moisture) if its value is not found
2179       !Config         in the restart file. This should only be used if the model is
2180       !Config         started without a restart file.
2181       !Config Units = [-]
2182       !
2183       DO jsl=1,nslm
2184          CALL setvar_p (us(:,:,:,jsl), val_exp, 'US_INIT', zero)
2185       ENDDO
2186       !
2187       !Config Key   = ZWT_FORCE
2188       !Config Desc  = Prescribed water depth, dimension nstm
2189       !Config If    = HYDROL_CWRR       
2190       !Config Def   = undef undef undef
2191       !Config Help  = The initial value of zwt_force if its value is not found
2192       !Config         in the restart file. undef corresponds to a case whith no forced WT.
2193       !Config         This should only be used if the model is started without a restart file.
2194       !Config Units = [m]
2195       
2196       ALLOCATE (zwt_default(nstm),stat=ier)
2197       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zwt_default','','')
2198       zwt_default(:) = undef_sechiba
2199       CALL setvar_p (zwt_force, val_exp, 'ZWT_FORCE', zwt_default )
2200
2201       zforce = .FALSE.
2202       DO jst=1,nstm
2203          IF (zwt_force(1,jst) <= zmaxh) zforce = .TRUE. ! AD16*** check if OK with vertical_soil
2204       ENDDO
2205       !
2206       !Config Key   = FREE_DRAIN_COEF
2207       !Config Desc  = Coefficient for free drainage at bottom, dimension nstm
2208       !Config If    = HYDROL_CWRR       
2209       !Config Def   = 1.0 1.0 1.0
2210       !Config Help  = The initial value of free drainage coefficient if its value is not found
2211       !Config         in the restart file. This should only be used if the model is
2212       !Config         started without a restart file.
2213       !Config Units = [-]
2214             
2215       ALLOCATE (free_drain_max(nstm),stat=ier)
2216       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable free_drain_max','','')
2217       free_drain_max(:)=1.0
2218
2219       CALL setvar_p (free_drain_coef, val_exp, 'FREE_DRAIN_COEF', free_drain_max)
2220       IF (printlev>=2) WRITE (numout,*) ' hydrol_init => free_drain_coef = ',free_drain_coef(1,:)
2221       DEALLOCATE(free_drain_max)
2222
2223       !
2224       !Config Key   = WATER_TO_INFILT
2225       !Config Desc  = Water to be infiltrated on top of the soil
2226       !Config If    = HYDROL_CWRR   
2227       !Config Def   = 0.0
2228       !Config Help  = The initial value of free drainage if its value is not found
2229       !Config         in the restart file. This should only be used if the model is
2230       !Config         started without a restart file.
2231       !Config Units = [mm]
2232       !
2233       CALL setvar_p (water2infilt, val_exp, 'WATER_TO_INFILT', zero)
2234       !
2235       !Config Key   = EVAPNU_SOIL
2236       !Config Desc  = Bare soil evap on each soil if not found in restart
2237       !Config If    = HYDROL_CWRR 
2238       !Config Def   = 0.0
2239       !Config Help  = The initial value of bare soils evap if its value is not found
2240       !Config         in the restart file. This should only be used if the model is
2241       !Config         started without a restart file.
2242       !Config Units = [mm]
2243       !
2244       CALL setvar_p (ae_ns, val_exp, 'EVAPNU_SOIL', zero)
2245       !
2246       !Config Key  = HYDROL_SNOW
2247       !Config Desc  = Initial snow mass if not found in restart
2248       !Config If    = OK_SECHIBA
2249       !Config Def   = 0.0
2250       !Config Help  = The initial value of snow mass if its value is not found
2251       !Config         in the restart file. This should only be used if the model is
2252       !Config         started without a restart file.
2253       !Config Units =
2254       !
2255       CALL setvar_p (snow, val_exp, 'HYDROL_SNOW', zero)
2256       !
2257       !Config Key   = HYDROL_SNOWAGE
2258       !Config Desc  = Initial snow age if not found in restart
2259       !Config If    = OK_SECHIBA
2260       !Config Def   = 0.0
2261       !Config Help  = The initial value of snow age if its value is not found
2262       !Config         in the restart file. This should only be used if the model is
2263       !Config         started without a restart file.
2264       !Config Units = ***
2265       !
2266       CALL setvar_p (snow_age, val_exp, 'HYDROL_SNOWAGE', zero)
2267       !
2268       !Config Key   = HYDROL_SNOW_NOBIO
2269       !Config Desc  = Initial snow amount on ice, lakes, etc. if not found in restart
2270       !Config If    = OK_SECHIBA
2271       !Config Def   = 0.0
2272       !Config Help  = The initial value of snow if its value is not found
2273       !Config         in the restart file. This should only be used if the model is
2274       !Config         started without a restart file.
2275       !Config Units = [mm]
2276       !
2277       CALL setvar_p (snow_nobio, val_exp, 'HYDROL_SNOW_NOBIO', zero)
2278       !
2279       !Config Key   = HYDROL_SNOW_NOBIO_AGE
2280       !Config Desc  = Initial snow age on ice, lakes, etc. if not found in restart
2281       !Config If    = OK_SECHIBA
2282       !Config Def   = 0.0
2283       !Config Help  = The initial value of snow age if its value is not found
2284       !Config         in the restart file. This should only be used if the model is
2285       !Config         started without a restart file.
2286       !Config Units = ***
2287       !
2288       CALL setvar_p (snow_nobio_age, val_exp, 'HYDROL_SNOW_NOBIO_AGE', zero)
2289       !
2290       !Config Key   = HYDROL_QSV
2291       !Config Desc  = Initial water on canopy if not found in restart
2292       !Config If    = OK_SECHIBA
2293       !Config Def   = 0.0
2294       !Config Help  = The initial value of moisture on canopy if its value
2295       !Config         is not found in the restart file. This should only be used if
2296       !Config         the model is started without a restart file.
2297       !Config Units = [mm]
2298       !
2299       CALL setvar_p (qsintveg, val_exp, 'HYDROL_QSV', zero)
2300
2301    !! 6 Vegetation array     
2302       !
2303       ! If resdist is not in restart file, initialize with soiltile
2304       IF ( MINVAL(resdist) .EQ.  MAXVAL(resdist) .AND. MINVAL(resdist) .EQ. val_exp) THEN
2305          resdist(:,:) = soiltile(:,:)
2306       ENDIF
2307       
2308       !
2309       !  Remember that it is only frac_nobio + SUM(veget_max(,:)) that is equal to 1. Thus we need vegtot
2310       !
2311       IF ( ALL(vegtot_old(:) == val_exp) ) THEN
2312          ! vegtot_old was not found in restart file
2313          DO ji = 1, kjpindex
2314             vegtot_old(ji) = SUM(veget_max(ji,:))
2315          ENDDO
2316       ENDIF
2317       
2318       ! In the initialization phase, vegtot must take the value from previous time-step.
2319       ! This is because hydrol_main is done before veget_max is updated in the end of the time step.
2320       vegtot(:) = vegtot_old(:)
2321       
2322       !
2323       !
2324       ! compute the masks for veget
2325
2326       mask_veget(:,:) = 0
2327       mask_soiltile(:,:) = 0
2328
2329       DO jst=1,nstm
2330          DO ji = 1, kjpindex
2331             IF(soiltile(ji,jst) .GT. min_sechiba) THEN
2332                mask_soiltile(ji,jst) = 1
2333             ENDIF
2334          END DO
2335       ENDDO
2336         
2337       DO jv = 1, nvm
2338          DO ji = 1, kjpindex
2339             IF(veget_max(ji,jv) .GT. min_sechiba) THEN
2340                mask_veget(ji,jv) = 1
2341             ENDIF
2342          END DO
2343       END DO
2344
2345       humrelv(:,:,:) = SUM(us,dim=4)
2346
2347         
2348       !! 7a. Set vegstress
2349     
2350       var_name= 'vegstress'
2351       IF (is_root_prc) THEN
2352          CALL ioconf_setatt_p('UNITS', '-')
2353          CALL ioconf_setatt_p('LONG_NAME','Vegetation growth moisture stress')
2354       ENDIF
2355       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., vegstress, "gather", nbp_glo, index_g)
2356
2357       vegstressv(:,:,:) = humrelv(:,:,:)
2358       ! Calculate vegstress if it is not found in restart file
2359       IF (ALL(vegstress(:,:)==val_exp)) THEN
2360          DO jv=1,nvm
2361             DO ji=1,kjpindex
2362                vegstress(ji,jv)=vegstress(ji,jv) + vegstressv(ji,jv,pref_soil_veg(jv))
2363             END DO
2364          END DO
2365       END IF
2366       !! 7b. Set humrel   
2367       ! Read humrel from restart file
2368       var_name= 'humrel'
2369       IF (is_root_prc) THEN
2370          CALL ioconf_setatt_p('UNITS', '')
2371          CALL ioconf_setatt_p('LONG_NAME','Relative humidity')
2372       ENDIF
2373       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., humrel, "gather", nbp_glo, index_g)
2374
2375       ! Calculate humrel if it is not found in restart file
2376       IF (ALL(humrel(:,:)==val_exp)) THEN
2377          ! set humrel from humrelv, assuming equi-repartition for the first time step
2378          humrel(:,:) = zero
2379          DO jv=1,nvm
2380             DO ji=1,kjpindex
2381                humrel(ji,jv)=humrel(ji,jv) + humrelv(ji,jv,pref_soil_veg(jv))     
2382             END DO
2383          END DO
2384       END IF
2385
2386       ! Read evap_bare_lim from restart file
2387       var_name= 'evap_bare_lim'
2388       IF (is_root_prc) THEN
2389          CALL ioconf_setatt_p('UNITS', '')
2390          CALL ioconf_setatt_p('LONG_NAME','Limitation factor for bare soil evaporation')
2391       ENDIF
2392       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., evap_bare_lim, "gather", nbp_glo, index_g)
2393
2394       ! Calculate evap_bare_lim if it was not found in the restart file.
2395       IF ( ALL(evap_bare_lim(:) == val_exp) ) THEN
2396          DO ji = 1, kjpindex
2397             evap_bare_lim(ji) =  SUM(evap_bare_lim_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
2398          ENDDO
2399       END IF
2400
2401
2402    ! Read from restart file       
2403    ! The variables tot_watsoil_beg, tot_watsoil_beg and snwo_beg will be initialized in the end of
2404    ! hydrol_initialize if they were not found in the restart file.
2405       
2406    var_name= 'tot_watveg_beg'
2407    IF (is_root_prc) THEN
2408       CALL ioconf_setatt_p('UNITS', '?')
2409       CALL ioconf_setatt_p('LONG_NAME','?')
2410    ENDIF
2411    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., tot_watveg_beg, "gather", nbp_glo, index_g)
2412   
2413    var_name= 'tot_watsoil_beg'
2414    IF (is_root_prc) THEN
2415       CALL ioconf_setatt_p('UNITS', '?')
2416       CALL ioconf_setatt_p('LONG_NAME','?')
2417    ENDIF
2418    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., tot_watsoil_beg, "gather", nbp_glo, index_g)
2419   
2420    var_name= 'snow_beg'
2421    IF (is_root_prc) THEN
2422       CALL ioconf_setatt_p('UNITS', '?')
2423       CALL ioconf_setatt_p('LONG_NAME','?')
2424    ENDIF
2425    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., snow_beg, "gather", nbp_glo, index_g)
2426       
2427 
2428    ! Initialize variables for explictsnow module by reading restart file
2429    IF (ok_explicitsnow) THEN
2430       CALL explicitsnow_initialize( kjit,     kjpindex, rest_id,    snowrho,   &
2431                                     snowtemp, snowdz,   snowheat,   snowgrain)
2432    END IF
2433
2434
2435    ! Initialize soil moisture for nudging if not found in restart file
2436    IF (ok_nudge_mc) THEN
2437       IF ( ALL(mc_read_next(:,:,:)==val_exp) ) mc_read_next(:,:,:) = mc(:,:,:)
2438    END IF
2439   
2440    ! Initialize snow variables for nudging if not found in restart file
2441    IF (ok_nudge_snow) THEN
2442       IF ( ALL(snowdz_read_next(:,:)==val_exp) ) snowdz_read_next(:,:) = snowdz(:,:)
2443       IF ( ALL(snowrho_read_next(:,:)==val_exp) ) snowrho_read_next(:,:) = snowrho(:,:)
2444       IF ( ALL(snowtemp_read_next(:,:)==val_exp) ) snowtemp_read_next(:,:) = snowtemp(:,:)
2445    END IF
2446   
2447   
2448    IF (printlev>=3) WRITE (numout,*) ' hydrol_init done '
2449   
2450  END SUBROUTINE hydrol_init
2451
2452
2453!! ================================================================================================================================
2454!! SUBROUTINE   : hydrol_clear
2455!!
2456!>\BRIEF        Deallocate arrays
2457!!
2458!_ ================================================================================================================================
2459!_ hydrol_clear
2460
2461  SUBROUTINE hydrol_clear()
2462
2463    ! Allocation for soiltile related parameters
2464    IF ( ALLOCATED (nvan)) DEALLOCATE (nvan)
2465    IF ( ALLOCATED (avan)) DEALLOCATE (avan)
2466    IF ( ALLOCATED (mcr)) DEALLOCATE (mcr)
2467    IF ( ALLOCATED (mcs)) DEALLOCATE (mcs)
2468    IF ( ALLOCATED (ks)) DEALLOCATE (ks)
2469    IF ( ALLOCATED (pcent)) DEALLOCATE (pcent)
2470    IF ( ALLOCATED (mcfc)) DEALLOCATE (mcfc)
2471    IF ( ALLOCATED (mcw)) DEALLOCATE (mcw)
2472    IF ( ALLOCATED (mc_awet)) DEALLOCATE (mc_awet)
2473    IF ( ALLOCATED (mc_adry)) DEALLOCATE (mc_adry)
2474    ! Other arrays
2475    IF (ALLOCATED (mask_veget)) DEALLOCATE (mask_veget)
2476    IF (ALLOCATED (mask_soiltile)) DEALLOCATE (mask_soiltile)
2477    IF (ALLOCATED (humrelv)) DEALLOCATE (humrelv)
2478    IF (ALLOCATED (vegstressv)) DEALLOCATE (vegstressv)
2479    IF (ALLOCATED (us)) DEALLOCATE (us)
2480    IF (ALLOCATED  (precisol)) DEALLOCATE (precisol)
2481    IF (ALLOCATED  (throughfall)) DEALLOCATE (throughfall)
2482    IF (ALLOCATED  (precisol_ns)) DEALLOCATE (precisol_ns)
2483    IF (ALLOCATED  (free_drain_coef)) DEALLOCATE (free_drain_coef)
2484    IF (ALLOCATED  (frac_bare_ns)) DEALLOCATE (frac_bare_ns)
2485    IF (ALLOCATED  (water2infilt)) DEALLOCATE (water2infilt)
2486    IF (ALLOCATED  (ae_ns)) DEALLOCATE (ae_ns)
2487    IF (ALLOCATED  (evap_bare_lim_ns)) DEALLOCATE (evap_bare_lim_ns)
2488    IF (ALLOCATED  (rootsink)) DEALLOCATE (rootsink)
2489    IF (ALLOCATED  (subsnowveg)) DEALLOCATE (subsnowveg)
2490    IF (ALLOCATED  (subsnownobio)) DEALLOCATE (subsnownobio)
2491    IF (ALLOCATED  (icemelt)) DEALLOCATE (icemelt)
2492    IF (ALLOCATED  (subsinksoil)) DEALLOCATE (subsinksoil)
2493    IF (ALLOCATED  (mx_eau_var)) DEALLOCATE (mx_eau_var)
2494    IF (ALLOCATED  (vegtot)) DEALLOCATE (vegtot)
2495    IF (ALLOCATED  (vegtot_old)) DEALLOCATE (vegtot_old)
2496    IF (ALLOCATED  (resdist)) DEALLOCATE (resdist)
2497    IF (ALLOCATED  (tot_watveg_beg)) DEALLOCATE (tot_watveg_beg)
2498    IF (ALLOCATED  (tot_watveg_end)) DEALLOCATE (tot_watveg_end)
2499    IF (ALLOCATED  (tot_watsoil_beg)) DEALLOCATE (tot_watsoil_beg)
2500    IF (ALLOCATED  (tot_watsoil_end)) DEALLOCATE (tot_watsoil_end)
2501    IF (ALLOCATED  (delsoilmoist)) DEALLOCATE (delsoilmoist)
2502    IF (ALLOCATED  (delintercept)) DEALLOCATE (delintercept)
2503    IF (ALLOCATED  (snow_beg)) DEALLOCATE (snow_beg)
2504    IF (ALLOCATED  (snow_end)) DEALLOCATE (snow_end)
2505    IF (ALLOCATED  (delswe)) DEALLOCATE (delswe)
2506    IF (ALLOCATED  (undermcr)) DEALLOCATE (undermcr)
2507    IF (ALLOCATED  (v1)) DEALLOCATE (v1)
2508    IF (ALLOCATED  (humtot)) DEALLOCATE (humtot)
2509    IF (ALLOCATED  (resolv)) DEALLOCATE (resolv)
2510    IF (ALLOCATED  (k)) DEALLOCATE (k)
2511    IF (ALLOCATED  (kk)) DEALLOCATE (kk)
2512    IF (ALLOCATED  (kk_moy)) DEALLOCATE (kk_moy)
2513    IF (ALLOCATED  (avan_mod_tab)) DEALLOCATE (avan_mod_tab)
2514    IF (ALLOCATED  (nvan_mod_tab)) DEALLOCATE (nvan_mod_tab)
2515    IF (ALLOCATED  (a)) DEALLOCATE (a)
2516    IF (ALLOCATED  (b)) DEALLOCATE (b)
2517    IF (ALLOCATED  (d)) DEALLOCATE (d)
2518    IF (ALLOCATED  (e)) DEALLOCATE (e)
2519    IF (ALLOCATED  (f)) DEALLOCATE (f)
2520    IF (ALLOCATED  (g1)) DEALLOCATE (g1)
2521    IF (ALLOCATED  (ep)) DEALLOCATE (ep)
2522    IF (ALLOCATED  (fp)) DEALLOCATE (fp)
2523    IF (ALLOCATED  (gp)) DEALLOCATE (gp)
2524    IF (ALLOCATED  (rhs)) DEALLOCATE (rhs)
2525    IF (ALLOCATED  (srhs)) DEALLOCATE (srhs)
2526    IF (ALLOCATED  (tmc)) DEALLOCATE (tmc)
2527    IF (ALLOCATED  (tmcs)) DEALLOCATE (tmcs)
2528    IF (ALLOCATED  (tmcr)) DEALLOCATE (tmcr)
2529    IF (ALLOCATED  (tmcfc)) DEALLOCATE (tmcfc)
2530    IF (ALLOCATED  (tmcw)) DEALLOCATE (tmcw)
2531    IF (ALLOCATED  (tmc_litter)) DEALLOCATE (tmc_litter)
2532    IF (ALLOCATED  (tmc_litt_mea)) DEALLOCATE (tmc_litt_mea)
2533    IF (ALLOCATED  (tmc_litter_res)) DEALLOCATE (tmc_litter_res)
2534    IF (ALLOCATED  (tmc_litter_wilt)) DEALLOCATE (tmc_litter_wilt)
2535    IF (ALLOCATED  (tmc_litter_field)) DEALLOCATE (tmc_litter_field)
2536    IF (ALLOCATED  (tmc_litter_sat)) DEALLOCATE (tmc_litter_sat)
2537    IF (ALLOCATED  (tmc_litter_awet)) DEALLOCATE (tmc_litter_awet)
2538    IF (ALLOCATED  (tmc_litter_adry)) DEALLOCATE (tmc_litter_adry)
2539    IF (ALLOCATED  (tmc_litt_wet_mea)) DEALLOCATE (tmc_litt_wet_mea)
2540    IF (ALLOCATED  (tmc_litt_dry_mea)) DEALLOCATE (tmc_litt_dry_mea)
2541    IF (ALLOCATED  (ru_ns)) DEALLOCATE (ru_ns)
2542    IF (ALLOCATED  (dr_ns)) DEALLOCATE (dr_ns)
2543    IF (ALLOCATED  (tr_ns)) DEALLOCATE (tr_ns)
2544    IF (ALLOCATED  (vegetmax_soil)) DEALLOCATE (vegetmax_soil)
2545    IF (ALLOCATED  (mc)) DEALLOCATE (mc)
2546    IF (ALLOCATED  (soilmoist)) DEALLOCATE (soilmoist)
2547    IF (ALLOCATED  (soilmoist_liquid)) DEALLOCATE (soilmoist_liquid)
2548    IF (ALLOCATED  (soil_wet_ns)) DEALLOCATE (soil_wet_ns)
2549    IF (ALLOCATED  (soil_wet_litter)) DEALLOCATE (soil_wet_litter)
2550    IF (ALLOCATED  (qflux)) DEALLOCATE (qflux)
2551    IF (ALLOCATED  (tmat)) DEALLOCATE (tmat)
2552    IF (ALLOCATED  (stmat)) DEALLOCATE (stmat)
2553    IF (ALLOCATED  (nroot)) DEALLOCATE (nroot)
2554    IF (ALLOCATED  (kfact_root)) DEALLOCATE (kfact_root)
2555    IF (ALLOCATED  (kfact)) DEALLOCATE (kfact)
2556    IF (ALLOCATED  (zz)) DEALLOCATE (zz)
2557    IF (ALLOCATED  (dz)) DEALLOCATE (dz)
2558    IF (ALLOCATED  (dh)) DEALLOCATE (dh)
2559    IF (ALLOCATED  (mc_lin)) DEALLOCATE (mc_lin)
2560    IF (ALLOCATED  (k_lin)) DEALLOCATE (k_lin)
2561    IF (ALLOCATED  (d_lin)) DEALLOCATE (d_lin)
2562    IF (ALLOCATED  (a_lin)) DEALLOCATE (a_lin)
2563    IF (ALLOCATED  (b_lin)) DEALLOCATE (b_lin)
2564
2565  END SUBROUTINE hydrol_clear
2566
2567!! ================================================================================================================================
2568!! SUBROUTINE   : hydrol_tmc_update
2569!!
2570!>\BRIEF        This routine updates the soil moisture profiles when the vegetation fraction have changed.
2571!!
2572!! DESCRIPTION  :
2573!!
2574!!    This routine update tmc and mc with variation of veget_max (LAND_USE or DGVM activated)
2575!!
2576!!
2577!!
2578!!
2579!! RECENT CHANGE(S) : Adaptation to excluding nobio from soiltile(1)
2580!!
2581!! MAIN OUTPUT VARIABLE(S) :
2582!!
2583!! REFERENCE(S) :
2584!!
2585!! FLOWCHART    : None
2586!! \n
2587!_ ================================================================================================================================
2588!_ hydrol_tmc_update
2589  SUBROUTINE hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg, drain_upd, runoff_upd)
2590
2591    !! 0.1 Input variables
2592    INTEGER(i_std), INTENT(in)                            :: kjpindex      !! domain size
2593    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)     :: veget_max     !! max fraction of vegetation type
2594    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)   :: soiltile      !! Fraction of each soil tile (0-1, unitless)
2595
2596    !! 0.2 Output variables
2597    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: drain_upd        !! Change in drainage due to decrease in vegtot
2598                                                                              !! on mc [kg/m2/dt]
2599    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: runoff_upd       !! Change in runoff due to decrease in vegtot
2600                                                                              !! on water2infilt[kg/m2/dt]
2601   
2602    !! 0.3 Modified variables
2603    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg   !! Amount of water in the canopy interception
2604
2605    !! 0.4 Local variables
2606    INTEGER(i_std)                           :: ji, jv, jst,jsl
2607    LOGICAL                                  :: soil_upd        !! True if soiltile changed since last time step
2608    LOGICAL                                  :: vegtot_upd      !! True if vegtot changed since last time step
2609    LOGICAL                                  :: error=.FALSE.   !! If true, exit in the end of subroutine
2610    REAL(r_std), DIMENSION(kjpindex,nstm)    :: vmr             !! Change in soiltile (within vegtot)
2611    REAL(r_std), DIMENSION(kjpindex)         :: vmr_sum
2612    REAL(r_std), DIMENSION(kjpindex)         :: delvegtot   
2613    REAL(r_std), DIMENSION(kjpindex,nslm)    :: mc_dilu         !! Total loss of moisture content
2614    REAL(r_std), DIMENSION(kjpindex)         :: infil_dilu      !! Total loss for water2infilt
2615    REAL(r_std), DIMENSION(kjpindex,nstm)    :: tmc_old         !! tmc before calculations
2616    REAL(r_std), DIMENSION(kjpindex,nstm)    :: water2infilt_old!! water2infilt before calculations
2617    REAL(r_std), DIMENSION (kjpindex,nvm)    :: qsintveg_old    !! qsintveg before calculations
2618    REAL(r_std), DIMENSION(kjpindex)         :: test
2619    REAL(r_std), DIMENSION(kjpindex,nslm,nstm) :: mcaux        !! serves to hold the chnage in mc when vegtot decreases
2620
2621    !! 0. For checks
2622
2623    IF (check_cwrr) THEN
2624       ! Save soil moisture for later use
2625       tmc_old(:,:) = tmc(:,:) 
2626       water2infilt_old(:,:) = water2infilt(:,:)
2627       qsintveg_old(:,:) = qsintveg(:,:)
2628    ENDIF
2629   
2630    !! 1. If a PFT has disapperead as result from a veget_max change,
2631    !!    then add canopy water to surface water.
2632    !     Other adaptations of qsintveg are delt by the normal functioning of hydrol_canop
2633
2634    DO ji=1,kjpindex
2635       IF (vegtot_old(ji) .GT.min_sechiba) THEN
2636          DO jv=1,nvm
2637             IF ((veget_max(ji,jv).LT.min_sechiba).AND.(qsintveg(ji,jv).GT.0.)) THEN
2638                jst=pref_soil_veg(jv) ! soil tile index
2639                water2infilt(ji,jst) = water2infilt(ji,jst) + qsintveg(ji,jv)/(resdist(ji,jst)*vegtot_old(ji))
2640                qsintveg(ji,jv) = zero
2641             ENDIF
2642          ENDDO
2643       ENDIF
2644    ENDDO
2645   
2646    !! 2. We now deal with the changes of soiltile and corresponding soil moistures
2647    !!    Because sum(soiltile)=1 whatever vegtot, we need to distinguish two cases:
2648    !!    - when vegtot changes (meaning that the nobio fraction changes too),
2649    !!    - and when vegtot does not changes (a priori the most frequent case)
2650
2651    vegtot_upd = SUM(ABS((vegtot(:)-vegtot_old(:)))) .GT. zero ! True if at least one land point with a vegtot change
2652    runoff_upd(:) = zero
2653    drain_upd(:) = zero
2654    IF (vegtot_upd) THEN
2655       ! We find here the processing specific to the chnages of nobio fraction and vegtot
2656
2657       delvegtot(:) = vegtot(:) - vegtot_old(:)
2658
2659       DO jst=1,nstm
2660          DO ji=1,kjpindex
2661
2662             IF (delvegtot(ji) .GT. min_sechiba) THEN
2663
2664                !! 2.1. If vegtot increases (nobio decreases), then the mc in each soiltile is decreased
2665                !!      assuming the same proportions for each soiltile, and each soil layer
2666               
2667                mc(ji,:,jst) = mc(ji,:,jst) * vegtot_old(ji)/vegtot(ji) ! vegtot cannot be zero as > vegtot_old
2668                water2infilt(ji,jst) = water2infilt(ji,jst) * vegtot_old(ji)/vegtot(ji)
2669
2670             ELSE
2671
2672                !! 2.2 If vegtot decreases (nobio increases), then the mc in each soiltile should increase,
2673                !!     but should not exceed mcs
2674                !!     For simplicity, we choose to send the corresponding water volume to drainage
2675                !!     We do the same for water2infilt but send the excess to surface runoff
2676
2677                IF (vegtot(ji) .GT.min_sechiba) THEN
2678                   mcaux(ji,:,jst) =  mc(ji,:,jst) * (vegtot_old(ji)-vegtot(ji))/vegtot(ji) ! mcaux is the delta mc
2679                ELSE ! we just have nobio in the grid-cell
2680                   mcaux(ji,:,jst) =  mc(ji,:,jst)
2681                ENDIF
2682               
2683                drain_upd(ji) = drain_upd(ji) + dz(2) * ( trois*mcaux(ji,1,jst) + mcaux(ji,2,jst) )/huit
2684                DO jsl = 2,nslm-1
2685                   drain_upd(ji) = drain_upd(ji) + dz(jsl) * (trois*mcaux(ji,jsl,jst)+mcaux(ji,jsl-1,jst))/huit &
2686                        + dz(jsl+1) * (trois*mcaux(ji,jsl,jst)+mcaux(ji,jsl+1,jst))/huit
2687                ENDDO
2688                drain_upd(ji) = drain_upd(ji) + dz(nslm) * (trois*mcaux(ji,nslm,jst) + mcaux(ji,nslm-1,jst))/huit
2689
2690                IF (vegtot(ji) .GT.min_sechiba) THEN
2691                   runoff_upd(ji) = runoff_upd(ji) + water2infilt(ji,jst) * (vegtot_old(ji)-vegtot(ji))/vegtot(ji)
2692                ELSE ! we just have nobio in the grid-cell
2693                   runoff_upd(ji) = runoff_upd(ji) + water2infilt(ji,jst)
2694                ENDIF
2695
2696             ENDIF
2697             
2698          ENDDO
2699       ENDDO
2700       
2701    ENDIF
2702   
2703    !! 3. At the end of step 2, we are back to a case where vegtot changes are treated, so we can use soiltile
2704    !!    as a fraction of vegtot to process the mc transfers between soil tiles due to the changes of vegetation map
2705   
2706    !! 3.1 Check if soiltiles changed since last time step
2707    soil_upd=SUM(ABS(soiltile(:,:)-resdist(:,:))) .GT. zero
2708    IF (printlev>=3) WRITE (numout,*) 'soil_upd ', soil_upd
2709       
2710    IF (soil_upd) THEN
2711     
2712       !! 3.2 Define the change in soiltile
2713       vmr(:,:) = soiltile(:,:) - resdist(:,:)  ! resdist is the previous values of soiltiles, previous timestep, so before new map
2714
2715       ! Total area loss by the three soil tiles
2716       DO ji=1,kjpindex
2717          vmr_sum(ji)=SUM(vmr(ji,:),MASK=vmr(ji,:).LT.zero)
2718       ENDDO
2719
2720       !! 3.3 Shrinking soil tiles
2721       !! 3.3.1 Total loss of moisture content from the shrinking soil tiles, expressed by soil layer
2722       mc_dilu(:,:)=zero
2723       DO jst=1,nstm
2724          DO jsl = 1, nslm
2725             DO ji=1,kjpindex
2726                IF ( vmr(ji,jst) < -min_sechiba ) THEN
2727                   mc_dilu(ji,jsl) = mc_dilu(ji,jsl) + mc(ji,jsl,jst) * vmr(ji,jst) / vmr_sum(ji)
2728                ENDIF
2729             ENDDO
2730          ENDDO
2731       ENDDO
2732
2733       !! 3.3.2 Total loss of water2inft from the shrinking soil tiles
2734       infil_dilu(:)=zero
2735       DO jst=1,nstm
2736          DO ji=1,kjpindex
2737             IF ( vmr(ji,jst) < -min_sechiba ) THEN
2738                infil_dilu(ji) = infil_dilu(ji) + water2infilt(ji,jst) * vmr(ji,jst) / vmr_sum(ji)
2739             ENDIF
2740          ENDDO
2741       ENDDO
2742
2743       !! 3.4 Each gaining soil tile gets moisture proportionally to both the total loss and its areal increase
2744
2745       ! As the original mc from each soil tile are in [mcr,mcs] and we do weighted avrage, the new mc are in [mcr,mcs]
2746       ! The case where the soiltile is created (soiltile_old=0) works as the other cases
2747
2748       ! 3.4.1 Update mc(kjpindex,nslm,nstm) !m3/m3
2749       DO jst=1,nstm
2750          DO jsl = 1, nslm
2751             DO ji=1,kjpindex
2752                IF ( vmr(ji,jst) > min_sechiba ) THEN
2753                   mc(ji,jsl,jst) = ( mc(ji,jsl,jst) * resdist(ji,jst) + mc_dilu(ji,jsl) * vmr(ji,jst) ) / soiltile(ji,jst)
2754                   ! NB : soiltile can not be zero for case vmr > zero, see slowproc_veget
2755                ENDIF
2756             ENDDO
2757          ENDDO
2758       ENDDO
2759       
2760       ! 3.4.2 Update water2inft
2761       DO jst=1,nstm
2762          DO ji=1,kjpindex
2763             IF ( vmr(ji,jst) > min_sechiba ) THEN !donc soiltile>0     
2764                water2infilt(ji,jst) = ( water2infilt(ji,jst) * resdist(ji,jst) + infil_dilu(ji) * vmr(ji,jst) ) / soiltile(ji,jst)
2765             ENDIF !donc resdist>0
2766          ENDDO
2767       ENDDO
2768
2769       ! 3.4.3 Case where soiltile < min_sechiba
2770       DO jst=1,nstm
2771          DO ji=1,kjpindex
2772             IF ( soiltile(ji,jst) .LT. min_sechiba ) THEN
2773                water2infilt(ji,jst) = zero
2774                mc(ji,:,jst) = zero
2775             ENDIF
2776          ENDDO
2777       ENDDO
2778
2779    ENDIF ! soil_upd
2780
2781    !! 4. Update tmc and humtot
2782   
2783    DO jst=1,nstm
2784       DO ji=1,kjpindex
2785             tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
2786             DO jsl = 2,nslm-1
2787                tmc(ji,jst) = tmc(ji,jst) + dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
2788                     + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
2789             ENDDO
2790             tmc(ji,jst) = tmc(ji,jst) + dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
2791             tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
2792             ! WARNING tmc is increased by includes water2infilt(ji,jst)
2793       ENDDO
2794    ENDDO
2795
2796    humtot(:) = zero
2797    DO jst=1,nstm
2798       DO ji=1,kjpindex
2799          humtot(ji) = humtot(ji) + vegtot(ji) * soiltile(ji,jst) * tmc(ji,jst) ! average over grid-cell (i.e. total land)
2800       ENDDO
2801    ENDDO
2802
2803    !! 5. Check
2804    IF (check_cwrr) THEN
2805       DO ji=1,kjpindex
2806          test(ji) = SUM(tmc(ji,:)*soiltile(ji,:)*vegtot(ji)) - SUM(tmc_old(ji,:)*resdist(ji,:)*vegtot_old(ji)) + &
2807               SUM(qsintveg(ji,:)) - SUM(qsintveg_old(ji,:)) + (drain_upd(ji) + runoff_upd(ji))   
2808          IF ( ABS(test(ji)) .GT.  10.*allowed_err ) THEN
2809             WRITE(numout,*) 'tmc update WRONG: ji',ji
2810             WRITE(numout,*) 'tot water avant:',SUM(tmc_old(ji,:)*resdist(ji,:)*vegtot_old(ji)) + SUM(qsintveg_old(ji,:))
2811             WRITE(numout,*) 'tot water apres:',SUM(tmc(ji,:)*soiltile(ji,:)*vegtot(ji)) + SUM(qsintveg(ji,:))
2812             WRITE(numout,*) 'err:',test(ji)
2813             WRITE(numout,*) 'allowed_err:',allowed_err
2814             WRITE(numout,*) 'tmc:',tmc(ji,:)
2815             WRITE(numout,*) 'tmc_old:',tmc_old(ji,:)
2816             WRITE(numout,*) 'qsintveg:',qsintveg(ji,:)
2817             WRITE(numout,*) 'qsintveg_old:',qsintveg_old(ji,:)
2818             WRITE(numout,*) 'SUMqsintveg:',SUM(qsintveg(ji,:))
2819             WRITE(numout,*) 'SUMqsintveg_old:',SUM(qsintveg_old(ji,:))
2820             WRITE(numout,*) 'veget_max:',veget_max(ji,:)
2821             WRITE(numout,*) 'soiltile:',soiltile(ji,:)
2822             WRITE(numout,*) 'resdist:',resdist(ji,:)
2823             WRITE(numout,*) 'vegtot:',vegtot(ji)
2824             WRITE(numout,*) 'vegtot_old:',vegtot_old(ji)
2825             WRITE(numout,*) 'drain_upd:',drain_upd(ji)
2826             WRITE(numout,*) 'runoff_upd:',runoff_upd(ji)
2827             WRITE(numout,*) 'vmr:',vmr(ji,:)
2828             WRITE(numout,*) 'vmr_sum:',vmr_sum(ji)
2829             DO jst=1,nstm
2830                WRITE(numout,*) 'mc(',jst,'):',mc(ji,:,jst)
2831             ENDDO
2832             WRITE(numout,*) 'water2infilt:',water2infilt(ji,:)
2833             WRITE(numout,*) 'water2infilt_old:',water2infilt_old(ji,:)
2834             WRITE(numout,*) 'infil_dilu:',infil_dilu(ji)
2835             WRITE(numout,*) 'mc_dilu:',mc_dilu(ji,:)
2836
2837             error=.TRUE.
2838             CALL ipslerr_p(2, 'hydrol_tmc_update', 'Error in water balance', 'We STOP in the end of this subroutine','')
2839          ENDIF
2840       ENDDO
2841    ENDIF
2842
2843    !! Now that the work is done, update resdist
2844    resdist(:,:) = soiltile(:,:)
2845
2846    !
2847    !!  Exit if error was found previously in this subroutine
2848    !
2849    IF ( error ) THEN
2850       WRITE(numout,*) 'One or more errors have been detected in hydrol_tmc_update. Model stops.'
2851       CALL ipslerr_p(3, 'hydrol_tmc_update', 'We will STOP now.',&
2852                  & 'One or several fatal errors were found previously.','')
2853    END IF
2854
2855    IF (printlev>=3) WRITE (numout,*) ' hydrol_tmc_update done '
2856
2857  END SUBROUTINE hydrol_tmc_update
2858
2859!! ================================================================================================================================
2860!! SUBROUTINE   : hydrol_var_init
2861!!
2862!>\BRIEF        This routine initializes hydrologic parameters to define K and D, and diagnostic hydrologic variables. 
2863!!
2864!! DESCRIPTION  :
2865!! - 1 compute the depths
2866!! - 2 compute the profile for roots
2867!! - 3 compute the profile for a and n Van Genuchten parameter
2868!! - 4 compute the linearized values of k, a, b and d for the resolution of Fokker Planck equation
2869!! - 5 water reservoirs initialisation
2870!!
2871!! RECENT CHANGE(S) : None
2872!!
2873!! MAIN OUTPUT VARIABLE(S) :
2874!!
2875!! REFERENCE(S) :
2876!!
2877!! FLOWCHART    : None
2878!! \n
2879!_ ================================================================================================================================
2880!_ hydrol_var_init
2881
2882  SUBROUTINE hydrol_var_init (kjpindex, veget, veget_max, soiltile, njsc, &
2883       mx_eau_var, shumdiag_perma, &
2884       drysoil_frac, qsintveg, mc_layh, mcl_layh) 
2885
2886    ! interface description
2887
2888    !! 0. Variable and parameter declaration
2889
2890    !! 0.1 Input variables
2891
2892    ! input scalar
2893    INTEGER(i_std), INTENT(in)                          :: kjpindex      !! Domain size (number of grid cells) (1)
2894    ! input fields
2895    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max     !! PFT fractions within grid-cells (1; 1)
2896    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget         !! Effective fraction of vegetation by PFT (1; 1)
2897    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: njsc          !! Index of the dominant soil textural class
2898                                                                         !! in the grid cell (1-nscm, unitless)
2899    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile      !! Fraction of each soil tile within vegtot (0-1, unitless)
2900
2901    !! 0.2 Output variables
2902
2903    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: mx_eau_var    !! Maximum water content of the soil
2904                                                                         !! @tex $(kg m^{-2})$ @endtex
2905    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out) :: shumdiag_perma!! Percent of porosity filled with water (mc/mcs)
2906                                                                         !! used for the thermal computations
2907    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)    :: drysoil_frac  !! function of litter humidity
2908    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: mc_layh       !! Volumetric soil moisture content for each layer in hydrol(liquid+ice) [m3/m3]
2909    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: mcl_layh      !! Volumetric soil moisture content for each layer in hydrol(liquid) [m3/m3]
2910
2911    !! 0.3 Modified variables
2912    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg    !! Water on vegetation due to interception
2913                                                                         !! @tex $(kg m^{-2})$ @endtex 
2914
2915    !! 0.4 Local variables
2916
2917    INTEGER(i_std)                                      :: ji, jv        !! Grid-cell and PFT indices (1)
2918    INTEGER(i_std)                                      :: jst, jsc, jsl !! Soiltile, Soil Texture, and Soil layer indices (1)
2919    INTEGER(i_std)                                      :: i             !! Index (1)
2920    REAL(r_std)                                         :: m             !! m=1-1/n (unitless)
2921    REAL(r_std)                                         :: frac          !! Relative linearized VWC (unitless)
2922    REAL(r_std)                                         :: avan_mod      !! VG parameter a modified from  exponantial profile
2923                                                                         !! @tex $(mm^{-1})$ @endtex
2924    REAL(r_std)                                         :: nvan_mod      !! VG parameter n  modified from  exponantial profile
2925                                                                         !! (unitless)
2926    REAL(r_std), DIMENSION(nslm,nscm)                   :: afact, nfact  !! Multiplicative factor for decay of a and n with depth
2927                                                                         !! (unitless)
2928    ! parameters for "soil densification" with depth
2929    REAL(r_std)                                         :: dp_comp       !! Depth at which the 'compacted' value of ksat
2930                                                                         !! is reached (m)
2931    REAL(r_std)                                         :: f_ks          !! Exponential factor for decay of ksat with depth
2932                                                                         !! @tex $(m^{-1})$ @endtex
2933    ! Fixed parameters from fitted relationships
2934    REAL(r_std)                                         :: n0            !! fitted value for relation log((n-n0)/(n_ref-n0)) =
2935                                                                         !! nk_rel * log(k/k_ref)
2936                                                                         !! (unitless)
2937    REAL(r_std)                                         :: nk_rel        !! fitted value for relation log((n-n0)/(n_ref-n0)) =
2938                                                                         !! nk_rel * log(k/k_ref)
2939                                                                         !! (unitless)
2940    REAL(r_std)                                         :: a0            !! fitted value for relation log((a-a0)/(a_ref-a0)) =
2941                                                                         !! ak_rel * log(k/k_ref)
2942                                                                         !! @tex $(mm^{-1})$ @endtex
2943    REAL(r_std)                                         :: ak_rel        !! fitted value for relation log((a-a0)/(a_ref-a0)) =
2944                                                                         !! ak_rel * log(k/k_ref)
2945                                                                         !! (unitless)
2946    REAL(r_std)                                         :: kfact_max     !! Maximum factor for Ks decay with depth (unitless)
2947    REAL(r_std)                                         :: k_tmp, tmc_litter_ratio
2948    INTEGER(i_std), PARAMETER                           :: error_level = 3 !! Error level for consistency check
2949                                                                           !! Switch to 2 tu turn fatal errors into warnings
2950    REAL(r_std), DIMENSION (kjpindex,nslm)              :: alphavg         !! VG param a modified with depth at each node
2951                                                                           !! @tex $(mm^{-1})$ @endtexe
2952    REAL(r_std), DIMENSION (kjpindex,nslm)              :: nvg             !! VG param n modified with depth at each node
2953                                                                           !! (unitless)
2954    INTEGER(i_std)                                      :: jiref           !! To identify the mc_lins where k_lin and d_lin
2955                                                                           !! need special treatment
2956
2957!_ ================================================================================================================================
2958
2959!!??Aurelien: Les 3 parametres qui suivent pourait peut-être mis dans hydrol_init?
2960    !
2961    !
2962    !Config Key   = CWRR_NKS_N0
2963    !Config Desc  = fitted value for relation log((n-n0)/(n_ref-n0)) = nk_rel * log(k/k_ref)
2964    !Config Def   = 0.0
2965    !Config If    = HYDROL_CWRR
2966    !Config Help  =
2967    !Config Units = [-]
2968    n0 = 0.0
2969    CALL getin_p("CWRR_NKS_N0",n0)
2970
2971    !! Check parameter value (correct range)
2972    IF ( n0 < zero ) THEN
2973       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2974            &     "Wrong parameter value for CWRR_NKS_N0.", &
2975            &     "This parameter should be non-negative. ", &
2976            &     "Please, check parameter value in run.def. ")
2977    END IF
2978
2979
2980    !Config Key   = CWRR_NKS_POWER
2981    !Config Desc  = fitted value for relation log((n-n0)/(n_ref-n0)) = nk_rel * log(k/k_ref)
2982    !Config Def   = 0.0
2983    !Config If    = HYDROL_CWRR
2984    !Config Help  =
2985    !Config Units = [-]
2986    nk_rel = 0.0
2987    CALL getin_p("CWRR_NKS_POWER",nk_rel)
2988
2989    !! Check parameter value (correct range)
2990    IF ( nk_rel < zero ) THEN
2991       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2992            &     "Wrong parameter value for CWRR_NKS_POWER.", &
2993            &     "This parameter should be non-negative. ", &
2994            &     "Please, check parameter value in run.def. ")
2995    END IF
2996
2997
2998    !Config Key   = CWRR_AKS_A0
2999    !Config Desc  = fitted value for relation log((a-a0)/(a_ref-a0)) = ak_rel * log(k/k_ref)
3000    !Config Def   = 0.0
3001    !Config If    = HYDROL_CWRR
3002    !Config Help  =
3003    !Config Units = [1/mm]
3004    a0 = 0.0
3005    CALL getin_p("CWRR_AKS_A0",a0)
3006
3007    !! Check parameter value (correct range)
3008    IF ( a0 < zero ) THEN
3009       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3010            &     "Wrong parameter value for CWRR_AKS_A0.", &
3011            &     "This parameter should be non-negative. ", &
3012            &     "Please, check parameter value in run.def. ")
3013    END IF
3014
3015
3016    !Config Key   = CWRR_AKS_POWER
3017    !Config Desc  = fitted value for relation log((a-a0)/(a_ref-a0)) = ak_rel * log(k/k_ref)
3018    !Config Def   = 0.0
3019    !Config If    = HYDROL_CWRR
3020    !Config Help  =
3021    !Config Units = [-]
3022    ak_rel = 0.0
3023    CALL getin_p("CWRR_AKS_POWER",ak_rel)
3024
3025    !! Check parameter value (correct range)
3026    IF ( nk_rel < zero ) THEN
3027       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3028            &     "Wrong parameter value for CWRR_AKS_POWER.", &
3029            &     "This parameter should be non-negative. ", &
3030            &     "Please, check parameter value in run.def. ")
3031    END IF
3032
3033
3034    !Config Key   = KFACT_DECAY_RATE
3035    !Config Desc  = Factor for Ks decay with depth
3036    !Config Def   = 2.0
3037    !Config If    = HYDROL_CWRR
3038    !Config Help  = 
3039    !Config Units = [1/m]
3040    f_ks = 2.0
3041    CALL getin_p ("KFACT_DECAY_RATE", f_ks)
3042
3043    !! Check parameter value (correct range)
3044    IF ( f_ks < zero ) THEN
3045       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3046            &     "Wrong parameter value for KFACT_DECAY_RATE.", &
3047            &     "This parameter should be positive. ", &
3048            &     "Please, check parameter value in run.def. ")
3049    END IF
3050
3051
3052    !Config Key   = KFACT_STARTING_DEPTH
3053    !Config Desc  = Depth for compacted value of Ks
3054    !Config Def   = 0.3
3055    !Config If    = HYDROL_CWRR
3056    !Config Help  = 
3057    !Config Units = [m]
3058    dp_comp = 0.3
3059    CALL getin_p ("KFACT_STARTING_DEPTH", dp_comp)
3060
3061    !! Check parameter value (correct range)
3062    IF ( dp_comp <= zero ) THEN
3063       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3064            &     "Wrong parameter value for KFACT_STARTING_DEPTH.", &
3065            &     "This parameter should be positive. ", &
3066            &     "Please, check parameter value in run.def. ")
3067    END IF
3068
3069
3070    !Config Key   = KFACT_MAX
3071    !Config Desc  = Maximum Factor for Ks increase due to vegetation
3072    !Config Def   = 10.0
3073    !Config If    = HYDROL_CWRR
3074    !Config Help  =
3075    !Config Units = [-]
3076    kfact_max = 10.0
3077    CALL getin_p ("KFACT_MAX", kfact_max)
3078
3079    !! Check parameter value (correct range)
3080    IF ( kfact_max < 10. ) THEN
3081       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3082            &     "Wrong parameter value for KFACT_MAX.", &
3083            &     "This parameter should be greater than 10. ", &
3084            &     "Please, check parameter value in run.def. ")
3085    END IF
3086
3087   
3088    !-
3089    !! 1 Create local variables in mm for the vertical depths
3090    !!   Vertical depth variables (znh, dnh, dlh) are stored in module vertical_soil_var in m.
3091    DO jsl=1,nslm
3092       zz(jsl) = znh(jsl)*mille
3093       dz(jsl) = dnh(jsl)*mille
3094       dh(jsl) = dlh(jsl)*mille
3095    ENDDO
3096
3097    !-
3098    !! 2 Compute the root density profile if not ok_dynroot
3099    !!   For the case with ok_dynroot, the calculations are done at each time step in hydrol_soil
3100    IF (.NOT. ok_dynroot) THEN
3101       DO ji=1, kjpindex
3102          !-
3103          !! The three following equations concerning nroot computation are derived from the integrals
3104          !! of equations C9 to C11 of De Rosnay's (1999) PhD thesis (page 158).
3105          !! The occasional absence of minus sign before humcste parameter is correct.
3106          DO jv = 1,nvm
3107             DO jsl = 2, nslm-1
3108                nroot(ji,jv,jsl) = (EXP(-humcste(jv)*zz(jsl)/mille)) * &
3109                     & (EXP(humcste(jv)*dz(jsl)/mille/deux) - &
3110                     & EXP(-humcste(jv)*dz(jsl+1)/mille/deux))/ &
3111                     & (EXP(-humcste(jv)*dz(2)/mille/deux) &
3112                     & -EXP(-humcste(jv)*zz(nslm)/mille))
3113             ENDDO
3114             nroot(ji,jv,1) = zero
3115
3116             nroot(ji,jv,nslm) = (EXP(humcste(jv)*dz(nslm)/mille/deux) -un) * &
3117                  & EXP(-humcste(jv)*zz(nslm)/mille) / &
3118                  & (EXP(-humcste(jv)*dz(2)/mille/deux) &
3119                  & -EXP(-humcste(jv)*zz(nslm)/mille))
3120          ENDDO
3121       ENDDO
3122    END IF
3123
3124    !-
3125    !! 3 Compute the profile for a and n
3126    !-
3127
3128    ! For every soil texture
3129    DO jsc = 1, nscm 
3130       DO jsl=1,nslm
3131          ! PhD thesis of d'Orgeval, 2006, p81, Eq. 4.38; d'Orgeval et al. 2008, Eq. 2
3132          ! Calibrated against Hapex-Sahel measurements
3133          kfact(jsl,jsc) = MIN(MAX(EXP(- f_ks * (zz(jsl)/mille - dp_comp)), un/kfact_max),un)
3134          ! PhD thesis of d'Orgeval, 2006, p81, Eqs. 4.39; 4.42, and Fig 4.14
3135         
3136          nfact(jsl,jsc) = ( kfact(jsl,jsc) )**nk_rel
3137          afact(jsl,jsc) = ( kfact(jsl,jsc) )**ak_rel
3138       ENDDO
3139    ENDDO
3140
3141    ! For every soil texture
3142    DO jsc = 1, nscm
3143       !-
3144       !! 4 Compute the linearized values of k, a, b and d
3145       !!   The effect of kfact_root on ks thus on k, a, n and d, is taken into account further in the code,
3146       !!   in hydrol_soil_coef.
3147       !-
3148       ! Calculate the matrix coef for Dublin model (de Rosnay, 1999; p149)
3149       ! piece-wise linearised hydraulic conductivity k_lin=alin * mc_lin + b_lin
3150       ! and diffusivity d_lin in each interval of mc, called mc_lin,
3151       ! between imin, for residual mcr, and imax for saturation mcs.
3152
3153       ! We define 51 bounds for 50 bins of mc between mcr and mcs
3154       mc_lin(imin,jsc)=mcr(jsc)
3155       mc_lin(imax,jsc)=mcs(jsc)
3156       DO ji= imin+1, imax-1 ! ji=2,50
3157          mc_lin(ji,jsc) = mcr(jsc) + (ji-imin)*(mcs(jsc)-mcr(jsc))/(imax-imin)
3158       ENDDO
3159
3160       DO jsl = 1, nslm
3161          ! From PhD thesis of d'Orgeval, 2006, p81, Eq. 4.42
3162          nvan_mod = n0 + (nvan(jsc)-n0) * nfact(jsl,jsc)
3163          avan_mod = a0 + (avan(jsc)-a0) * afact(jsl,jsc)
3164          m = un - un / nvan_mod
3165          ! Creation of arrays for SP-MIP output by landpoint
3166          nvan_mod_tab(jsl,jsc) = nvan_mod
3167          avan_mod_tab(jsl,jsc) = avan_mod
3168          ! We apply Van Genuchten equation for K(theta) based on Ks(z)=ks(jsc) * kfact(jsl,jsc)
3169          DO ji = imax,imin,-1 
3170             frac=MIN(un,(mc_lin(ji,jsc)-mcr(jsc))/(mcs(jsc)-mcr(jsc)))
3171             k_lin(ji,jsl,jsc) = ks(jsc) * kfact(jsl,jsc) * (frac**0.5) * ( un - ( un - frac ** (un/m)) ** m )**2
3172          ENDDO
3173
3174          ! k_lin should not be zero, nor too small
3175          ! We track jiref, the bin under which mc is too small and we may get zero k_lin     
3176          ji=imax-1
3177          DO WHILE ((k_lin(ji,jsl,jsc) > 1.e-32) .and. (ji>0))
3178             jiref=ji
3179             ji=ji-1
3180          ENDDO
3181          DO ji=jiref-1,imin,-1
3182             k_lin(ji,jsl,jsc)=k_lin(ji+1,jsl,jsc)/10.
3183          ENDDO
3184         
3185          DO ji = imin,imax-1 ! ji=1,50
3186             ! We deduce a_lin and b_lin based on continuity between segments k_lin = a_lin*mc-lin+b_lin
3187             a_lin(ji,jsl,jsc) = (k_lin(ji+1,jsl,jsc)-k_lin(ji,jsl,jsc)) / (mc_lin(ji+1,jsc)-mc_lin(ji,jsc))
3188             b_lin(ji,jsl,jsc)  = k_lin(ji,jsl,jsc) - a_lin(ji,jsl,jsc)*mc_lin(ji,jsc)
3189
3190             ! We calculate the d_lin for each mc bin, from Van Genuchten equation for D(theta)
3191             ! d_lin is constant and taken as the arithmetic mean between the values at the bounds of each bin
3192             IF (ji.NE.imin .AND. ji.NE.imax-1) THEN
3193                frac=MIN(un,(mc_lin(ji,jsc)-mcr(jsc))/(mcs(jsc)-mcr(jsc)))
3194                d_lin(ji,jsl,jsc) =(k_lin(ji,jsl,jsc) / (avan_mod*m*nvan_mod)) *  &
3195                     ( (frac**(-un/m))/(mc_lin(ji,jsc)-mcr(jsc)) ) * &
3196                     (  frac**(-un/m) -un ) ** (-m)
3197                frac=MIN(un,(mc_lin(ji+1,jsc)-mcr(jsc))/(mcs(jsc)-mcr(jsc)))
3198                d_lin(ji+1,jsl,jsc) =(k_lin(ji+1,jsl,jsc) / (avan_mod*m*nvan_mod))*&
3199                     ( (frac**(-un/m))/(mc_lin(ji+1,jsc)-mcr(jsc)) ) * &
3200                     (  frac**(-un/m) -un ) ** (-m)
3201                d_lin(ji,jsl,jsc) = undemi * (d_lin(ji,jsl,jsc)+d_lin(ji+1,jsl,jsc))
3202             ELSE IF(ji.EQ.imax-1) THEN
3203                d_lin(ji,jsl,jsc) =(k_lin(ji,jsl,jsc) / (avan_mod*m*nvan_mod)) * &
3204                     ( (frac**(-un/m))/(mc_lin(ji,jsc)-mcr(jsc)) ) *  &
3205                     (  frac**(-un/m) -un ) ** (-m)
3206             ENDIF
3207          ENDDO
3208
3209          ! Special case for ji=imin
3210          d_lin(imin,jsl,jsc) = d_lin(imin+1,jsl,jsc)/1000.
3211
3212          ! We adjust d_lin where k_lin was previously adjusted otherwise we might get non-monotonous variations
3213          ! We don't want d_lin = zero
3214          DO ji=jiref-1,imin,-1
3215             d_lin(ji,jsl,jsc)=d_lin(ji+1,jsl,jsc)/10.
3216          ENDDO
3217
3218       ENDDO
3219    ENDDO
3220
3221    ! Output of alphavg and nvg at each node for SP-MIP
3222    DO jsl = 1, nslm
3223       alphavg(:,jsl) = avan_mod_tab(jsl,njsc(:))*1000. ! from mm-1 to m-1
3224       nvg(:,jsl) = nvan_mod_tab(jsl,njsc(:))
3225    ENDDO
3226    CALL xios_orchidee_send_field("alphavg",alphavg) ! in m-1
3227    CALL xios_orchidee_send_field("nvg",nvg) ! unitless
3228
3229    !! 5 Water reservoir initialisation
3230    !
3231!!$    DO jst = 1,nstm
3232!!$       DO ji = 1, kjpindex
3233!!$          mx_eau_var(ji) = mx_eau_var(ji) + soiltile(ji,jst)*&
3234!!$               &   zmaxh*mille*mcs(njsc(ji))
3235!!$       END DO
3236!!$    END DO
3237!!$    IF (check_CWRR) THEN
3238!!$       IF ( ANY ( ABS( mx_eau_var(:) - zmaxh*mille*mcs(njsc(:)) ) > min_sechiba ) ) THEN
3239!!$          ji=MAXLOC ( ABS( mx_eau_var(:) - zmaxh*mille*mcs(njsc(:)) ) , 1)
3240!!$          WRITE(numout, *) "Erreur formule simplifiée mx_eau_var ! ", mx_eau_var(ji), zmaxh*mille*mcs(njsc(ji))
3241!!$          WRITE(numout, *) "err = ",ABS(mx_eau_var(ji) - zmaxh*mille*mcs(njsc(ji)))
3242!!$          STOP 1
3243!!$       ENDIF
3244!!$    ENDIF
3245
3246    mx_eau_var(:) = zero
3247    mx_eau_var(:) = zmaxh*mille*mcs(njsc(:)) 
3248
3249    DO ji = 1,kjpindex 
3250       IF (vegtot(ji) .LE. zero) THEN
3251          mx_eau_var(ji) = mx_eau_nobio*zmaxh
3252          ! Aurelien: what does vegtot=0 mean? is it like frac_nobio=1? But if 0<frac_nobio<1 ???
3253       ENDIF
3254
3255    END DO
3256
3257    ! Compute the litter humidity, shumdiag and fry
3258    shumdiag_perma(:,:) = zero
3259    humtot(:) = zero
3260    tmc(:,:) = zero
3261
3262    ! Loop on soiltiles to compute the variables (ji,jst)
3263    DO jst=1,nstm 
3264       DO ji = 1, kjpindex
3265          tmcs(ji,jst)=zmaxh* mille*mcs(njsc(ji))
3266          tmcr(ji,jst)=zmaxh* mille*mcr(njsc(ji))
3267          tmcfc(ji,jst)=zmaxh* mille*mcfc(njsc(ji))
3268          tmcw(ji,jst)=zmaxh* mille*mcw(njsc(ji))
3269       ENDDO
3270    ENDDO
3271       
3272    ! The total soil moisture for each soiltile:
3273    DO jst=1,nstm
3274       DO ji=1,kjpindex
3275          tmc(ji,jst)= dz(2) * ( trois*mc(ji,1,jst)+ mc(ji,2,jst))/huit
3276       END DO
3277    ENDDO
3278
3279    DO jst=1,nstm 
3280       DO jsl=2,nslm-1
3281          DO ji=1,kjpindex
3282             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) * ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
3283                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
3284          END DO
3285       END DO
3286    ENDDO
3287
3288    DO jst=1,nstm 
3289       DO ji=1,kjpindex
3290          tmc(ji,jst) = tmc(ji,jst) +  dz(nslm) * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
3291          tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
3292       ENDDO
3293    END DO
3294
3295!JG: hydrol_tmc_update should not be called in the initialization phase. Call of hydrol_tmc_update makes the model restart differenlty.   
3296!    ! If veget has been updated before restart (with LAND USE or DGVM),
3297!    ! tmc and mc must be modified with respect to humtot conservation.
3298!   CALL hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg)
3299
3300    ! The litter variables:
3301    ! level 1
3302    DO jst=1,nstm 
3303       DO ji=1,kjpindex
3304          tmc_litter(ji,jst) = dz(2) * (trois*mcl(ji,1,jst)+mcl(ji,2,jst))/huit
3305          tmc_litter_wilt(ji,jst) = dz(2) * mcw(njsc(ji)) / deux
3306          tmc_litter_res(ji,jst) = dz(2) * mcr(njsc(ji)) / deux
3307          tmc_litter_field(ji,jst) = dz(2) * mcfc(njsc(ji)) / deux
3308          tmc_litter_sat(ji,jst) = dz(2) * mcs(njsc(ji)) / deux
3309          tmc_litter_awet(ji,jst) = dz(2) * mc_awet(njsc(ji)) / deux
3310          tmc_litter_adry(ji,jst) = dz(2) * mc_adry(njsc(ji)) / deux
3311       ENDDO
3312    END DO
3313    ! sum from level 2 to 4
3314    DO jst=1,nstm 
3315       DO jsl=2,4
3316          DO ji=1,kjpindex
3317             tmc_litter(ji,jst) = tmc_litter(ji,jst) + dz(jsl) * & 
3318                  & ( trois*mcl(ji,jsl,jst) + mcl(ji,jsl-1,jst))/huit &
3319                  & + dz(jsl+1)*(trois*mcl(ji,jsl,jst) + mcl(ji,jsl+1,jst))/huit
3320             tmc_litter_wilt(ji,jst) = tmc_litter_wilt(ji,jst) + &
3321                  &(dz(jsl)+ dz(jsl+1))*& 
3322                  & mcw(njsc(ji))/deux
3323             tmc_litter_res(ji,jst) = tmc_litter_res(ji,jst) + &
3324                  &(dz(jsl)+ dz(jsl+1))*& 
3325                  & mcr(njsc(ji))/deux
3326             tmc_litter_sat(ji,jst) = tmc_litter_sat(ji,jst) + &
3327                  &(dz(jsl)+ dz(jsl+1))* & 
3328                  & mcs(njsc(ji))/deux
3329             tmc_litter_field(ji,jst) = tmc_litter_field(ji,jst) + &
3330                  & (dz(jsl)+ dz(jsl+1))* & 
3331                  & mcfc(njsc(ji))/deux
3332             tmc_litter_awet(ji,jst) = tmc_litter_awet(ji,jst) + &
3333                  &(dz(jsl)+ dz(jsl+1))* & 
3334                  & mc_awet(njsc(ji))/deux
3335             tmc_litter_adry(ji,jst) = tmc_litter_adry(ji,jst) + &
3336                  & (dz(jsl)+ dz(jsl+1))* & 
3337                  & mc_adry(njsc(ji))/deux
3338          END DO
3339       END DO
3340    END DO
3341
3342
3343    DO jst=1,nstm 
3344       DO ji=1,kjpindex
3345          ! here we set that humrelv=0 in PFT1
3346          humrelv(ji,1,jst) = zero
3347       ENDDO
3348    END DO
3349
3350
3351    ! Calculate shumdiag_perma for thermosoil
3352    ! Use resdist instead of soiltile because we here need to have
3353    ! shumdiag_perma at the value from previous time step.
3354    ! Here, soilmoist is only used as a temporary variable to calculate shumdiag_perma
3355    ! (based on resdist=soiltile from previous timestep, but normally equal to soiltile)
3356    ! For consistency with hydrol_soil, we want to calculate a grid-cell average
3357    soilmoist(:,:) = zero
3358    DO jst=1,nstm
3359       DO ji=1,kjpindex
3360          soilmoist(ji,1) = soilmoist(ji,1) + resdist(ji,jst) * &
3361               dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
3362          DO jsl = 2,nslm-1
3363             soilmoist(ji,jsl) = soilmoist(ji,jsl) + resdist(ji,jst) * &
3364                  ( dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
3365                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit )
3366          END DO
3367          soilmoist(ji,nslm) = soilmoist(ji,nslm) + resdist(ji,jst) * &
3368               dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
3369       ENDDO
3370    ENDDO
3371    DO ji=1,kjpindex
3372        soilmoist(ji,:) = soilmoist(ji,:) * vegtot_old(ji) ! grid cell average
3373    ENDDO
3374   
3375    ! -- shumdiag_perma for restart
3376    !  For consistency with hydrol_soil, we want to calculate a grid-cell average
3377    DO jsl = 1, nslm
3378       DO ji=1,kjpindex       
3379          shumdiag_perma(ji,jsl) = soilmoist(ji,jsl) / (dh(jsl)*mcs(njsc(ji)))
3380          shumdiag_perma(ji,jsl) = MAX(MIN(shumdiag_perma(ji,jsl), un), zero) 
3381       ENDDO
3382    ENDDO
3383               
3384    ! Calculate drysoil_frac if it was not found in the restart file
3385    ! For simplicity, we set drysoil_frac to 0.5 in this case
3386    IF (ALL(drysoil_frac(:) == val_exp)) THEN
3387       DO ji=1,kjpindex
3388          drysoil_frac(ji) = 0.5
3389       END DO
3390    END IF
3391
3392    !! Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in
3393    !! thermosoil for the thermal conductivity.
3394    ! These values are only used in thermosoil_init in absence of a restart file
3395    mc_layh(:,:) = zero
3396    mcl_layh(:,:) = zero
3397    DO jst=1,nstm
3398       DO jsl=1,nslm
3399          DO ji=1,kjpindex
3400            mc_layh(ji,jsl) = mc_layh(ji,jsl) + mc(ji,jsl,jst) * resdist(ji,jst)  * vegtot_old(ji)
3401            mcl_layh(ji,jsl) = mcl_layh(ji,jsl) + mcl(ji,jsl,jst) * resdist(ji,jst) * vegtot_old(ji)
3402         ENDDO
3403      END DO
3404    END DO
3405
3406    IF (printlev>=3) WRITE (numout,*) ' hydrol_var_init done '
3407
3408  END SUBROUTINE hydrol_var_init
3409
3410
3411!! ================================================================================================================================
3412!! SUBROUTINE   : hydrol_snow
3413!!
3414!>\BRIEF        This routine computes snow processes.
3415!!
3416!! DESCRIPTION  :
3417!! - 0 initialisation
3418!! - 1 On vegetation
3419!! - 1.1 Compute snow masse
3420!! - 1.2 Sublimation
3421!! - 1.2.1 Check that sublimation on the vegetated fraction is possible.
3422!! - 1.3. snow melt only if temperature positive
3423!! - 1.3.1 enough snow for melting or not
3424!! - 1.3.2 not enough snow
3425!! - 1.3.3 negative snow - now snow melt
3426!! - 1.4 Snow melts only on weight glaciers
3427!! - 2 On Land ice
3428!! - 2.1 Compute snow
3429!! - 2.2 Sublimation
3430!! - 2.3 Snow melt only for continental ice fraction
3431!! - 2.3.1 If there is snow on the ice-fraction it can melt
3432!! - 2.4 Snow melts only on weight glaciers
3433!! - 3 On other surface types - not done yet
3434!! - 4 computes total melt (snow and ice)
3435!! - 5 computes snow age on veg and ice (for albedo)
3436!! - 5.1 Snow age on vegetation
3437!! - 5.2 Snow age on ice
3438!! - 6 Diagnose the depth of the snow layer
3439!!
3440!! RECENT CHANGE(S) : None
3441!!
3442!! MAIN OUTPUT VARIABLE(S) :
3443!!
3444!! REFERENCE(S) :
3445!!
3446!! FLOWCHART    : None
3447!! \n
3448!_ ================================================================================================================================
3449!_ hydrol_snow
3450
3451  SUBROUTINE hydrol_snow (kjpindex, precip_rain, precip_snow , temp_sol_new, soilcap,&
3452       & frac_nobio, totfrac_nobio, vevapsno, snow, snow_age, snow_nobio, snow_nobio_age, &
3453       & tot_melt, snowdepth,snowmelt)
3454
3455    !
3456    ! interface description
3457
3458    !! 0. Variable and parameter declaration
3459
3460    !! 0.1 Input variables
3461
3462    ! input scalar
3463    INTEGER(i_std), INTENT(in)                               :: kjpindex      !! Domain size
3464    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_rain   !! Rainfall
3465    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_snow   !! Snow precipitation
3466    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: temp_sol_new  !! New soil temperature
3467    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: soilcap       !! Soil capacity
3468    REAL(r_std), DIMENSION (kjpindex,nnobio), INTENT(in)     :: frac_nobio    !! Fraction of continental ice, lakes, ...
3469    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: totfrac_nobio !! Total fraction of continental ice+lakes+ ...
3470
3471    !! 0.2 Output variables
3472
3473    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: tot_melt      !! Total melt from snow and ice 
3474    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: snowmelt      !! Snow melt
3475    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: snowdepth     !! Snow depth
3476
3477    !! 0.3 Modified variables
3478
3479    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapsno      !! Snow evaporation
3480    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: snow          !! Snow mass [Kg/m^2]
3481    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: snow_age      !! Snow age
3482    REAL(r_std), DIMENSION (kjpindex,nnobio), INTENT(inout)  :: snow_nobio    !! Ice water balance
3483    REAL(r_std), DIMENSION (kjpindex,nnobio), INTENT(inout)  :: snow_nobio_age!! Snow age on ice, lakes, ...
3484
3485    !! 0.4 Local variables
3486
3487    INTEGER(i_std)                               :: ji, jv
3488    REAL(r_std), DIMENSION (kjpindex)             :: d_age  !! Snow age change
3489    REAL(r_std), DIMENSION (kjpindex)             :: xx     !! temporary
3490    REAL(r_std)                                   :: snowmelt_tmp !! The name says it all !
3491    REAL(r_std)                                   :: snow_d1k !! The amount of snow that corresponds to a 1K cooling
3492
3493!_ ================================================================================================================================
3494
3495    !
3496    ! for continental points
3497    !
3498
3499    !
3500    !!_0 initialisation
3501    !
3502    DO jv = 1, nnobio
3503       DO ji=1,kjpindex
3504          subsnownobio(ji,jv) = zero
3505       ENDDO
3506    ENDDO
3507    DO ji=1,kjpindex
3508       subsnowveg(ji) = zero
3509       snowmelt(ji) = zero
3510       icemelt(ji) = zero
3511       subsinksoil(ji) = zero
3512       tot_melt(ji) = zero
3513    ENDDO
3514    !
3515    !! 1 On vegetation
3516    !
3517    DO ji=1,kjpindex
3518       !
3519    !! 1.1 Compute snow masse
3520       !
3521       snow(ji) = snow(ji) + (un - totfrac_nobio(ji))*precip_snow(ji)
3522       !
3523       !
3524    !! 1.2 Sublimation
3525       !      Separate between vegetated and no-veget fractions
3526       !      Care has to be taken as we might have sublimation from the
3527       !      the frac_nobio while there is no snow on the rest of the grid.
3528       !
3529       IF ( snow(ji) > snowcri ) THEN
3530          subsnownobio(ji,iice) = frac_nobio(ji,iice)*vevapsno(ji)
3531          subsnowveg(ji) = vevapsno(ji) - subsnownobio(ji,iice)
3532       ELSE
3533          ! Correction Nathalie - Juillet 2006.
3534          ! On doit d'abord tester s'il existe un frac_nobio!
3535          ! Pour le moment je ne regarde que le iice
3536          IF ( frac_nobio(ji,iice) .GT. min_sechiba) THEN
3537             subsnownobio(ji,iice) = vevapsno(ji)
3538             subsnowveg(ji) = zero
3539          ELSE
3540             subsnownobio(ji,iice) = zero
3541             subsnowveg(ji) = vevapsno(ji)
3542          ENDIF
3543       ENDIF
3544       ! here vevapsno bas been separated into a bio and nobio fractions, without changing the total
3545       !
3546       !
3547    !! 1.2.1 Check that sublimation on the vegetated fraction is possible.
3548       !
3549       IF (subsnowveg(ji) .GT. snow(ji)) THEN
3550          ! What could not be sublimated goes into subsinksoil
3551          IF( (un - totfrac_nobio(ji)).GT.min_sechiba) THEN
3552             subsinksoil (ji) = (subsnowveg(ji) - snow(ji))/ (un - totfrac_nobio(ji))
3553          END IF
3554          ! Sublimation is thus limited to what is available
3555          ! Then, evavpsnow is reduced, of subsinksoil
3556          subsnowveg(ji) = snow(ji)
3557          snow(ji) = zero
3558          vevapsno(ji) = subsnowveg(ji) + subsnownobio(ji,iice)
3559       ELSE
3560          snow(ji) = snow(ji) - subsnowveg(ji)
3561       ENDIF
3562       !
3563    !! 1.3. snow melt only if temperature positive
3564       !
3565       IF (temp_sol_new(ji).GT.tp_00) THEN
3566          !
3567          IF (snow(ji).GT.sneige) THEN
3568             !
3569             snowmelt(ji) = (un - frac_nobio(ji,iice))*(temp_sol_new(ji) - tp_00) * soilcap(ji) / chalfu0
3570             !
3571    !! 1.3.1 enough snow for melting or not
3572             !
3573             IF (snowmelt(ji).LT.snow(ji)) THEN
3574                snow(ji) = snow(ji) - snowmelt(ji)
3575             ELSE
3576                snowmelt(ji) = snow(ji)
3577                snow(ji) = zero
3578             END IF
3579             !
3580          ELSEIF (snow(ji).GE.zero) THEN
3581             !
3582    !! 1.3.2 not enough snow
3583             !
3584             snowmelt(ji) = snow(ji)
3585             snow(ji) = zero
3586          ELSE
3587             !
3588    !! 1.3.3 negative snow - now snow melt
3589             !
3590             snow(ji) = zero
3591             snowmelt(ji) = zero
3592             WRITE(numout,*) 'hydrol_snow: WARNING! snow was negative and was reset to zero. '
3593             !
3594          END IF
3595
3596       ENDIF
3597    !! 1.4 Snow melts above a threshold
3598       ! Ice melt only if there is more than a given mass : maxmass_snow,
3599       ! But the snow cannot melt more in one time step to what corresponds to
3600       ! a 1K cooling. This will lead to a progressive melting of snow above
3601       ! maxmass_snow but it is needed as a too strong cooling can destabilise the model.
3602       IF ( snow(ji) .GT. maxmass_snow ) THEN
3603          snow_d1k = un * soilcap(ji) / chalfu0
3604          snowmelt(ji) = snowmelt(ji) + MIN((snow(ji) - maxmass_snow),snow_d1k)
3605          snow(ji) = snow(ji) - snowmelt(ji)
3606          IF ( printlev >= 3 ) WRITE (numout,*) "Snow was above maxmass_snow (", maxmass_snow,") and we melted ", snowmelt(ji)
3607       ENDIF
3608       
3609    END DO
3610    !
3611    !! 2 On Land ice
3612    !
3613    DO ji=1,kjpindex
3614       !
3615    !! 2.1 Compute snow
3616       !
3617       !!??Aurelien: pkoi mettre precip_rain en dessous? We considere liquid precipitations becomes instantly snow? 
3618       snow_nobio(ji,iice) = snow_nobio(ji,iice) + frac_nobio(ji,iice)*precip_snow(ji) + &
3619            & frac_nobio(ji,iice)*precip_rain(ji)
3620       !
3621    !! 2.2 Sublimation
3622       !      Was calculated before it can give us negative snow_nobio but that is OK
3623       !      Once it goes below a certain values (-maxmass_snow for instance) we should kill
3624       !      the frac_nobio(ji,iice) !
3625       !
3626       snow_nobio(ji,iice) = snow_nobio(ji,iice) - subsnownobio(ji,iice)
3627       !
3628    !! 2.3 Snow melt only for continental ice fraction
3629       !
3630       snowmelt_tmp = zero
3631       IF (temp_sol_new(ji) .GT. tp_00) THEN
3632          !
3633    !! 2.3.1 If there is snow on the ice-fraction it can melt
3634          !
3635          snowmelt_tmp = frac_nobio(ji,iice)*(temp_sol_new(ji) - tp_00) * soilcap(ji) / chalfu0
3636          !
3637          IF ( snowmelt_tmp .GT. snow_nobio(ji,iice) ) THEN
3638             snowmelt_tmp = MAX( zero, snow_nobio(ji,iice))
3639          ENDIF
3640          snowmelt(ji) = snowmelt(ji) + snowmelt_tmp
3641          snow_nobio(ji,iice) = snow_nobio(ji,iice) - snowmelt_tmp
3642          !
3643       ENDIF
3644       !
3645    !! 2.4 Snow melts over a threshold
3646       !   Ice melt only if there is more than a given mass : maxmass_snow,
3647       !   But the snow cannot melt more in one time step to what corresponds to
3648       !   a 1K cooling. This will lead to a progressive melting of snow above
3649       !   maxmass_snow but it is needed as a too strong cooling can destabilise the model.
3650       !
3651       IF ( snow_nobio(ji,iice) .GT. maxmass_snow ) THEN
3652          snow_d1k = un * soilcap(ji) / chalfu0
3653          icemelt(ji) = MIN((snow_nobio(ji,iice) - maxmass_snow),snow_d1k)
3654          snow_nobio(ji,iice) = snow_nobio(ji,iice) - icemelt(ji)
3655
3656          IF ( printlev >= 3 ) WRITE (numout,*) "Snow was above maxmass_snow ON ICE (", maxmass_snow,") and we melted ", icemelt(ji)
3657       ENDIF
3658
3659    END DO
3660
3661    !
3662    !! 3 On other surface types - not done yet
3663    !
3664    IF ( nnobio .GT. 1 ) THEN
3665       WRITE(numout,*) 'WE HAVE',nnobio-1,' SURFACE TYPES I DO NOT KNOW'
3666       WRITE(numout,*) 'CANNOT TREAT SNOW ON THESE SURFACE TYPES'
3667       CALL ipslerr_p(3,'hydrol_snow','nnobio > 1 not allowded','Cannot treat snow on these surface types.','')
3668    ENDIF
3669
3670    !
3671    !! 4 computes total melt (snow and ice)
3672    !
3673    DO ji = 1, kjpindex
3674       tot_melt(ji) = icemelt(ji) + snowmelt(ji)
3675    ENDDO
3676
3677    !
3678    !! 5 computes snow age on veg and ice (for albedo)
3679    !
3680    DO ji = 1, kjpindex
3681       !
3682    !! 5.1 Snow age on vegetation
3683       !
3684       IF (snow(ji) .LE. zero) THEN
3685          snow_age(ji) = zero
3686       ELSE
3687          snow_age(ji) =(snow_age(ji) + (un - snow_age(ji)/max_snow_age) * dt_sechiba/one_day) &
3688               & * EXP(-precip_snow(ji) / snow_trans)
3689       ENDIF
3690       !
3691    !! 5.2 Snow age on ice
3692       !
3693       ! age of snow on ice: a little bit different because in cold regions, we really
3694       ! cannot negect the effect of cold temperatures on snow metamorphism any more.
3695       !
3696       IF (snow_nobio(ji,iice) .LE. zero) THEN
3697          snow_nobio_age(ji,iice) = zero
3698       ELSE
3699          !
3700          d_age(ji) = ( snow_nobio_age(ji,iice) + &
3701               &  (un - snow_nobio_age(ji,iice)/max_snow_age) * dt_sechiba/one_day ) * &
3702               &  EXP(-precip_snow(ji) / snow_trans) - snow_nobio_age(ji,iice)
3703          IF (d_age(ji) .GT. min_sechiba ) THEN
3704             xx(ji) = MAX( tp_00 - temp_sol_new(ji), zero )
3705             xx(ji) = ( xx(ji) / 7._r_std ) ** 4._r_std
3706             d_age(ji) = d_age(ji) / (un+xx(ji))
3707          ENDIF
3708          snow_nobio_age(ji,iice) = MAX( snow_nobio_age(ji,iice) + d_age(ji), zero )
3709          !
3710       ENDIF
3711
3712    ENDDO
3713
3714    !
3715    !! 6 Diagnose the depth of the snow layer
3716    !
3717
3718    DO ji = 1, kjpindex
3719       snowdepth(ji) = snow(ji) /sn_dens
3720    ENDDO
3721
3722    IF (printlev>=3) WRITE (numout,*) ' hydrol_snow done '
3723
3724  END SUBROUTINE hydrol_snow
3725
3726   
3727!! ================================================================================================================================
3728!! SUBROUTINE   : hydrol_canop
3729!!
3730!>\BRIEF        This routine computes canopy processes.
3731!!
3732!! DESCRIPTION  :
3733!! - 1 evaporation off the continents
3734!! - 1.1 The interception loss is take off the canopy.
3735!! - 1.2 precip_rain is shared for each vegetation type
3736!! - 1.3 Limits the effect and sum what receives soil
3737!! - 1.4 swap qsintveg to the new value
3738!!
3739!! RECENT CHANGE(S) : None
3740!!
3741!! MAIN OUTPUT VARIABLE(S) :
3742!!
3743!! REFERENCE(S) :
3744!!
3745!! FLOWCHART    : None
3746!! \n
3747!_ ================================================================================================================================
3748!_ hydrol_canop
3749
3750  SUBROUTINE hydrol_canop (kjpindex, precip_rain, vevapwet, veget_max, veget, qsintmax, &
3751       & qsintveg,precisol,tot_melt)
3752
3753    !
3754    ! interface description
3755    !
3756
3757    !! 0. Variable and parameter declaration
3758
3759    !! 0.1 Input variables
3760
3761    INTEGER(i_std), INTENT(in)                               :: kjpindex    !! Domain size
3762    ! input fields
3763    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_rain !! Rain precipitation
3764    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: vevapwet    !! Interception loss
3765    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: veget_max   !! max fraction of vegetation type
3766    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: veget       !! Fraction of vegetation type
3767    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: qsintmax    !! Maximum water on vegetation for interception
3768    REAL(r_std), DIMENSION  (kjpindex), INTENT (in)          :: tot_melt    !! Total melt
3769
3770    !! 0.2 Output variables
3771
3772    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: precisol    !! Water fallen onto the ground (throughfall+Totmelt)
3773
3774    !! 0.3 Modified variables
3775
3776    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(inout)     :: qsintveg    !! Water on vegetation due to interception
3777
3778    !! 0.4 Local variables
3779
3780    INTEGER(i_std)                                           :: ji, jv
3781    REAL(r_std), DIMENSION (kjpindex,nvm)                    :: zqsintvegnew
3782
3783!_ ================================================================================================================================
3784
3785    ! boucle sur les points continentaux
3786    ! calcul de qsintveg au pas de temps suivant
3787    ! par ajout du flux interception loss
3788    ! calcule par enerbil en fonction
3789    ! des calculs faits dans diffuco
3790    ! calcul de ce qui tombe sur le sol
3791    ! avec accumulation dans precisol
3792    ! essayer d'harmoniser le traitement du sol nu
3793    ! avec celui des differents types de vegetation
3794    ! fait si on impose qsintmax ( ,1) = 0.0
3795    !
3796    ! loop for continental subdomain
3797    !
3798    !
3799    !! 1 evaporation off the continents
3800    !
3801    !! 1.1 The interception loss is take off the canopy.
3802    DO jv=2,nvm
3803       qsintveg(:,jv) = qsintveg(:,jv) - vevapwet(:,jv)
3804    END DO
3805
3806    !     It is raining :
3807    !! 1.2 precip_rain is shared for each vegetation type
3808    !
3809    qsintveg(:,1) = zero
3810    DO jv=2,nvm
3811       qsintveg(:,jv) = qsintveg(:,jv) + veget(:,jv) * ((1-throughfall_by_pft(jv))*precip_rain(:))
3812    END DO
3813
3814    !
3815    !! 1.3 Limits the effect and sum what receives soil
3816    !
3817    precisol(:,1)=veget_max(:,1)*precip_rain(:)
3818    DO jv=2,nvm
3819       DO ji = 1, kjpindex
3820          zqsintvegnew(ji,jv) = MIN (qsintveg(ji,jv),qsintmax(ji,jv)) 
3821          precisol(ji,jv) = (veget(ji,jv)*throughfall_by_pft(jv)*precip_rain(ji)) + &
3822               qsintveg(ji,jv) - zqsintvegnew (ji,jv) + &
3823               (veget_max(ji,jv) - veget(ji,jv))*precip_rain(ji)
3824       ENDDO
3825    END DO
3826       
3827    ! Precisol is currently the same as throughfall, save it for diagnostics
3828    throughfall(:,:) = precisol(:,:)
3829
3830    DO jv=1,nvm
3831       DO ji = 1, kjpindex
3832          IF (vegtot(ji).GT.min_sechiba) THEN
3833             precisol(ji,jv) = precisol(ji,jv)+tot_melt(ji)*veget_max(ji,jv)/vegtot(ji)
3834          ENDIF
3835       ENDDO
3836    END DO
3837    !   
3838    !
3839    !! 1.4 swap qsintveg to the new value
3840    !
3841    DO jv=2,nvm
3842       qsintveg(:,jv) = zqsintvegnew (:,jv)
3843    END DO
3844
3845    IF (printlev>=3) WRITE (numout,*) ' hydrol_canop done '
3846
3847  END SUBROUTINE hydrol_canop
3848
3849
3850!! ================================================================================================================================
3851!! SUBROUTINE   : hydrol_vegupd
3852!!
3853!>\BRIEF        Vegetation update   
3854!!
3855!! DESCRIPTION  :
3856!!   The vegetation cover has changed and we need to adapt the reservoir distribution
3857!!   and the distribution of plants on different soil types.
3858!!   You may note that this occurs after evaporation and so on have been computed. It is
3859!!   not a problem as a new vegetation fraction will start with humrel=0 and thus will have no
3860!!   evaporation. If this is not the case it should have been caught above.
3861!!
3862!! - 1 Update of vegetation is it needed?
3863!! - 2 calculate water mass that we have to redistribute
3864!! - 3 put it into reservoir of plant whose surface area has grown
3865!! - 4 Soil tile gestion
3866!! - 5 update the corresponding masks
3867!!
3868!! RECENT CHANGE(S) : None
3869!!
3870!! MAIN OUTPUT VARIABLE(S) :
3871!!
3872!! REFERENCE(S) :
3873!!
3874!! FLOWCHART    : None
3875!! \n
3876!_ ================================================================================================================================
3877!_ hydrol_vegupd
3878
3879  SUBROUTINE hydrol_vegupd(kjpindex, veget, veget_max, soiltile, qsintveg, frac_bare, drain_upd, runoff_upd)
3880
3881
3882    !! 0. Variable and parameter declaration
3883
3884    !! 0.1 Input variables
3885
3886    ! input scalar
3887    INTEGER(i_std), INTENT(in)                            :: kjpindex 
3888    ! input fields
3889    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(in)    :: veget            !! New vegetation map
3890    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)     :: veget_max        !! Max. fraction of vegetation type
3891    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)   :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
3892
3893    !! 0.2 Output variables
3894    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)    :: frac_bare        !! Fraction(of veget_max) of bare soil
3895                                                                              !! in each vegetation type
3896    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: drain_upd        !! Change in drainage due to decrease in vegtot
3897                                                                              !! on mc [kg/m2/dt]
3898    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: runoff_upd       !! Change in runoff due to decrease in vegtot
3899                                                                              !! on water2infilt[kg/m2/dt]
3900   
3901
3902    !! 0.3 Modified variables
3903
3904    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg         !! Water on old vegetation
3905
3906    !! 0.4 Local variables
3907
3908    INTEGER(i_std)                                 :: ji,jv,jst
3909
3910!_ ================================================================================================================================
3911
3912    !! 1 If veget has been updated at last time step (with LAND USE or DGVM),
3913    !! tmc and mc must be modified with respect to humtot conservation.
3914    CALL hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg, drain_upd, runoff_upd)
3915
3916
3917    ! Compute the masks for veget
3918   
3919    mask_veget(:,:) = 0
3920    mask_soiltile(:,:) = 0
3921   
3922    DO jst=1,nstm
3923       DO ji = 1, kjpindex
3924          IF(soiltile(ji,jst) .GT. min_sechiba) THEN
3925             mask_soiltile(ji,jst) = 1
3926          ENDIF
3927       END DO
3928    ENDDO
3929         
3930    DO jv = 1, nvm
3931       DO ji = 1, kjpindex
3932          IF(veget_max(ji,jv) .GT. min_sechiba) THEN
3933             mask_veget(ji,jv) = 1
3934          ENDIF
3935       END DO
3936    END DO
3937
3938    ! Compute vegetmax_soil
3939    vegetmax_soil(:,:,:) = zero
3940    DO jv = 1, nvm
3941       jst = pref_soil_veg(jv)
3942       DO ji=1,kjpindex
3943          ! for veget distribution used in sechiba via humrel
3944          IF (mask_soiltile(ji,jst).GT.0 .AND. vegtot(ji) > min_sechiba) THEN
3945             vegetmax_soil(ji,jv,jst)=veget_max(ji,jv)/soiltile(ji,jst)
3946          ENDIF
3947       ENDDO
3948    ENDDO
3949
3950    ! Calculate frac_bare (previosly done in slowproc_veget)
3951    DO ji =1, kjpindex
3952       IF( veget_max(ji,1) .GT. min_sechiba ) THEN
3953          frac_bare(ji,1) = un
3954       ELSE
3955          frac_bare(ji,1) = zero
3956       ENDIF
3957    ENDDO
3958    DO jv = 2, nvm
3959       DO ji =1, kjpindex
3960          IF( veget_max(ji,jv) .GT. min_sechiba ) THEN
3961             frac_bare(ji,jv) = un - veget(ji,jv)/veget_max(ji,jv)
3962          ELSE
3963             frac_bare(ji,jv) = zero
3964          ENDIF
3965       ENDDO
3966    ENDDO
3967
3968    ! Tout dans cette routine est maintenant certainement obsolete (veget_max etant constant) en dehors des lignes
3969    ! suivantes et le calcul de frac_bare:
3970    frac_bare_ns(:,:) = zero
3971    DO jst = 1, nstm
3972       DO jv = 1, nvm
3973          DO ji =1, kjpindex
3974             IF(vegtot(ji) .GT. min_sechiba) THEN
3975                frac_bare_ns(ji,jst) = frac_bare_ns(ji,jst) + vegetmax_soil(ji,jv,jst) * frac_bare(ji,jv) / vegtot(ji)
3976             ENDIF
3977          END DO
3978       ENDDO
3979    END DO
3980   
3981    IF (printlev>=3) WRITE (numout,*) ' hydrol_vegupd done '
3982
3983  END SUBROUTINE hydrol_vegupd
3984
3985
3986!! ================================================================================================================================
3987!! SUBROUTINE   : hydrol_flood
3988!!
3989!>\BRIEF        This routine computes the evolution of the surface reservoir (floodplain). 
3990!!
3991!! DESCRIPTION  :
3992!! - 1 Take out vevapflo from the reservoir and transfer the remaining to subsinksoil
3993!! - 2 Compute the total flux from floodplain floodout (transfered to routing)
3994!! - 3 Discriminate between precip over land and over floodplain
3995!!
3996!! RECENT CHANGE(S) : None
3997!!
3998!! MAIN OUTPUT VARIABLE(S) :
3999!!
4000!! REFERENCE(S) :
4001!!
4002!! FLOWCHART    : None
4003!! \n
4004!_ ================================================================================================================================
4005!_ hydrol_flood
4006
4007  SUBROUTINE hydrol_flood (kjpindex, vevapflo, flood_frac, flood_res, floodout)
4008
4009    !! 0. Variable and parameter declaration
4010
4011    !! 0.1 Input variables
4012
4013    ! input scalar
4014    INTEGER(i_std), INTENT(in)                               :: kjpindex         !!
4015    ! input fields
4016    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: flood_frac       !! Fraction of floodplains in grid box
4017
4018    !! 0.2 Output variables
4019
4020    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: floodout         !! Flux to take out from floodplains
4021
4022    !! 0.3 Modified variables
4023
4024    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: flood_res        !! Floodplains reservoir estimate
4025    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapflo         !! Evaporation over floodplains
4026
4027    !! 0.4 Local variables
4028
4029    INTEGER(i_std)                                           :: ji, jv           !! Indices
4030    REAL(r_std), DIMENSION (kjpindex)                        :: temp             !!
4031
4032!_ ================================================================================================================================
4033    !-
4034    !! 1 Take out vevapflo from the reservoir and transfer the remaining to subsinksoil
4035    !-
4036    DO ji = 1,kjpindex
4037       temp(ji) = MIN(flood_res(ji), vevapflo(ji))
4038    ENDDO
4039    DO ji = 1,kjpindex
4040       flood_res(ji) = flood_res(ji) - temp(ji)
4041       subsinksoil(ji) = subsinksoil(ji) + vevapflo(ji) - temp(ji)
4042       vevapflo(ji) = temp(ji)
4043    ENDDO
4044
4045    !-
4046    !! 2 Compute the total flux from floodplain floodout (transfered to routing)
4047    !-
4048    DO ji = 1,kjpindex
4049       floodout(ji) = vevapflo(ji) - flood_frac(ji) * SUM(precisol(ji,:))
4050    ENDDO
4051
4052    !-
4053    !! 3 Discriminate between precip over land and over floodplain
4054    !-
4055    DO jv=1, nvm
4056       DO ji = 1,kjpindex
4057          precisol(ji,jv) = precisol(ji,jv) * (1 - flood_frac(ji))
4058       ENDDO
4059    ENDDO 
4060
4061    IF (printlev>=3) WRITE (numout,*) ' hydrol_flood done'
4062
4063  END SUBROUTINE hydrol_flood
4064
4065
4066!! ================================================================================================================================
4067!! SUBROUTINE   : hydrol_soil
4068!!
4069!>\BRIEF        This routine computes soil processes with CWRR scheme (Richards equation solved by finite differences).
4070!! Note that the water fluxes are in kg/m2/dt_sechiba.
4071!!
4072!! DESCRIPTION  :
4073!! 0. Initialisation, and split 2d variables to 3d variables, per soil tile
4074!! -- START MAIN LOOP (prognostic loop to update mc and mcl) OVER SOILTILES
4075!! 1. FIRSTLY, WE CHANGE MC BASED ON EXTERNAL FLUXES, ALL APPLIED AT THE SOIL SURFACE
4076!! 1.1 Reduces water2infilt and water2extract to their difference
4077!! 1.2 To remove water2extract (including bare soilevaporation) from top layer
4078!! 1.3 Infiltration
4079!! 1.4 Reinfiltration of surface runoff : compute temporary surface water and extract from runoff
4080!! 2. SECONDLY, WE UPDATE MC FROM DIFFUSION, INCLUDING DRAINAGE AND ROOTSINK
4081!!    This will act on mcl (liquid water content) only
4082!! 2.1 K and D are recomputed after infiltration
4083!! 2.2 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
4084!! 2.3 We define mcl (liquid water content) based on mc and profil_froz_hydro_ns
4085!! 2.4 We calculate the total SM at the beginning of the routine tridiag for water conservation check
4086!! 2.5 Defining where diffusion is solved : everywhere
4087!! 2.6 We define the system of linear equations for mcl redistribution
4088!! 2.7 Solves diffusion equations
4089!! 2.8 Computes drainage = bottom boundary condition, consistent with rhs(ji,jsl=nslm)
4090!! 2.9 For water conservation check during redistribution, we calculate the total liquid SM
4091!!     at the end of the routine tridiag, and we compare the difference with the flux...
4092!! 3. AFTER DIFFUSION/REDISTRIBUTION
4093!! 3.1 Updating mc, as all the following checks against saturation will compare mc to mcs
4094!! 3.2 Correct here the possible over-saturation values (subroutine hydrol_soil_smooth_over_mcs2 acts on mc)
4095!!     Here hydrol_soil_smooth_over_mcs2 discard all excess as ru_corr_ns, oriented to either ru_ns or dr_ns
4096!! 3.3 Negative runoff is reported to drainage
4097!! 3.4 Optional block to force saturation below zwt_force
4098!! 3.5 Diagnosing the effective water table depth
4099!! 3.6 Diagnose under_mcr to adapt water stress calculation below
4100!! 4. At the end of the prognostic calculations, we recompute important moisture variables
4101!! 4.1 Total soil moisture content (water2infilt added below)
4102!! 4.2 mcl is a module variable; we update it here for calculating bare soil evaporation,
4103!! 5. Optional check of the water balance of soil column (if check_cwrr)
4104!! 5.1 Computation of the vertical water fluxes
4105!! 5.2 Total mc conservation
4106!! 5.3 Total mc should not reach zero, or the tridiag solver will have problems
4107!! 6. SM DIAGNOSTICS FOR OTHER ROUTINES, MODULES, OR NEXT STEP
4108!! 6.1 Total soil moisture, soil moisture at litter levels, soil wetness, us, humrelv, vesgtressv
4109!! 6.2 We need to turn off evaporation when is_under_mcr
4110!! 6.3 Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in thermosoil
4111!! 6.4 The hydraulic conductivities exported here are the ones used in the diffusion/redistribution
4112!! -- ENDING THE MAIN LOOP ON SOILTILES
4113!! 7. Summing 3d variables into 2d variables
4114!! 8. XIOS export of local variables, including water conservation checks
4115!! 9. COMPUTING EVAP_BARE_LIM_NS FOR NEXT TIME STEP, WITH A LOOP ON SOILTILES
4116!!    The principle is to run a dummy integration of the water redistribution scheme
4117!!    to check if the SM profile can sustain a potential evaporation.
4118!!    If not, the dummy integration is redone from the SM profile of the end of the normal integration,
4119!!    with a boundary condition leading to a very severe water limitation: mc(1)=mcr
4120!! 10. evap_bar_lim is the grid-cell scale beta
4121!! 11. Exit if error was found previously in this subroutine
4122!!
4123!! RECENT CHANGE(S) : 2016 by A. Ducharne
4124!!
4125!! MAIN OUTPUT VARIABLE(S) :
4126!!
4127!! REFERENCE(S) :
4128!!
4129!! FLOWCHART    : None
4130!! \n
4131!_ ================================================================================================================================
4132!_ hydrol_soil
4133
4134  SUBROUTINE hydrol_soil (kjpindex, veget_max, soiltile, njsc, reinf_slope, &
4135       & transpir, vevapnu, evapot, evapot_penm, runoff, drainage, &
4136       & returnflow, reinfiltration, irrigation, &
4137       & tot_melt, evap_bare_lim, shumdiag, shumdiag_perma,&
4138       & k_litt, litterhumdiag, humrel,vegstress, drysoil_frac, &
4139       & stempdiag,snow, &
4140       & snowdz, tot_bare_soil, u, v, tq_cdrag, mc_layh, mcl_layh)
4141    !
4142    ! interface description
4143
4144    !! 0. Variable and parameter declaration
4145
4146    !! 0.1 Input variables
4147
4148    INTEGER(i_std), INTENT(in)                               :: kjpindex 
4149    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: veget_max        !! Map of max vegetation types [-]
4150    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc             !! Index of the dominant soil textural class
4151                                                                                 !!   in the grid cell (1-nscm, unitless)
4152    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
4153    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: transpir         !! Transpiration 
4154                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4155    REAL(r_std), DIMENSION (kjpindex), INTENT (in)           :: reinf_slope      !! Fraction of surface runoff that reinfiltrates
4156                                                                                 !!  (unitless, [0-1])
4157    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow       !! Water returning to the soil from the bottom
4158                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4159    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: reinfiltration   !! Water returning to the top of the soil
4160                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4161    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: irrigation       !! Irrigation
4162                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4163    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot           !! Potential evaporation
4164                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4165    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot_penm      !! Potential evaporation "Penman" (Milly's correction)
4166                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4167    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_melt         !! Total melt from snow and ice
4168                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4169    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in)       :: stempdiag        !! Diagnostic temp profile from thermosoil
4170    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: snow             !! Snow mass
4171                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4172    REAL(r_std), DIMENSION (kjpindex,nsnow),INTENT(in)       :: snowdz           !! Snow depth (m)
4173    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_bare_soil    !! Total evaporating bare soil fraction
4174                                                                                 !!  (unitless, [0-1])
4175    REAL(r_std),DIMENSION (kjpindex), INTENT(in)             :: u,v              !! Horizontal wind speed
4176    REAL(r_std),DIMENSION (kjpindex), INTENT(in)             :: tq_cdrag         !! Surface drag coefficient
4177
4178    !! 0.2 Output variables
4179
4180    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: runoff           !! Surface runoff
4181                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4182    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drainage         !! Drainage
4183                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4184    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: evap_bare_lim    !! Limitation factor (beta) for bare soil evaporation 
4185                                                                                 !! on each soil column (unitless, [0-1])
4186    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: shumdiag         !! Relative soil moisture in each diag soil layer
4187                                                                                 !! with respect to (mcfc-mcw) (unitless, [0-1])
4188    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: shumdiag_perma   !! Percent of porosity filled with water (mc/mcs)
4189                                                                                 !! in each diag soil layer (for the thermal computations)
4190                                                                                 !! (unitless, [0-1])
4191    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: k_litt           !! Litter approximated hydraulic conductivity
4192                                                                                 !!  @tex $(mm d^{-1})$ @endtex
4193    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: litterhumdiag    !! Mean of soil_wet_litter across soil tiles
4194                                                                                 !! (unitless, [0-1])
4195    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(out)      :: vegstress        !! Veg. moisture stress (only for vegetation
4196                                                                                 !! growth) (unitless, [0-1])
4197    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: drysoil_frac     !! Function of the litter humidity
4198    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: mc_layh          !! Volumetric water content (liquid + ice) for each soil layer
4199                                                                                 !! averaged over the mesh (for thermosoil)
4200                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
4201    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: mcl_layh         !! Volumetric liquid water content for each soil layer
4202                                                                                 !! averaged over the mesh (for thermosoil)
4203                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
4204
4205    !! 0.3 Modified variables
4206
4207    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapnu          !! Bare soil evaporation
4208                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4209    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (inout)    :: humrel           !! Relative humidity (0-1, dimensionless)
4210
4211    !! 0.4 Local variables
4212
4213    INTEGER(i_std)                                 :: ji, jv, jsl, jst           !! Indices
4214    REAL(r_std), PARAMETER                         :: frac_mcs = 0.66            !! Temporary depth
4215    REAL(r_std), DIMENSION(kjpindex)               :: temp                       !! Temporary value for fluxes
4216    REAL(r_std), DIMENSION(kjpindex)               :: tmcold                     !! Total SM at beginning of hydrol_soil (kg/m2)
4217    REAL(r_std), DIMENSION(kjpindex)               :: tmcint                     !! Ancillary total SM (kg/m2)
4218    REAL(r_std), DIMENSION(kjpindex,nslm)          :: mcint                      !! To save mc values for future use
4219    REAL(r_std), DIMENSION(kjpindex,nslm)          :: mclint                     !! To save mcl values for future use
4220    LOGICAL, DIMENSION(kjpindex,nstm)              :: is_under_mcr               !! Identifies under residual soil moisture points
4221    LOGICAL, DIMENSION(kjpindex)                   :: is_over_mcs                !! Identifies over saturated soil moisture points
4222    REAL(r_std), DIMENSION(kjpindex)               :: deltahum,diff              !!
4223    LOGICAL(r_std), DIMENSION(kjpindex)            :: test                       !!
4224    REAL(r_std), DIMENSION(kjpindex)               :: water2extract              !! Water flux to be extracted at the soil surface
4225                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4226    REAL(r_std), DIMENSION(kjpindex)               :: returnflow_soil            !! Water from the routing back to the bottom of
4227                                                                                 !! the soil @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4228    REAL(r_std), DIMENSION(kjpindex)               :: reinfiltration_soil        !! Water from the routing back to the top of the
4229                                                                                 !! soil @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4230    REAL(r_std), DIMENSION(kjpindex)               :: irrigation_soil            !! Water from irrigation returning to soil moisture
4231                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4232    REAL(r_std), DIMENSION(kjpindex)               :: flux_infilt                !! Water to infiltrate
4233                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4234    REAL(r_std), DIMENSION(kjpindex)               :: flux_bottom                !! Flux at bottom of the soil column
4235                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4236    REAL(r_std), DIMENSION(kjpindex)               :: flux_top                   !! Flux at top of the soil column (for bare soil evap)
4237                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4238    REAL(r_std), DIMENSION (kjpindex,nstm)         :: qinfilt_ns                 !! Effective infiltration flux per soil tile
4239                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
4240    REAL(r_std), DIMENSION (kjpindex)              :: qinfilt                    !! Effective infiltration flux 
4241                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4242    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_infilt_ns               !! Surface runoff from hydrol_soil_infilt per soil tile
4243                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
4244    REAL(r_std), DIMENSION (kjpindex)              :: ru_infilt                  !! Surface runoff from hydrol_soil_infilt
4245                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4246    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_corr_ns                 !! Surface runoff produced to correct excess per soil tile
4247                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4248    REAL(r_std), DIMENSION (kjpindex)              :: ru_corr                    !! Surface runoff produced to correct excess
4249                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex 
4250    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_corr2_ns                !! Correction of negative surface runoff per soil tile
4251                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4252    REAL(r_std), DIMENSION (kjpindex)              :: ru_corr2                   !! Correction of negative surface runoff
4253                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4254    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_corr_ns                 !! Drainage produced to correct excess
4255                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4256    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_corrnum_ns              !! Drainage produced to correct numerical errors in tridiag
4257                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
4258    REAL(r_std), DIMENSION (kjpindex)              :: dr_corr                    !! Drainage produced to correct excess
4259                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4260    REAL(r_std), DIMENSION (kjpindex)              :: dr_corrnum                 !! Drainage produced to correct numerical errors in tridiag
4261                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
4262    REAL(r_std), DIMENSION (kjpindex,nslm)         :: dmc                        !! Delta mc when forcing saturation (zwt_force)
4263                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
4264    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_force_ns                !! Delta drainage when forcing saturation (zwt_force)
4265                                                                                 !!  per soil tile  @tex $(kg m^{-2})$ @endtex
4266    REAL(r_std), DIMENSION (kjpindex)              :: dr_force                   !! Delta drainage when forcing saturation (zwt_force)
4267                                                                                 !!  @tex $(kg m^{-2})$ @endtex 
4268    REAL(r_std), DIMENSION (kjpindex,nstm)         :: wtd_ns                     !! Effective water table depth (m)
4269    REAL(r_std), DIMENSION (kjpindex)              :: wtd                        !! Mean water table depth in the grid-cell (m)
4270    LOGICAL                                        :: error=.FALSE.              !! If true, exit in the end of subroutine
4271
4272    ! For the calculation of soil_wet_ns and us/humrel/vegstress
4273    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sm                         !! Soil moisture of each layer (liquid phase)
4274                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4275    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smt                        !! Soil moisture of each layer (liquid+solid phase)
4276                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4277    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smw                        !! Soil moisture of each layer at wilting point
4278                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4279    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smf                        !! Soil moisture of each layer at field capacity
4280                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
4281    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sms                        !! Soil moisture of each layer at saturation
4282                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4283    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sm_nostress                !! Soil moisture of each layer at which us reaches 1
4284                                                                                 !!  @tex $(kg m^{-2})$ @endtex
4285    ! For water conservation checks (in mm/dtstep unless otherwise mentioned)
4286    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_infilt_ns             !! Water conservation diagnostic at routine scale
4287    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check1_ns                   !! Water conservation diagnostic at routine scale
4288    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_tr_ns                 !! Water conservation diagnostic at routine scale
4289    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_over_ns               !! Water conservation diagnostic at routine scale
4290    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_under_ns              !! Water conservation diagnostic at routine scale
4291    REAL(r_std), DIMENSION(kjpindex)               :: tmci                        !! Total soil moisture at beginning of routine (kg/m2)
4292    REAL(r_std), DIMENSION(kjpindex)               :: tmcf                        !! Total soil moisture at end of routine (kg/m2)
4293    REAL(r_std), DIMENSION(kjpindex)               :: diag_tr                     !! Transpiration flux
4294    REAL(r_std), DIMENSION (kjpindex)              :: check_infilt                !! Water conservation diagnostic at routine scale
4295    REAL(r_std), DIMENSION (kjpindex)              :: check1                      !! Water conservation diagnostic at routine scale
4296    REAL(r_std), DIMENSION (kjpindex)              :: check_tr                    !! Water conservation diagnostic at routine scale
4297    REAL(r_std), DIMENSION (kjpindex)              :: check_over                  !! Water conservation diagnostic at routine scale
4298    REAL(r_std), DIMENSION (kjpindex)              :: check_under                 !! Water conservation diagnostic at routine scale
4299
4300    ! Variables for calculation of a soil resistance, option do_rsoil (following the formulation of Sellers et al 1992, implemented in Oleson et al. 2008)
4301    REAL(r_std)                                    :: speed                      !! magnitude of wind speed required for Aerodynamic resistance
4302    REAL(r_std)                                    :: ra                         !! diagnosed aerodynamic resistance
4303    REAL(r_std), DIMENSION(kjpindex)               :: mc_rel                     !! first layer relative soil moisture, required for rsoil
4304    REAL(r_std), DIMENSION(kjpindex)               :: evap_soil                  !! soil evaporation from Oleson et al 2008
4305    REAL(r_std), DIMENSION(kjpindex,nstm)          :: r_soil_ns                  !! soil resistance from Oleson et al 2008
4306    REAL(r_std), DIMENSION(kjpindex)               :: r_soil                     !! soil resistance from Oleson et al 2008
4307    REAL(r_std), DIMENSION(kjpindex)               :: tmcs_litter                !! Saturated soil moisture in the 4 "litter" soil layers
4308    REAL(r_std), DIMENSION(nslm)                   :: nroot_tmp                  !! Temporary variable to calculate the nroot
4309
4310    ! For CMIP6 and SP-MIP : ksat and matric pressure head psi(theta)
4311    REAL(r_std)                                    :: mc_ratio, mvg, avg
4312    REAL(r_std)                                    :: psi                        !! Matric head (per soil layer and soil tile) [mm=kg/m2]
4313    REAL(r_std), DIMENSION (kjpindex,nslm)         :: psi_moy                    !! Mean matric head per soil layer [mm=kg/m2] 
4314    REAL(r_std), DIMENSION (kjpindex,nslm)         :: ksat                       !! Saturated hydraulic conductivity at each node (mm/d) 
4315
4316!_ ================================================================================================================================
4317
4318    !! 0.1 Arrays with DIMENSION(kjpindex)
4319   
4320    returnflow_soil(:) = zero
4321    reinfiltration_soil(:) = zero
4322    irrigation_soil(:) = zero
4323    qflux(:,:,:) = zero
4324    mc_layh(:,:) = zero ! for thermosoil
4325    mcl_layh(:,:) = zero ! for thermosoil
4326    kk(:,:,:) = zero
4327    kk_moy(:,:) = zero
4328    undermcr(:) = zero ! needs to be initialized outside from jst loop
4329    ksat(:,:) = zero
4330    psi_moy(:,:) = zero
4331
4332    IF (ok_freeze_cwrr) THEN
4333       
4334       ! 0.1 Calculate the temperature and fozen fraction at the hydrological levels
4335       
4336       ! AD16*** This subroutine could probably be simplified massively given
4337       ! that hydro and T share the same vertical discretization
4338       ! Here stempdiag is in from thermosoil and temp_hydro is out
4339       CALL hydrol_calculate_temp_hydro(kjpindex, stempdiag, snow,snowdz)
4340       
4341       ! Calculates profil_froz_hydro_ns as a function of temp_hydro, and mc if ok_thermodynamical_freezing
4342       ! These values will be kept till the end of the prognostic loop
4343       DO jst=1,nstm
4344          CALL hydrol_soil_froz(kjpindex,jst,njsc)
4345       ENDDO
4346
4347    ELSE
4348 
4349       profil_froz_hydro_ns(:,:,:) = zero
4350             
4351    ENDIF
4352   
4353    !! 0.2 Split 2d variables to 3d variables, per soil tile
4354    !  Here, the evaporative fluxes are distributed over the soiltiles as a function of the
4355    !    corresponding control factors; they are normalized to vegtot
4356    !  At step 7, the reverse transformation is used for the fluxes produced in hydrol_soil
4357    !    flux_cell(ji)=sum(flux_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji))
4358    CALL hydrol_split_soil (kjpindex, veget_max, soiltile, vevapnu, transpir, humrel, evap_bare_lim, tot_bare_soil)
4359   
4360    !! 0.3 Common variables related to routing, with all return flow applied to the soil surface
4361    ! The fluxes coming from the routing are uniformly splitted into the soiltiles,
4362    !    but are normalized to vegtot like the above fluxes:
4363    !            flux_ns(ji,jst)=flux_cell(ji)/vegtot(ji)
4364    ! It is the case for : irrigation_soil(ji) and reinfiltration_soil(ji) cf below
4365    ! It is also the case for subsinksoil(ji), which is divided by (1-tot_frac_nobio) at creation in hydrol_snow
4366    ! AD16*** The transformation in 0.2 and 0.3 is likely to induce conservation problems
4367    !         when tot_frac_nobio NE 0, since sum(soiltile) NE vegtot in this case
4368   
4369    DO ji=1,kjpindex
4370       IF(vegtot(ji).GT.min_sechiba) THEN
4371          ! returnflow_soil is assumed to enter from the bottom, but it is not possible with CWRR
4372          returnflow_soil(ji) = zero
4373          reinfiltration_soil(ji) = (returnflow(ji) + reinfiltration(ji))/vegtot(ji)
4374          irrigation_soil(ji) = irrigation(ji)/vegtot(ji)
4375       ELSE
4376          returnflow_soil(ji) = zero
4377          reinfiltration_soil(ji) = zero
4378          irrigation_soil(ji) = zero
4379       ENDIF
4380    ENDDO       
4381   
4382    !! -- START MAIN LOOP (prognostic loop to update mc and mcl) OVER SOILTILES
4383    !!    The called subroutines work on arrays with DIMENSION(kjpindex),
4384    !!    recursively used for each soiltile jst
4385   
4386    DO jst = 1,nstm
4387
4388       is_under_mcr(:,jst) = .FALSE.
4389       is_over_mcs(:) = .FALSE.
4390       
4391       !! 0.4. Keep initial values for future check-up
4392       
4393       ! Total moisture content (including water2infilt) is saved for balance checks at the end
4394       ! In hydrol_tmc_update, tmc is increased by water2infilt(ji,jst), but mc is not modified !
4395       tmcold(:) = tmc(:,jst)
4396       
4397       ! The value of mc is kept in mcint (nstm dimension removed), in case needed for water balance checks
4398       DO jsl = 1, nslm
4399          DO ji = 1, kjpindex
4400             mcint(ji,jsl) = mask_soiltile(ji,jst) * mc(ji,jsl,jst)
4401          ENDDO
4402       ENDDO
4403       !
4404       ! Initial total moisture content : tmcint does not include water2infilt, contrarily to tmcold
4405       DO ji = 1, kjpindex
4406          tmcint(ji) = dz(2) * ( trois*mcint(ji,1) + mcint(ji,2) )/huit 
4407       ENDDO
4408       DO jsl = 2,nslm-1
4409          DO ji = 1, kjpindex
4410             tmcint(ji) = tmcint(ji) + dz(jsl) &
4411                  & * (trois*mcint(ji,jsl)+mcint(ji,jsl-1))/huit &
4412                  & + dz(jsl+1) * (trois*mcint(ji,jsl)+mcint(ji,jsl+1))/huit
4413          ENDDO
4414       ENDDO
4415       DO ji = 1, kjpindex
4416          tmcint(ji) = tmcint(ji) + dz(nslm) &
4417               & * (trois * mcint(ji,nslm) + mcint(ji,nslm-1))/huit
4418       ENDDO
4419
4420       !! 1. FIRSTLY, WE CHANGE MC BASED ON EXTERNAL FLUXES, ALL APPLIED AT THE SOIL SURFACE
4421       !!   Input = water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) + precisol_ns(ji,jst)
4422       !!      - negative evaporation fluxes (MIN(ae_ns(ji,jst),zero)+ MIN(subsinksoil(ji),zero))
4423       !!   Output = MAX(ae_ns(ji,jst),zero) + subsinksoil(ji) = positive evaporation flux = water2extract
4424       ! In practice, negative subsinksoil(ji) is not possible
4425
4426       !! 1.1 Reduces water2infilt and water2extract to their difference
4427
4428       ! Compares water2infilt and water2extract to keep only difference
4429       ! Here, temp is used as a temporary variable to store the min of water to infiltrate vs evaporate
4430       DO ji = 1, kjpindex
4431          temp(ji) = MIN(water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) &
4432                         - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst), &
4433                           MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) )
4434       ENDDO
4435
4436       ! The water to infiltrate at the soil surface is either 0, or the difference to what has to be evaporated
4437       !   - the initial water2infilt (right hand side) results from qsintveg changes with vegetation updates
4438       !   - irrigation_soil is the input flux to the soil surface from irrigation
4439       !   - reinfiltration_soil is the input flux to the soil surface from routing 'including returnflow)
4440       !   - eventually, water2infilt holds all fluxes to the soil surface except precisol (reduced by water2extract)
4441       DO ji = 1, kjpindex
4442          water2infilt(ji,jst) = water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) &
4443                - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst) &
4444                - temp(ji) 
4445       ENDDO       
4446             
4447       ! The water to evaporate from the sol surface is either the difference to what has to be infiltrated, or 0
4448       !   - subsinksoil is the residual from sublimation is the snowpack is not sufficient
4449       !   - how are the negative values of ae_ns taken into account ???
4450       DO ji = 1, kjpindex
4451          water2extract(ji) =  MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) - temp(ji) 
4452       ENDDO
4453
4454       ! Here we acknowledge that subsinksoil is part of ae_ns, but ae_ns is not used further
4455       ae_ns(:,jst) = ae_ns(:,jst) + subsinksoil(:) 
4456
4457       !! 1.2 To remove water2extract (including bare soil) from top layer
4458       flux_top(:) = water2extract(:)
4459
4460       !! 1.3 Infiltration
4461
4462       !! Definition of flux_infilt
4463       DO ji = 1, kjpindex
4464          ! Initialise the flux to be infiltrated 
4465          flux_infilt(ji) = water2infilt(ji,jst) 
4466       ENDDO
4467       
4468       !! K and D are computed for the profile of mc before infiltration
4469       !! They depend on the fraction of soil ice, given by profil_froz_hydro_ns
4470       CALL hydrol_soil_coef(kjpindex,jst,njsc)
4471
4472       !! Infiltration and surface runoff are computed
4473       !! Infiltration stems from comparing liquid water2infilt to initial total mc (liquid+ice)
4474       !! The conductivity comes from hydrol_soil_coef and relates to the liquid phase only
4475       !  This seems consistent with ok_freeze
4476       CALL hydrol_soil_infilt(kjpindex, jst, njsc, flux_infilt, qinfilt_ns, ru_infilt_ns, &
4477            check_infilt_ns)
4478       ru_ns(:,jst) = ru_infilt_ns(:,jst) 
4479
4480       !! 1.4 Reinfiltration of surface runoff : compute temporary surface water and extract from runoff
4481       ! Evrything here is liquid
4482       ! RK: water2infilt is both a volume for future reinfiltration (in mm) and a correction term for surface runoff (in mm/dt_sechiba)
4483       IF ( .NOT. doponds ) THEN ! this is the general case...
4484          DO ji = 1, kjpindex
4485             water2infilt(ji,jst) = reinf_slope(ji) * ru_ns(ji,jst)
4486          ENDDO
4487       ELSE
4488          DO ji = 1, kjpindex           
4489             water2infilt(ji,jst) = zero
4490          ENDDO
4491       ENDIF
4492       !
4493       DO ji = 1, kjpindex           
4494          ru_ns(ji,jst) = ru_ns(ji,jst) - water2infilt(ji,jst)
4495       END DO
4496
4497       !! 2. SECONDLY, WE UPDATE MC FROM DIFFUSION, INCLUDING DRAINAGE AND ROOTSINK
4498       !!    This will act on mcl only
4499       
4500       !! 2.1 K and D are recomputed after infiltration
4501       !! They depend on the fraction of soil ice, still given by profil_froz_hydro_ns
4502       CALL hydrol_soil_coef(kjpindex,jst,njsc)
4503 
4504       !! 2.2 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
4505       !! This process will further act on mcl only, based on a, b, d from hydrol_soil_coef
4506       CALL hydrol_soil_setup(kjpindex,jst)
4507
4508       !! 2.3 We define mcl (liquid water content) based on mc and profil_froz_hydro_ns
4509       DO jsl = 1, nslm
4510          DO ji =1, kjpindex
4511             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(njsc(ji)) + &
4512                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
4513             ! we always have mcl<=mc
4514             ! if mc>mcr, then mcl>mcr; if mc=mcr,mcl=mcr; if mc<mcr, then mcl<mcr
4515             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
4516          ENDDO
4517       ENDDO
4518
4519       ! The value of mcl is kept in mclint (nstm dimension removed), used in the flux computation after diffusion
4520       DO jsl = 1, nslm
4521          DO ji = 1, kjpindex
4522             mclint(ji,jsl) = mask_soiltile(ji,jst) * mcl(ji,jsl,jst)
4523          ENDDO
4524       ENDDO
4525
4526       !! 2.3bis Diagnostic of the matric potential used for redistribution by Richards/tridiag (in m)
4527       !  We use VG relationship giving psi as a function of mc (mcl in our case)
4528       !  With patches against numerical pbs when (mc_ratio - un) becomes very slightly negative (gives NaN)
4529       !  or if psi become too strongly negative (pbs with xios output)
4530       DO jsl=1, nslm
4531          DO ji = 1, kjpindex
4532             IF (soiltile(ji,jst) .GT. zero) THEN
4533                mvg = un - un / nvan_mod_tab(jsl,njsc(ji))
4534                avg = avan_mod_tab(jsl,njsc(ji))*1000. ! to convert in m-1
4535                mc_ratio = MAX( 10.**(-14*mvg), (mcl(ji,jsl,jst) - mcr(njsc(ji)))/(mcs(njsc(ji)) - mcr(njsc(ji))) )**(-un/mvg)
4536                psi = - MAX(zero,(mc_ratio - un))**(un/nvan_mod_tab(jsl,njsc(ji))) / avg ! in m
4537                psi_moy(ji,jsl) = psi_moy(ji,jsl) + soiltile(ji,jst) * psi ! average across soil tiles
4538             ENDIF
4539          ENDDO
4540       ENDDO
4541
4542       !! 2.4 We calculate the total SM at the beginning of the routine tridiag for water conservation check
4543       !  (on mcl only, since the diffusion only modifies mcl)
4544       tmci(:) = dz(2) * ( trois*mcl(:,1,jst) + mcl(:,2,jst) )/huit
4545       DO jsl = 2,nslm-1
4546          tmci(:) = tmci(:) + dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
4547               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
4548       ENDDO
4549       tmci(:) = tmci(:) + dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit
4550
4551       !! 2.5 Defining where diffusion is solved : everywhere
4552       !! Since mc>mcs is not possible after infiltration, and we accept that mc<mcr
4553       !! (corrected later by shutting off all evaporative fluxes in this case)
4554       !  Nothing is done if resolv=F
4555       resolv(:) = (mask_soiltile(:,jst) .GT. 0)
4556
4557       !! 2.6 We define the system of linear equations for mcl redistribution,
4558       !! based on the matrix coefficients from hydrol_soil_setup
4559       !! following the PhD thesis of de Rosnay (1999), p155-157
4560       !! The bare soil evaporation (subtracted from infiltration) is used directly as flux_top
4561       ! rhs for right-hand side term; fp for f'; gp for g'; ep for e'; with flux=0 !
4562       
4563       !- First layer
4564       DO ji = 1, kjpindex
4565          tmat(ji,1,1) = zero
4566          tmat(ji,1,2) = f(ji,1)
4567          tmat(ji,1,3) = g1(ji,1)
4568          rhs(ji,1)    = fp(ji,1) * mcl(ji,1,jst) + gp(ji,1)*mcl(ji,2,jst) &
4569               &  - flux_top(ji) - (b(ji,1)+b(ji,2))/deux *(dt_sechiba/one_day) - rootsink(ji,1,jst)
4570       ENDDO
4571       !- soil body
4572       DO jsl=2, nslm-1
4573          DO ji = 1, kjpindex
4574             tmat(ji,jsl,1) = e(ji,jsl)
4575             tmat(ji,jsl,2) = f(ji,jsl)
4576             tmat(ji,jsl,3) = g1(ji,jsl)
4577             rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
4578                  & +  gp(ji,jsl) * mcl(ji,jsl+1,jst) & 
4579                  & + (b(ji,jsl-1) - b(ji,jsl+1)) * (dt_sechiba/one_day) / deux & 
4580                  & - rootsink(ji,jsl,jst) 
4581          ENDDO
4582       ENDDO       
4583       !- Last layer, including drainage
4584       DO ji = 1, kjpindex
4585          jsl=nslm
4586          tmat(ji,jsl,1) = e(ji,jsl)
4587          tmat(ji,jsl,2) = f(ji,jsl)
4588          tmat(ji,jsl,3) = zero
4589          rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
4590               & + (b(ji,jsl-1) + b(ji,jsl)*(un-deux*free_drain_coef(ji,jst))) * (dt_sechiba/one_day) / deux &
4591               & - rootsink(ji,jsl,jst)
4592       ENDDO
4593       !- Store the equations in case needed again
4594       DO jsl=1,nslm
4595          DO ji = 1, kjpindex
4596             srhs(ji,jsl) = rhs(ji,jsl)
4597             stmat(ji,jsl,1) = tmat(ji,jsl,1)
4598             stmat(ji,jsl,2) = tmat(ji,jsl,2)
4599             stmat(ji,jsl,3) = tmat(ji,jsl,3) 
4600          ENDDO
4601       ENDDO
4602       
4603       !! 2.7 Solves diffusion equations, but only in grid-cells where resolv is true, i.e. everywhere (cf 2.2)
4604       !!     The result is an updated mcl profile
4605
4606       CALL hydrol_soil_tridiag(kjpindex,jst)
4607
4608       !! 2.8 Computes drainage = bottom boundary condition, consistent with rhs(ji,jsl=nslm)
4609       ! dr_ns in mm/dt_sechiba, from k in mm/d
4610       ! This should be done where resolv=T, like tridiag (drainage is part of the linear system !)
4611       DO ji = 1, kjpindex
4612          IF (resolv(ji)) THEN
4613             dr_ns(ji,jst) = mask_soiltile(ji,jst)*k(ji,nslm)*free_drain_coef(ji,jst) * (dt_sechiba/one_day)
4614          ELSE
4615             dr_ns(ji,jst) = zero
4616          ENDIF
4617       ENDDO
4618
4619       !! 2.9 For water conservation check during redistribution AND CORRECTION,
4620       !!     we calculate the total liquid SM at the end of the routine tridiag
4621       tmcf(:) = dz(2) * ( trois*mcl(:,1,jst) + mcl(:,2,jst) )/huit
4622       DO jsl = 2,nslm-1
4623          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
4624               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
4625       ENDDO
4626       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit
4627         
4628       !! And we compare the difference with the flux...
4629       ! Normally, tcmf=tmci-flux_top(ji)-transpir-dr_ns
4630       DO ji=1,kjpindex
4631          diag_tr(ji)=SUM(rootsink(ji,:,jst))
4632       ENDDO
4633       ! Here, check_tr_ns holds the inaccuracy during the redistribution phase
4634       check_tr_ns(:,jst) = tmcf(:)-(tmci(:)-flux_top(:)-dr_ns(:,jst)-diag_tr(:))
4635
4636       !! We solve here the numerical errors that happen when the soil is close to saturation
4637       !! and drainage very high, and which lead to negative check_tr_ns: the soil dries more
4638       !! than what is demanded by the fluxes, so we need to increase the fluxes.
4639       !! This is done by increasing the drainage.
4640       !! There are also instances of positive check_tr_ns, larger when the drainage is high
4641       !! They are similarly corrected by a decrease of dr_ns, in the limit of keeping a positive drainage.
4642       DO ji=1,kjpindex
4643          IF ( check_tr_ns(ji,jst) .LT. zero ) THEN
4644              dr_corrnum_ns(ji,jst) = -check_tr_ns(ji,jst)
4645          ELSE
4646              dr_corrnum_ns(ji,jst) = -MIN(dr_ns(ji,jst),check_tr_ns(ji,jst))             
4647          ENDIF
4648          dr_ns(ji,jst) = dr_ns(ji,jst) + dr_corrnum_ns(ji,jst) ! dr_ns increases/decrease if check_tr negative/positive
4649       ENDDO
4650       !! For water conservation check during redistribution
4651       IF (check_cwrr2) THEN         
4652          check_tr_ns(:,jst) = tmcf(:)-(tmci(:)-flux_top(:)-dr_ns(:,jst)-diag_tr(:)) 
4653       ENDIF
4654
4655       !! 3. AFTER DIFFUSION/REDISTRIBUTION
4656
4657       !! 3.1 Updating mc, as all the following checks against saturation will compare mc to mcs
4658       !      The frozen fraction is constant, so that any water flux to/from a layer changes
4659       !      both mcl and the ice amount. The assumption behind this is that water entering/leaving
4660       !      a soil layer immediately freezes/melts with the proportion profil_froz_hydro_ns/(1-profil_...)
4661       DO jsl = 1, nslm
4662          DO ji =1, kjpindex
4663             mc(ji,jsl,jst) = MAX( mcl(ji,jsl,jst), mcl(ji,jsl,jst) + &
4664                  profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
4665             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we get mc=mcl
4666          ENDDO
4667       ENDDO
4668
4669       !! 3.2 Correct here the possible over-saturation values (subroutine hydrol_soil_smooth_over_mcs2 acts on mc)
4670       !    Oversaturation results from numerical inaccuracies and can be frequent if free_drain_coef=0
4671       !    Here hydrol_soil_smooth_over_mcs2 discard all excess as ru_corr_ns, oriented to either ru_ns or dr_ns
4672       !    The former routine hydrol_soil_smooth_over_mcs, which keeps most of the excess in the soiltile
4673       !    after smoothing, first downward then upward, is kept in the module but not used here
4674       dr_corr_ns(:,jst) = zero
4675       ru_corr_ns(:,jst) = zero
4676       call hydrol_soil_smooth_over_mcs2(kjpindex, jst, njsc, is_over_mcs, ru_corr_ns, check_over_ns)
4677       
4678       ! In absence of freezing, if F is large enough, the correction of oversaturation is sent to drainage       
4679       DO ji = 1, kjpindex
4680          IF ((free_drain_coef(ji,jst) .GE. 0.5) .AND. (.NOT. ok_freeze_cwrr) ) THEN
4681             dr_corr_ns(ji,jst) = ru_corr_ns(ji,jst) 
4682             ru_corr_ns(ji,jst) = zero
4683          ENDIF
4684       ENDDO
4685       dr_ns(:,jst) = dr_ns(:,jst) + dr_corr_ns(:,jst)
4686       ru_ns(:,jst) = ru_ns(:,jst) + ru_corr_ns(:,jst)
4687
4688       !! 3.3 Negative runoff is reported to drainage
4689       !  Since we computed ru_ns directly from hydrol_soil_infilt, ru_ns should not be negative
4690             
4691       ru_corr2_ns(:,jst) = zero
4692       DO ji = 1, kjpindex
4693          IF (ru_ns(ji,jst) .LT. zero) THEN
4694             IF (printlev>=3)  WRITE (numout,*) 'NEGATIVE RU_NS: runoff and drainage before correction',&
4695                  ru_ns(ji,jst),dr_ns(ji,jst)
4696             dr_ns(ji,jst)=dr_ns(ji,jst)+ru_ns(ji,jst)
4697             ru_corr2_ns(ji,jst) = -ru_ns(ji,jst)
4698             ru_ns(ji,jst)= 0.
4699          END IF         
4700       ENDDO
4701
4702       !! 3.4 Optional block to force saturation below zwt_force
4703       ! This block is not compatible with freezing; in this case, mcl must be corrected too
4704       ! We test if zwt_force(1,jst) <= zmaxh, to avoid steps 1 and 2 if unnecessary
4705       
4706       IF (zwt_force(1,jst) <= zmaxh) THEN
4707
4708          !! We force the nodes below zwt_force to be saturated
4709          !  As above, we compare mc to mcs
4710          DO jsl = 1,nslm
4711             DO ji = 1, kjpindex
4712                dmc(ji,jsl) = zero
4713                IF ( ( zz(jsl) >= zwt_force(ji,jst)*mille ) ) THEN
4714                   dmc(ji,jsl) = mcs(njsc(ji)) - mc(ji,jsl,jst) ! addition to reach mcs (m3/m3) = positive value
4715                   mc(ji,jsl,jst) = mcs(njsc(ji))
4716                ENDIF
4717             ENDDO
4718          ENDDO
4719         
4720          !! To ensure conservation, this needs to be balanced by a negative change in drainage (in kg/m2/dt)
4721          DO ji = 1, kjpindex
4722             dr_force_ns(ji,jst) = dz(2) * ( trois*dmc(ji,1) + dmc(ji,2) )/huit ! top layer = initialization
4723          ENDDO
4724          DO jsl = 2,nslm-1 ! intermediate layers
4725             DO ji = 1, kjpindex
4726                dr_force_ns(ji,jst) = dr_force_ns(ji,jst) + dz(jsl) &
4727                     & * (trois*dmc(ji,jsl)+dmc(ji,jsl-1))/huit &
4728                     & + dz(jsl+1) * (trois*dmc(ji,jsl)+dmc(ji,jsl+1))/huit
4729             ENDDO
4730          ENDDO
4731          DO ji = 1, kjpindex
4732             dr_force_ns(ji,jst) = dr_force_ns(ji,jst) + dz(nslm) & ! bottom layer
4733                  & * (trois * dmc(ji,nslm) + dmc(ji,nslm-1))/huit
4734             dr_ns(ji,jst) = dr_ns(ji,jst) - dr_force_ns(ji,jst) ! dr_force_ns is positive and dr_ns must be reduced
4735          END DO
4736
4737       ELSE         
4738
4739          dr_force_ns(:,jst) = zero 
4740
4741       ENDIF
4742
4743       !! 3.5 Diagnosing the effective water table depth:
4744       !!     Defined as as the smallest jsl value when mc(jsl) is no more at saturation (mcs), starting from the bottom
4745       !      If there is a part of the soil which is saturated but underlain with unsaturated nodes,
4746       !      this is not considered as a water table
4747       DO ji = 1, kjpindex
4748          wtd_ns(ji,jst) = undef_sechiba ! in meters
4749          jsl=nslm
4750          DO WHILE ( (mc(ji,jsl,jst) .EQ. mcs(njsc(ji))) .AND. (jsl > 1) )
4751             wtd_ns(ji,jst) = zz(jsl)/mille ! in meters
4752             jsl=jsl-1
4753          ENDDO
4754       ENDDO
4755
4756       !! 3.6 Diagnose under_mcr to adapt water stress calculation below
4757       !      This routine does not change tmc but decides where we should turn off ET to prevent further mc decrease
4758       !      Like above, the tests are made on total mc, compared to mcr
4759       CALL hydrol_soil_smooth_under_mcr(kjpindex, jst, njsc, is_under_mcr, check_under_ns)
4760 
4761       !! 4. At the end of the prognostic calculations, we recompute important moisture variables
4762
4763       !! 4.1 Total soil moisture content (water2infilt added below)
4764       DO ji = 1, kjpindex
4765          tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
4766       ENDDO
4767       DO jsl = 2,nslm-1
4768          DO ji = 1, kjpindex
4769             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) &
4770                  & * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
4771                  & + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
4772          ENDDO
4773       ENDDO
4774       DO ji = 1, kjpindex
4775          tmc(ji,jst) = tmc(ji,jst) + dz(nslm) &
4776               & * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
4777       END DO
4778
4779       !! 4.2 mcl is a module variable; we update it here for calculating bare soil evaporation,
4780       !!     and in case we would like to export it (xios)
4781       DO jsl = 1, nslm
4782          DO ji =1, kjpindex
4783             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(njsc(ji)) + &
4784                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
4785             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
4786          ENDDO
4787       ENDDO
4788       
4789       !! 5. Optional check of the water balance of soil column (if check_cwrr)
4790
4791       IF (check_cwrr) THEN
4792
4793          !! 5.1 Computation of the vertical water fluxes
4794          CALL hydrol_soil_flux(kjpindex,jst,mclint,flux_top)
4795         
4796          !! 5.2 Total mc conservation
4797          DO ji = 1,kjpindex   
4798             deltahum(ji) = (tmc(ji,jst) - tmcold(ji))
4799             diff(ji) = flux_infilt(ji) - flux_top(ji) - SUM(rootsink(ji,:,jst)) &
4800                   -ru_ns(ji,jst) - dr_ns(ji,jst)
4801             test(ji) = (ABS(deltahum(ji)-diff(ji))*mask_soiltile(ji,jst) .GT. allowed_err)
4802 
4803             IF (test(ji)) THEN             
4804                WRITE (numout,*)'CWRR water conservation pb:',ji,jst,njsc(ji),deltahum(ji)-diff(ji)
4805                WRITE (numout,*)'tmc,tmcold,diff',tmc(ji,jst),tmcold(ji),deltahum(ji)
4806                WRITE(numout,*) 'evapot,evapot_penm,ae_ns,flux_top',evapot(ji),evapot_penm(ji),&
4807                     ae_ns(ji,jst),flux_top(ji)
4808                WRITE (numout,*)'ru_ns,dr_ns,SUM(rootsink)',ru_ns(ji,jst),dr_ns(ji,jst), &
4809                     SUM(rootsink(ji,:,jst))
4810                WRITE (numout,*)'precisol, flux_infilt',precisol_ns(ji,jst)
4811                WRITE (numout,*)'irrigation, returnflow, reinfiltration', &
4812                      irrigation_soil(ji),returnflow_soil(ji),reinfiltration_soil(ji)
4813                WRITE (numout,*)'mc',mc(ji,:,jst) ! along jsl
4814                WRITE (numout,*)'qflux',qflux(ji,:,jst) ! along jsl
4815                WRITE (numout,*)'k', k(ji,:) ! along jsl
4816                WRITE (numout,*)'soiltile',soiltile(ji,jst)
4817                WRITE (numout,*)'veget_max', veget_max(ji,:)
4818               
4819                error=.TRUE.
4820                CALL ipslerr_p(2, 'hydrol_soil', 'We will STOP in the end of this subroutine.',&
4821                     & 'CWRR water balance check','')
4822             ENDIF
4823          ENDDO
4824
4825          !! 5.3 Total mc should not reach zero, or the tridiag solver will have problems
4826          DO ji = 1,kjpindex
4827             IF(MINVAL(mc(ji,:,jst)).LT. min_sechiba) THEN
4828                WRITE (numout,*)'CWRR MC NEGATIVE', &
4829                     ji,lalo(ji,:),MINLOC(mc(ji,:,jst)),jst,mc(ji,:,jst)
4830                WRITE(numout,*) 'evapot,evapot_penm,ae_ns,flux_top',evapot(ji),evapot_penm(ji),&
4831                     ae_ns(ji,jst),flux_top(ji)
4832                WRITE (numout,*)'ru_ns,dr_ns,SUM(rootsink)',ru_ns(ji,jst),dr_ns(ji,jst), &
4833                     SUM(rootsink(ji,:,jst))
4834                WRITE (numout,*)'precisol, flux_infilt',precisol_ns(ji,jst)
4835                WRITE (numout,*)'irrigation, returnflow, reinfiltration', &
4836                      irrigation_soil(ji),returnflow_soil(ji),reinfiltration_soil(ji)
4837                WRITE (numout,*)'mc',mc(ji,:,jst) ! along jsl
4838                WRITE (numout,*)'qflux',qflux(ji,:,jst) ! along jsl
4839                WRITE (numout,*)'k', k(ji,:) ! along jsl
4840                WRITE (numout,*)'soiltile',soiltile(ji,jst)
4841                WRITE (numout,*)'veget_max', veget_max(ji,:)             
4842
4843                error=.TRUE.
4844                CALL ipslerr_p(2, 'hydrol_soil', 'We will STOP in the end of this subroutine.',&
4845                     & 'CWRR MC NEGATIVE','')
4846             ENDIF
4847          END DO
4848
4849       ENDIF
4850
4851       !! 6. SM DIAGNOSTICS FOR OTHER ROUTINES, MODULES, OR NEXT STEP
4852       !    Starting here, mc and mcl should not change anymore
4853       
4854       !! 6.1 Total soil moisture, soil moisture at litter levels, soil wetness, us, humrelv, vesgtressv
4855       !!     (based on mc)
4856
4857       !! In output, tmc includes water2infilt(ji,jst)
4858       DO ji=1,kjpindex
4859          tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
4860       END DO
4861       
4862       ! The litter is the 4 top levels of the soil
4863       ! Compute various field of soil moisture for the litter (used for stomate and for albedo)
4864       ! We exclude the frozen water from the calculation
4865       DO ji=1,kjpindex
4866          tmc_litter(ji,jst) = dz(2) * ( trois*mcl(ji,1,jst)+ mcl(ji,2,jst))/huit
4867       END DO
4868       ! sum from level 1 to 4
4869       DO jsl=2,4
4870          DO ji=1,kjpindex
4871             tmc_litter(ji,jst) = tmc_litter(ji,jst) + dz(jsl) * & 
4872                  & ( trois*mcl(ji,jsl,jst) + mcl(ji,jsl-1,jst))/huit &
4873                  & + dz(jsl+1)*(trois*mcl(ji,jsl,jst) + mcl(ji,jsl+1,jst))/huit
4874          END DO
4875       END DO
4876
4877       ! Subsequent calculation of soil_wet_litter (tmc-tmcw)/(tmcfc-tmcw)
4878       ! Based on liquid water content
4879       DO ji=1,kjpindex
4880          soil_wet_litter(ji,jst) = MIN(un, MAX(zero,&
4881               & (tmc_litter(ji,jst)-tmc_litter_wilt(ji,jst)) / &
4882               & (tmc_litter_field(ji,jst)-tmc_litter_wilt(ji,jst)) ))
4883       END DO
4884
4885       ! Preliminary calculation of various soil moistures (for each layer, in kg/m2)
4886       sm(:,1)  = dz(2) * (trois*mcl(:,1,jst) + mcl(:,2,jst))/huit
4887       smt(:,1) = dz(2) * (trois*mc(:,1,jst) + mc(:,2,jst))/huit
4888       smw(:,1) = dz(2) * (quatre*mcw(njsc(:)))/huit
4889       smf(:,1) = dz(2) * (quatre*mcfc(njsc(:)))/huit
4890       sms(:,1) = dz(2) * (quatre*mcs(njsc(:)))/huit
4891       DO jsl = 2,nslm-1
4892          sm(:,jsl)  = dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
4893               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
4894          smt(:,jsl) = dz(jsl) * (trois*mc(:,jsl,jst)+mc(:,jsl-1,jst))/huit &
4895               + dz(jsl+1) * (trois*mc(:,jsl,jst)+mc(:,jsl+1,jst))/huit
4896          smw(:,jsl) = dz(jsl) * ( quatre*mcw(njsc(:)) )/huit &
4897               + dz(jsl+1) * ( quatre*mcw(njsc(:)) )/huit
4898          smf(:,jsl) = dz(jsl) * ( quatre*mcfc(njsc(:)) )/huit &
4899               + dz(jsl+1) * ( quatre*mcfc(njsc(:)) )/huit
4900          sms(:,jsl) = dz(jsl) * ( quatre*mcs(njsc(:)) )/huit &
4901               + dz(jsl+1) * ( quatre*mcs(njsc(:)) )/huit
4902       ENDDO
4903       sm(:,nslm)  = dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit 
4904       smt(:,nslm) = dz(nslm) * (trois*mc(:,nslm,jst) + mc(:,nslm-1,jst))/huit     
4905       smw(:,nslm) = dz(nslm) * (quatre*mcw(njsc(:)))/huit
4906       smf(:,nslm) = dz(nslm) * (quatre*mcfc(njsc(:)))/huit
4907       sms(:,nslm) = dz(nslm) * (quatre*mcs(njsc(:)))/huit
4908       ! sm_nostress = soil moisture of each layer at which us reaches 1, here at the middle of [smw,smf]
4909       DO jsl = 1,nslm
4910          sm_nostress(:,jsl) = smw(:,jsl) + pcent(njsc(:)) * (smf(:,jsl)-smw(:,jsl))
4911       END DO
4912
4913       ! Saturated litter soil moisture for rsoil
4914       tmcs_litter(:) = zero
4915       DO jsl = 1,4
4916          tmcs_litter(:) = tmcs_litter(:) + sms(:,jsl)
4917       END DO
4918             
4919       ! Soil wetness profiles (W-Ww)/(Ws-Ww)
4920       ! soil_wet_ns is the ratio of available soil moisture to max available soil moisture
4921       ! (ie soil moisture at saturation minus soil moisture at wilting point).
4922       ! soil wet is a water stress for stomate, to control C decomposition
4923       ! Based on liquid water content
4924       DO jsl=1,nslm
4925          DO ji=1,kjpindex
4926             soil_wet_ns(ji,jsl,jst) = MIN(un, MAX(zero, &
4927                  (sm(ji,jsl)-smw(ji,jsl))/(sms(ji,jsl)-smw(ji,jsl)) ))
4928          END DO
4929       END DO
4930
4931       ! Compute us and the new humrelv to use in sechiba (with loops on the vegetation types)
4932       ! This is the water stress for transpiration (diffuco) and photosynthesis (diffuco)
4933       ! humrel is never used in stomate
4934       ! Based on liquid water content
4935
4936       ! -- PFT1
4937       humrelv(:,1,jst) = zero       
4938       ! -- Top layer
4939       DO jv = 2,nvm
4940          DO ji=1,kjpindex
4941             !- Here we make the assumption that roots do not take water from the 1st layer.
4942             us(ji,jv,jst,1) = zero
4943             humrelv(ji,jv,jst) = zero ! initialisation of the sum
4944          END DO
4945       ENDDO
4946
4947       !! Dynamic nroot to optimize water use: the root profile used to weight the water stress function
4948       !! of each soil layer is updated at each time step in order to match the soil water profile
4949       !! (the soil water content of each layer available for transpiration)
4950       IF (ok_dynroot) THEN
4951          DO jv = 1, nvm
4952             IF ( is_tree(jv) ) THEN
4953                DO ji = 1, kjpindex
4954                   nroot_tmp(:) = zero
4955                   DO jsl = 2, nslm
4956                      nroot_tmp(jsl) = MAX(zero,sm(ji,jsl)-smw(ji,jsl) )
4957                   ENDDO
4958                   IF (SUM(nroot_tmp(:)) .GT. min_sechiba ) THEN
4959                      nroot(ji,jv,:) = nroot_tmp(:)/SUM(nroot_tmp(:))
4960                   ELSE
4961                      nroot(ji,jv,:) = zero
4962                   END IF
4963                ENDDO
4964             ELSE
4965                ! Specific case for grasses where we only consider the first 1m of soil.               
4966                DO ji = 1, kjpindex
4967                   nroot_tmp(:) = zero
4968                   DO jsl = 2, nslm
4969                      IF (znt(jsl) .LT. un) THEN
4970                         nroot_tmp(jsl) = MAX(zero,sm(ji,jsl)-smw(ji,jsl) )
4971                      END IF
4972                   ENDDO
4973                   
4974                   IF (SUM(nroot_tmp(:)) .GT. min_sechiba ) THEN
4975                      DO jsl = 2,nslm
4976                         IF (znt(jsl) .LT. un) THEN
4977                            nroot(ji,jv,jsl) = nroot_tmp(jsl)/SUM(nroot_tmp(:))
4978                         ELSE
4979                            nroot(ji,jv,jsl) = zero
4980                         END IF
4981                      ENDDO
4982                      nroot(ji,jv,1) = zero
4983                   END IF
4984                ENDDO
4985             END IF
4986          ENDDO
4987       ENDIF
4988
4989       ! -- Intermediate and bottom layers
4990       DO jsl = 2,nslm
4991          DO jv = 2, nvm
4992             DO ji=1,kjpindex
4993                ! AD16*** Although plants can only withdraw liquid water, we compute here the water stress
4994                ! based on mc and the corresponding thresholds mcs, pcent, or potentially mcw and mcfc
4995                ! This is consistent with assuming that ice is uniformly distributed within the poral space
4996                ! In such a case, freezing makes mcl and the "liquid" porosity smaller than the "total" values
4997                ! And it is the same for all the moisture thresholds, which are proportional to porosity.
4998                ! Since the stress is based on relative moisture, it could thus independent from the porosity
4999                ! at first order, thus independent from freezing.   
5000                ! 26-07-2017: us and humrel now based on liquid soil moisture, so the stress is stronger
5001                IF(new_watstress) THEN
5002                   IF((sm(ji,jsl)-smw(ji,jsl)) .GT. min_sechiba) THEN
5003                      us(ji,jv,jst,jsl) = MIN(un, MAX(zero, &
5004                           (EXP(- alpha_watstress * &
5005                           ( (smf(ji,jsl) - smw(ji,jsl)) / ( sm_nostress(ji,jsl) - smw(ji,jsl)) ) * &
5006                           ( (sm_nostress(ji,jsl) - sm(ji,jsl)) / ( sm(ji,jsl) - smw(ji,jsl)) ) ) ) ))&
5007                           * nroot(ji,jv,jsl)
5008                   ELSE
5009                      us(ji,jv,jst,jsl) = 0.
5010                   ENDIF
5011                ELSE
5012                   us(ji,jv,jst,jsl) = MIN(un, MAX(zero, &
5013                        (sm(ji,jsl)-smw(ji,jsl))/(sm_nostress(ji,jsl)-smw(ji,jsl)) )) * nroot(ji,jv,jsl)
5014                ENDIF
5015                humrelv(ji,jv,jst) = humrelv(ji,jv,jst) + us(ji,jv,jst,jsl)
5016             END DO
5017          END DO
5018       ENDDO
5019
5020       !! vegstressv is the water stress for phenology in stomate
5021       !! It varies linearly from zero at wilting point to 1 at field capacity
5022       vegstressv(:,:,jst) = zero
5023       DO jv = 2, nvm
5024          DO ji=1,kjpindex
5025             DO jsl=1,nslm
5026                vegstressv(ji,jv,jst) = vegstressv(ji,jv,jst) + &
5027                     MIN(un, MAX(zero, (sm(ji,jsl)-smw(ji,jsl))/(smf(ji,jsl)-smw(ji,jsl)) )) &
5028                     * nroot(ji,jv,jsl)
5029             END DO
5030          END DO
5031       END DO
5032
5033
5034       ! -- If the PFT is absent, the corresponding humrelv and vegstressv = 0
5035       DO jv = 2, nvm
5036          DO ji = 1, kjpindex
5037             IF (vegetmax_soil(ji,jv,jst) .LT. min_sechiba) THEN
5038                humrelv(ji,jv,jst) = zero
5039                vegstressv(ji,jv,jst) = zero
5040                us(ji,jv,jst,:) = zero
5041             ENDIF
5042          END DO
5043       END DO
5044
5045       !! 6.2 We need to turn off evaporation when is_under_mcr
5046       !!     We set us, humrelv and vegstressv to zero in this case
5047       !!     WARNING: It's different from having locally us=0 in the soil layers(s) where mc<mcr
5048       !!              This part is crucial to preserve water conservation
5049       DO jsl = 1,nslm
5050          DO jv = 2, nvm
5051             WHERE (is_under_mcr(:,jst))
5052                us(:,jv,jst,jsl) = zero
5053             ENDWHERE
5054          ENDDO
5055       ENDDO
5056       DO jv = 2, nvm
5057          WHERE (is_under_mcr(:,jst))
5058             humrelv(:,jv,jst) = zero
5059          ENDWHERE
5060       ENDDO
5061       
5062       ! For consistency in stomate, we also set moderwilt and soil_wet_ns to zero in this case.
5063       ! They are used later for shumdiag and shumdiag_perma
5064       DO jsl = 1,nslm
5065          WHERE (is_under_mcr(:,jst))
5066             soil_wet_ns(:,jsl,jst) = zero
5067          ENDWHERE
5068       ENDDO
5069
5070       ! Counting the nb of under_mcr occurences in each grid-cell
5071       WHERE (is_under_mcr(:,jst))
5072          undermcr = undermcr + un
5073       ENDWHERE
5074
5075       !! 6.3 Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in
5076       !!     thermosoil for the thermal conductivity.
5077       !! The multiplication by vegtot creates grid-cell average values
5078       ! *** To be checked for consistency with the use of nobio properties in thermosoil
5079       DO jsl=1,nslm
5080          DO ji=1,kjpindex
5081             mc_layh(ji,jsl) = mc_layh(ji,jsl) + mc(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji) 
5082             mcl_layh(ji,jsl) = mcl_layh(ji,jsl) + mcl(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji)
5083          ENDDO
5084       END DO
5085
5086       !! 6.4 The hydraulic conductivities exported here are the ones used in the diffusion/redistribution
5087       ! (no call of hydrol_soil_coef since 2.1)
5088       ! We average the values of each soiltile and keep the specific value (no multiplication by vegtot)
5089       DO ji = 1, kjpindex
5090          kk_moy(ji,:) = kk_moy(ji,:) + soiltile(ji,jst) * k(ji,:) 
5091          kk(ji,:,jst) = k(ji,:)
5092       ENDDO
5093       
5094       !! 6.5 We also want to export ksat at each node for CMIP6
5095       !  (In the output, done only once according to field_def_orchidee.xml; same averaging as for kk)
5096       DO jsl = 1, nslm
5097          ksat(:,jsl) = ksat(:,jsl) + soiltile(:,jst) * &
5098               ( ks(njsc(:)) * kfact(jsl,njsc(:)) * kfact_root(:,jsl,jst) ) 
5099       ENDDO
5100             
5101      IF (printlev>=3) WRITE (numout,*) ' prognostic/diagnostic part of hydrol_soil done for jst =', jst         
5102
5103    END DO  ! end of loop on soiltile
5104
5105    !! -- ENDING THE MAIN LOOP ON SOILTILES
5106
5107    !! 7. Summing 3d variables into 2d variables
5108    CALL hydrol_diag_soil (kjpindex, veget_max, soiltile, njsc, runoff, drainage, &
5109         & evapot, vevapnu, returnflow, reinfiltration, irrigation, &
5110         & shumdiag,shumdiag_perma, k_litt, litterhumdiag, humrel, vegstress, drysoil_frac,tot_melt)
5111
5112    ! Means of wtd, runoff and drainage corrections, across soiltiles   
5113    wtd(:) = zero 
5114    ru_corr(:) = zero
5115    ru_corr2(:) = zero
5116    dr_corr(:) = zero
5117    dr_corrnum(:) = zero
5118    dr_force(:) = zero
5119    DO jst = 1, nstm
5120       DO ji = 1, kjpindex 
5121          wtd(ji) = wtd(ji) + soiltile(ji,jst) * wtd_ns(ji,jst) ! average over vegtot only
5122          IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
5123             ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
5124             ru_corr(ji) = ru_corr(ji) + vegtot(ji) * soiltile(ji,jst) * ru_corr_ns(ji,jst) 
5125             ru_corr2(ji) = ru_corr2(ji) + vegtot(ji) * soiltile(ji,jst) * ru_corr2_ns(ji,jst) 
5126             dr_corr(ji) = dr_corr(ji) + vegtot(ji) * soiltile(ji,jst) * dr_corr_ns(ji,jst) 
5127             dr_corrnum(ji) = dr_corrnum(ji) + vegtot(ji) * soiltile(ji,jst) * dr_corrnum_ns(ji,jst)
5128             dr_force(ji) = dr_force(ji) - vegtot(ji) * soiltile(ji,jst) * dr_force_ns(ji,jst)
5129                                       ! the sign is OK to get a negative drainage flux
5130          ENDIF
5131       ENDDO
5132    ENDDO
5133
5134    ! Means local variables, including water conservation checks
5135    ru_infilt(:)=0.
5136    qinfilt(:)=0.
5137    check_infilt(:)=0.
5138    check_tr(:)=0.
5139    check_over(:)=0.
5140    check_under(:)=0.
5141    DO jst = 1, nstm
5142       DO ji = 1, kjpindex 
5143          IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
5144             ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
5145             ru_infilt(ji) = ru_infilt(ji) + vegtot(ji) * soiltile(ji,jst) * ru_infilt_ns(ji,jst)
5146             qinfilt(ji) = qinfilt(ji) + vegtot(ji) * soiltile(ji,jst) * qinfilt_ns(ji,jst)
5147          ENDIF
5148       ENDDO
5149    ENDDO
5150 
5151    IF (check_cwrr2) THEN
5152       DO jst = 1, nstm
5153          DO ji = 1, kjpindex 
5154             IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
5155                ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
5156                check_infilt(ji) = check_infilt(ji) + vegtot(ji) * soiltile(ji,jst) * check_infilt_ns(ji,jst)
5157                check_tr(ji) = check_tr(ji) + vegtot(ji) * soiltile(ji,jst) * check_tr_ns(ji,jst)
5158                check_over(ji) = check_over(ji) + vegtot(ji) * soiltile(ji,jst) * check_over_ns(ji,jst)
5159                check_under(ji) =  check_under(ji) + vegtot(ji) * soiltile(ji,jst) * check_under_ns(ji,jst)
5160             ENDIF
5161          ENDDO
5162       ENDDO
5163    END IF
5164
5165    !! 8. COMPUTING EVAP_BARE_LIM_NS FOR NEXT TIME STEP, WITH A LOOP ON SOILTILES
5166    !!    The principle is to run a dummy integration of the water redistribution scheme
5167    !!    to check if the SM profile can sustain a potential evaporation.
5168    !!    If not, the dummy integration is redone from the SM profile of the end of the normal integration,
5169    !!    with a boundary condition leading to a very severe water limitation: mc(1)=mcr
5170
5171    ! evap_bare_lim = beta factor for bare soil evaporation
5172    evap_bare_lim(:) = zero
5173    evap_bare_lim_ns(:,:) = zero
5174
5175    ! Loop on soil tiles 
5176    DO jst = 1,nstm
5177
5178       !! 8.1 Save actual mc, mcl, and tmc for restoring at the end of the time step
5179       !!      and calculate tmcint corresponding to mc without water2infilt
5180       DO jsl = 1, nslm
5181          DO ji = 1, kjpindex
5182             mcint(ji,jsl) = mask_soiltile(ji,jst) * mc(ji,jsl,jst)
5183             mclint(ji,jsl) = mask_soiltile(ji,jst) * mcl(ji,jsl,jst)
5184          ENDDO
5185       ENDDO
5186
5187       DO ji = 1, kjpindex
5188          temp(ji) = tmc(ji,jst)
5189          tmcint(ji) = temp(ji) - water2infilt(ji,jst) ! to estimate bare soil evap based on water budget
5190       ENDDO
5191
5192       !! 8.2 Since we estimate bare soile evap for the next time step, we update profil_froz_hydro and mcl
5193       !     (effect of mc only, the change in temp_hydro is neglected)
5194       IF ( ok_freeze_cwrr ) CALL hydrol_soil_froz(kjpindex,jst,njsc)
5195        DO jsl = 1, nslm
5196          DO ji =1, kjpindex
5197             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(njsc(ji)) + &
5198                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
5199             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
5200          ENDDO
5201       ENDDO         
5202
5203       !! 8.3 K and D are recomputed for the updated profile of mc/mcl
5204       CALL hydrol_soil_coef(kjpindex,jst,njsc)
5205
5206       !! 8.4 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
5207       CALL hydrol_soil_setup(kjpindex,jst)
5208       resolv(:) = (mask_soiltile(:,jst) .GT. 0) 
5209
5210       !! 8.5 We define the system of linear equations, based on matrix coefficients,
5211
5212       !- Impose potential evaporation as flux_top in mm/step, assuming the water is available
5213       ! Note that this should lead to never have evapnu>evapot_penm(ji)
5214
5215       DO ji = 1, kjpindex
5216         
5217          IF (vegtot(ji).GT.min_sechiba) THEN
5218             
5219             ! We calculate a reduced demand, by means of a soil resistance (Sellers et al., 1992)
5220             ! It is based on the liquid SM only, like for us and humrel
5221             IF (do_rsoil) THEN
5222                mc_rel(ji) = tmc_litter(ji,jst)/tmcs_litter(ji) ! tmc_litter based on mcl
5223                ! based on SM in the top 4 soil layers (litter) to smooth variability
5224                r_soil_ns(ji,jst) = exp(8.206 - 4.255 * mc_rel(ji))
5225             ELSE
5226                r_soil_ns(ji,jst) = zero
5227             ENDIF
5228
5229             ! Aerodynamic resistance
5230             speed = MAX(min_wind, SQRT (u(ji)*u(ji) + v(ji)*v(ji)))
5231             IF (speed * tq_cdrag(ji) .GT. min_sechiba) THEN
5232                ra = un / (speed * tq_cdrag(ji))
5233                evap_soil(ji) = evapot_penm(ji) / (un + r_soil_ns(ji,jst)/ra)
5234             ELSE
5235                evap_soil(ji) = evapot_penm(ji)
5236             ENDIF
5237             
5238       ! AD16*** et si evap_bare_lim_ns<0 ?? car on suppose que tmcint > tmc(new)
5239       ! (water2inflit permet de propager de la ponded water d'un pas de temps a l'autre:
5240       ! peut-on s'en servir pour creer des cas d'evapnu potentielle negative ? a gerer dans diffuco ?)
5241             
5242             flux_top(ji) = evap_soil(ji) * &
5243                  AINT(frac_bare_ns(ji,jst)+un-min_sechiba)
5244          ELSE
5245             
5246             flux_top(ji) = zero
5247             
5248          ENDIF
5249       ENDDO
5250
5251       ! We don't use rootsinks, because we assume there is no transpiration in the bare soil fraction (??)
5252       !- First layer
5253       DO ji = 1, kjpindex
5254          tmat(ji,1,1) = zero
5255          tmat(ji,1,2) = f(ji,1)
5256          tmat(ji,1,3) = g1(ji,1)
5257          rhs(ji,1)    = fp(ji,1) * mcl(ji,1,jst) + gp(ji,1)*mcl(ji,2,jst) &
5258               - flux_top(ji) - (b(ji,1)+b(ji,2))/deux *(dt_sechiba/one_day)
5259       ENDDO
5260       !- soil body
5261       DO jsl=2, nslm-1
5262          DO ji = 1, kjpindex
5263             tmat(ji,jsl,1) = e(ji,jsl)
5264             tmat(ji,jsl,2) = f(ji,jsl)
5265             tmat(ji,jsl,3) = g1(ji,jsl)
5266             rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
5267                  +  gp(ji,jsl) * mcl(ji,jsl+1,jst) &
5268                  + (b(ji,jsl-1) - b(ji,jsl+1)) * (dt_sechiba/one_day) / deux
5269          ENDDO
5270       ENDDO
5271       !- Last layer
5272       DO ji = 1, kjpindex
5273          jsl=nslm
5274          tmat(ji,jsl,1) = e(ji,jsl)
5275          tmat(ji,jsl,2) = f(ji,jsl)
5276          tmat(ji,jsl,3) = zero
5277          rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
5278               + (b(ji,jsl-1) + b(ji,jsl)*(un-deux*free_drain_coef(ji,jst))) * (dt_sechiba/one_day) / deux
5279       ENDDO
5280       !- Store the equations for later use (9.6)
5281       DO jsl=1,nslm
5282          DO ji = 1, kjpindex
5283             srhs(ji,jsl) = rhs(ji,jsl)
5284             stmat(ji,jsl,1) = tmat(ji,jsl,1)
5285             stmat(ji,jsl,2) = tmat(ji,jsl,2)
5286             stmat(ji,jsl,3) = tmat(ji,jsl,3)
5287          ENDDO
5288       ENDDO
5289
5290       !! 8.6 Solve the diffusion equation, assuming that flux_top=evapot_penm (updates mcl)
5291       CALL hydrol_soil_tridiag(kjpindex,jst)
5292
5293       !! 9.7 Alternative solution with mc(1)=mcr in points where the above solution leads to mcl<mcr
5294       ! hydrol_soil_tridiag calculates mc recursively from the top as a fonction of rhs and tmat
5295       ! We re-use these the above values, but for mc(1)=mcr and the related tmat
5296       
5297       DO ji = 1, kjpindex
5298          ! by construction, mc and mcl are always on the same side of mcr, so we can use mcl here
5299          resolv(ji) = (mcl(ji,1,jst).LT.(mcr(njsc(ji))).AND.flux_top(ji).GT.min_sechiba)
5300       ENDDO
5301       !! Reset the coefficient for diffusion (tridiag is only solved if resolv(ji) = .TRUE.)O
5302       DO jsl=1,nslm
5303          !- The new condition is to put the upper layer at residual soil moisture
5304          DO ji = 1, kjpindex
5305             rhs(ji,jsl) = srhs(ji,jsl)
5306             tmat(ji,jsl,1) = stmat(ji,jsl,1)
5307             tmat(ji,jsl,2) = stmat(ji,jsl,2)
5308             tmat(ji,jsl,3) = stmat(ji,jsl,3)
5309          END DO
5310       END DO
5311       
5312       DO ji = 1, kjpindex
5313          tmat(ji,1,2) = un
5314          tmat(ji,1,3) = zero
5315          rhs(ji,1) = mcr(njsc(ji))
5316       ENDDO
5317       
5318       ! Solves the diffusion equation with new surface bc where resolv=T
5319       CALL hydrol_soil_tridiag(kjpindex,jst)
5320
5321       !! 8.8 In both case, we have drainage to be consistent with rhs
5322       DO ji = 1, kjpindex
5323          flux_bottom(ji) = mask_soiltile(ji,jst)*k(ji,nslm)*free_drain_coef(ji,jst) * (dt_sechiba/one_day)
5324       ENDDO
5325       
5326       !! 8.9 Water budget to assess the top flux = soil evaporation
5327       !      Where resolv=F at the 2nd step (9.6), it should simply be the potential evaporation
5328
5329       ! Total soil moisture content for water budget
5330
5331       DO jsl = 1, nslm
5332          DO ji =1, kjpindex
5333             mc(ji,jsl,jst) = MAX( mcl(ji,jsl,jst), mcl(ji,jsl,jst) + &
5334                  profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
5335             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we get mc=mcl
5336          ENDDO
5337       ENDDO
5338       
5339       DO ji = 1, kjpindex
5340          tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
5341       ENDDO       
5342       DO jsl = 2,nslm-1
5343          DO ji = 1, kjpindex
5344             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) &
5345                  * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
5346                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
5347          ENDDO
5348       ENDDO
5349       DO ji = 1, kjpindex
5350          tmc(ji,jst) = tmc(ji,jst) + dz(nslm) &
5351               * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
5352       END DO
5353   
5354       ! Deduce upper flux from soil moisture variation and bottom flux
5355       ! TMCi-D-BSE=TMC (BSE=bare soil evap=TMCi-TMC-D)
5356       ! The numerical errors of tridiag close to saturation cannot be simply solved here,
5357       ! we can only hope they are not too large because we don't add water at this stage...
5358       DO ji = 1, kjpindex
5359          evap_bare_lim_ns(ji,jst) = mask_soiltile(ji,jst) * &
5360               (tmcint(ji)-tmc(ji,jst)-flux_bottom(ji))
5361       END DO
5362
5363       !! 8.10 evap_bare_lim_ns is turned from an evaporation rate to a beta
5364       DO ji = 1, kjpindex
5365          ! Here we weight evap_bare_lim_ns by the fraction of bare evaporating soil.
5366          ! This is given by frac_bare_ns, taking into account bare soil under vegetation
5367          IF(vegtot(ji) .GT. min_sechiba) THEN
5368             evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) * frac_bare_ns(ji,jst)
5369          ELSE
5370             evap_bare_lim_ns(ji,jst) = 0.
5371          ENDIF
5372       END DO
5373
5374       ! We divide by evapot, which is consistent with diffuco (evap_bare_lim_ns < evapot_penm/evapot)
5375       ! Further decrease if tmc_litter is below the wilting point
5376
5377       IF (do_rsoil) THEN
5378          DO ji=1,kjpindex
5379             IF (evapot(ji).GT.min_sechiba) THEN
5380                evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) / evapot(ji)
5381             ELSE
5382                evap_bare_lim_ns(ji,jst) = zero ! not redundant with the is_under_mcr case below
5383                                                ! but not necessarily useful
5384             END IF
5385             evap_bare_lim_ns(ji,jst)=MAX(MIN(evap_bare_lim_ns(ji,jst),1.),0.)
5386          END DO
5387       ELSE
5388          DO ji=1,kjpindex
5389             IF ((evapot(ji).GT.min_sechiba) .AND. &
5390                  (tmc_litter(ji,jst).GT.(tmc_litter_wilt(ji,jst)))) THEN
5391                evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) / evapot(ji)
5392             ELSEIF((evapot(ji).GT.min_sechiba).AND. &
5393                  (tmc_litter(ji,jst).GT.(tmc_litter_res(ji,jst)))) THEN
5394                evap_bare_lim_ns(ji,jst) =  (un/deux) * evap_bare_lim_ns(ji,jst) / evapot(ji)
5395                ! This is very arbitrary, with no justification from the literature
5396             ELSE
5397                evap_bare_lim_ns(ji,jst) = zero
5398             END IF
5399             evap_bare_lim_ns(ji,jst)=MAX(MIN(evap_bare_lim_ns(ji,jst),1.),0.)
5400          END DO
5401       ENDIF
5402
5403       !! 8.11 Set evap_bare_lim_ns to zero if is_under_mcr at the end of the prognostic loop
5404       !!      (cf us, humrelv, vegstressv in 5.2)
5405       WHERE (is_under_mcr(:,jst))
5406          evap_bare_lim_ns(:,jst) = zero
5407       ENDWHERE
5408
5409       !! 8.12 Restores mc, mcl, and tmc, to erase the effect of the dummy integrations
5410       !!      on these prognostic variables
5411       DO jsl = 1, nslm
5412          DO ji = 1, kjpindex
5413             mc(ji,jsl,jst) = mask_soiltile(ji,jst) * mcint(ji,jsl)
5414             mcl(ji,jsl,jst) = mask_soiltile(ji,jst) * mclint(ji,jsl)
5415          ENDDO
5416       ENDDO
5417       DO ji = 1, kjpindex
5418          tmc(ji,jst) = temp(ji)
5419       ENDDO
5420
5421    ENDDO !end loop on tiles for dummy integration
5422
5423    !! 9. evap_bar_lim is the grid-cell scale beta
5424    DO ji = 1, kjpindex
5425       evap_bare_lim(ji) =  SUM(evap_bare_lim_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
5426       r_soil(ji) =  SUM(r_soil_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
5427    ENDDO
5428
5429    !! 10. XIOS export of local variables, including water conservation checks
5430   
5431    CALL xios_orchidee_send_field("ksat",ksat) ! mm/d (for CMIP6, once)
5432    CALL xios_orchidee_send_field("psi_moy",psi_moy) ! mm (for SP-MIP)
5433    CALL xios_orchidee_send_field("wtd",wtd) ! in m
5434    CALL xios_orchidee_send_field("ru_corr",ru_corr/dt_sechiba)   ! adjustment flux added to surface runoff (included in runoff)
5435    CALL xios_orchidee_send_field("ru_corr2",ru_corr2/dt_sechiba)
5436    CALL xios_orchidee_send_field("dr_corr",dr_corr/dt_sechiba)   ! adjustment flux added to drainage (included in drainage)
5437    CALL xios_orchidee_send_field("dr_corrnum",dr_corrnum/dt_sechiba) 
5438    CALL xios_orchidee_send_field("dr_force",dr_force/dt_sechiba) ! adjustement flux added to drainage to sustain a forced wtd
5439    CALL xios_orchidee_send_field("qinfilt",qinfilt/dt_sechiba)
5440    CALL xios_orchidee_send_field("ru_infilt",ru_infilt/dt_sechiba)
5441    CALL xios_orchidee_send_field("r_soil",r_soil) ! s/m
5442
5443    IF (check_cwrr2) THEN
5444       CALL xios_orchidee_send_field("check_infilt",check_infilt/dt_sechiba)
5445       CALL xios_orchidee_send_field("check_tr",check_tr/dt_sechiba)
5446       CALL xios_orchidee_send_field("check_over",check_over/dt_sechiba)
5447       CALL xios_orchidee_send_field("check_under",check_under/dt_sechiba)   
5448    END IF
5449
5450    !! 11. Exit if error was found previously in this subroutine
5451   
5452    IF ( error ) THEN
5453       WRITE(numout,*) 'One or more errors have been detected in hydrol_soil. Model stops.'
5454       CALL ipslerr_p(3, 'hydrol_soil', 'We will STOP now.',&
5455                  & 'One or several fatal errors were found previously.','')
5456    END IF
5457
5458  END SUBROUTINE hydrol_soil
5459
5460
5461!! ================================================================================================================================
5462!! SUBROUTINE   : hydrol_soil_infilt
5463!!
5464!>\BRIEF        Infiltration
5465!!
5466!! DESCRIPTION  :
5467!! 1. We calculate the total SM at the beginning of the routine
5468!! 2. Infiltration process
5469!! 2.1 Initialization of time counter and infiltration rate
5470!! 2.2 Infiltration layer by layer, accounting for an exponential law for subgrid variability
5471!! 2.3 Resulting infiltration and surface runoff
5472!! 3. For water conservation check, we calculate the total SM at the beginning of the routine,
5473!!    and export the difference with the flux
5474!! 5. Local verification
5475!!
5476!! RECENT CHANGE(S) : 2016 by A. Ducharne
5477!! Adding checks and interactions variables with hydrol_soil, but the processes are unchanged
5478!!
5479!! MAIN OUTPUT VARIABLE(S) :
5480!!
5481!! REFERENCE(S) :
5482!!
5483!! FLOWCHART    : None
5484!! \n
5485!_ ================================================================================================================================
5486!_ hydrol_soil_infilt
5487
5488  SUBROUTINE hydrol_soil_infilt(kjpindex, ins, njsc, flux_infilt, qinfilt_ns, ru_infilt, check)
5489
5490    !! 0. Variable and parameter declaration
5491
5492    !! 0.1 Input variables
5493
5494    ! GLOBAL (in or inout)
5495    INTEGER(i_std), INTENT(in)                        :: kjpindex        !! Domain size
5496    INTEGER(i_std), INTENT(in)                        :: ins
5497    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc            !! Index of the dominant soil textural class in the grid cell
5498                                                                         !!  (1-nscm, unitless)
5499    REAL(r_std), DIMENSION (kjpindex), INTENT (in)    :: flux_infilt     !! Water to infiltrate
5500                                                                         !!  @tex $(kg m^{-2})$ @endtex
5501
5502    !! 0.2 Output variables
5503    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check       !! delta SM - flux (mm/dt_sechiba)
5504    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: ru_infilt   !! Surface runoff from soil_infilt (mm/dt_sechiba)
5505    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: qinfilt_ns  !! Effective infiltration flux (mm/dt_sechiba)
5506
5507    !! 0.3 Modified variables
5508
5509    !! 0.4 Local variables
5510
5511    INTEGER(i_std)                                :: ji, jsl      !! Indices
5512    REAL(r_std), DIMENSION (kjpindex)             :: wat_inf_pot  !! infiltrable water in the layer
5513    REAL(r_std), DIMENSION (kjpindex)             :: wat_inf      !! infiltrated water in the layer
5514    REAL(r_std), DIMENSION (kjpindex)             :: dt_tmp       !! time remaining before the end of the time step
5515    REAL(r_std), DIMENSION (kjpindex)             :: dt_inf       !! the time it takes to complete the infiltration in the
5516                                                                  !! layer
5517    REAL(r_std)                                   :: k_m          !! the mean conductivity used for the saturated front
5518    REAL(r_std), DIMENSION (kjpindex)             :: infilt_tmp   !! infiltration rate for the considered layer
5519    REAL(r_std), DIMENSION (kjpindex)             :: infilt_tot   !! total infiltration
5520    REAL(r_std), DIMENSION (kjpindex)             :: flux_tmp     !! rate at which precip hits the ground
5521
5522    REAL(r_std), DIMENSION(kjpindex)              :: tmci         !! total SM at beginning of routine (kg/m2)
5523    REAL(r_std), DIMENSION(kjpindex)              :: tmcf         !! total SM at end of routine (kg/m2)
5524   
5525
5526!_ ================================================================================================================================
5527
5528    ! If data (or coupling with GCM) was available, a parameterization for subgrid rainfall could be performed
5529
5530    !! 1. We calculate the total SM at the beginning of the routine
5531    IF (check_cwrr2) THEN
5532       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5533       DO jsl = 2,nslm-1
5534          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5535               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5536       ENDDO
5537       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5538    ENDIF
5539
5540    !! 2. Infiltration process
5541
5542    !! 2.1 Initialization
5543
5544    DO ji = 1, kjpindex
5545       !! First we fill up the first layer (about 1mm) without any resistance and quasi-immediately
5546       wat_inf_pot(ji) = MAX((mcs(njsc(ji))-mc(ji,1,ins)) * dz(2) / deux, zero)
5547       wat_inf(ji) = MIN(wat_inf_pot(ji), flux_infilt(ji))
5548       mc(ji,1,ins) = mc(ji,1,ins) + wat_inf(ji) * deux / dz(2)
5549       !
5550    ENDDO
5551
5552    !! Initialize a countdown for infiltration during the time-step and the value of potential runoff
5553    dt_tmp(:) = dt_sechiba / one_day
5554    infilt_tot(:) = wat_inf(:)
5555    !! Compute the rate at which water will try to infiltrate each layer
5556    ! flux_temp is converted here to the same unit as k_m
5557    flux_tmp(:) = (flux_infilt(:)-wat_inf(:)) / dt_tmp(:)
5558
5559    !! 2.2 Infiltration layer by layer
5560    DO jsl = 2, nslm-1
5561       DO ji = 1, kjpindex
5562          !! Infiltrability of each layer if under a saturated one
5563          ! This is computed by an simple arithmetic average because
5564          ! the time step (30min) is not appropriate for a geometric average (advised by Haverkamp and Vauclin)
5565          k_m = (k(ji,jsl) + ks(njsc(ji))*kfact(jsl-1,njsc(ji))*kfact_root(ji,jsl,ins)) / deux 
5566
5567          IF (ok_freeze_cwrr) THEN
5568             IF (temp_hydro(ji, jsl) .LT. ZeroCelsius) THEN
5569                k_m = k(ji,jsl)
5570             ENDIF
5571          ENDIF
5572
5573          !! We compute the mean rate at which water actually infiltrate:
5574          ! Subgrid: Exponential distribution of k around k_m, but average p directly used
5575          ! See d'Orgeval 2006, p 78, but it's not fully clear to me (AD16***)
5576          infilt_tmp(ji) = k_m * (un - EXP(- flux_tmp(ji) / k_m)) 
5577
5578          !! From which we deduce the time it takes to fill up the layer or to end the time step...
5579          wat_inf_pot(ji) =  MAX((mcs(njsc(ji))-mc(ji,jsl,ins)) * (dz(jsl) + dz(jsl+1)) / deux, zero)
5580          IF ( infilt_tmp(ji) > min_sechiba) THEN
5581             dt_inf(ji) =  MIN(wat_inf_pot(ji)/infilt_tmp(ji), dt_tmp(ji))
5582             ! The water infiltration TIME has to limited by what is still available for infiltration.
5583             IF ( dt_inf(ji) * infilt_tmp(ji) > flux_infilt(ji)-infilt_tot(ji) ) THEN
5584                dt_inf(ji) = MAX(flux_infilt(ji)-infilt_tot(ji),zero)/infilt_tmp(ji)
5585             ENDIF
5586          ELSE
5587             dt_inf(ji) = dt_tmp(ji)
5588          ENDIF
5589
5590          !! The water enters in the layer
5591          wat_inf(ji) = dt_inf(ji) * infilt_tmp(ji)
5592          ! bviously the moisture content
5593          mc(ji,jsl,ins) = mc(ji,jsl,ins) + &
5594               & wat_inf(ji) * deux / (dz(jsl) + dz(jsl+1))
5595          ! the time remaining before the next time step
5596          dt_tmp(ji) = dt_tmp(ji) - dt_inf(ji)
5597          ! and finally the infilt_tot (which is just used to check if there is a problem, below)
5598          infilt_tot(ji) = infilt_tot(ji) + infilt_tmp(ji) * dt_inf(ji)
5599       ENDDO
5600    ENDDO
5601
5602    !! 2.3 Resulting infiltration and surface runoff
5603    ru_infilt(:,ins) = flux_infilt(:) - infilt_tot(:)
5604    qinfilt_ns(:,ins) = infilt_tot(:)
5605
5606    !! 3. For water conservation check: we calculate the total SM at the beginning of the routine
5607    !!    and export the difference with the flux
5608    IF (check_cwrr2) THEN
5609       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5610       DO jsl = 2,nslm-1
5611          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5612               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5613       ENDDO
5614       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5615       ! Normally, tcmf=tmci+infilt_tot
5616       check(:,ins) = tmcf(:)-(tmci(:)+infilt_tot(:))
5617    ENDIF
5618   
5619    !! 5. Local verification
5620    DO ji = 1, kjpindex
5621       IF (infilt_tot(ji) .LT. -min_sechiba .OR. infilt_tot(ji) .GT. flux_infilt(ji) + min_sechiba) THEN
5622          WRITE (numout,*) 'Error in the calculation of infilt tot', infilt_tot(ji)
5623          WRITE (numout,*) 'k, ji, jst, mc', k(ji,1:2), ji, ins, mc(ji,1,ins)
5624          CALL ipslerr_p(3, 'hydrol_soil_infilt', 'We will STOP now.','Error in calculation of infilt tot','')
5625       ENDIF
5626    ENDDO
5627
5628  END SUBROUTINE hydrol_soil_infilt
5629
5630
5631!! ================================================================================================================================
5632!! SUBROUTINE   : hydrol_soil_smooth_under_mcr
5633!!
5634!>\BRIEF        : Modifies the soil moisture profile to avoid under-residual values,
5635!!                then diagnoses the points where such "excess" values remain.
5636!!
5637!! DESCRIPTION  :
5638!! The "excesses" under-residual are corrected from top to bottom, by transfer of excesses
5639!! to the lower layers. The reverse transfer is performed to smooth any remaining "excess" in the bottom layer.
5640!! If some "excess" remain afterwards, the entire soil profile is at the threshold value (mcs or mcr),
5641!! and the remaining "excess" is necessarily concentrated in the top layer.
5642!! This allowing diagnosing the flag is_under_mcr.
5643!! Eventually, the remaining "excess" is split over the entire profile
5644!! 1. We calculate the total SM at the beginning of the routine
5645!! 2. Smoothes the profile to avoid negative values of punctual soil moisture
5646!! Note that we check that mc > min_sechiba in hydrol_soil
5647!! 3. For water conservation check, We calculate the total SM at the beginning of the routine,
5648!!    and export the difference with the flux
5649!!
5650!! RECENT CHANGE(S) : 2016 by A. Ducharne
5651!!
5652!! MAIN OUTPUT VARIABLE(S) :
5653!!
5654!! REFERENCE(S) :
5655!!
5656!! FLOWCHART    : None
5657!! \n
5658!_ ================================================================================================================================
5659!_ hydrol_soil_smooth_under_mcr
5660
5661  SUBROUTINE hydrol_soil_smooth_under_mcr(kjpindex, ins, njsc, is_under_mcr, check)
5662
5663    !- arguments
5664
5665    !! 0. Variable and parameter declaration
5666
5667    !! 0.1 Input variables
5668
5669    INTEGER(i_std), INTENT(in)                         :: kjpindex     !! Domain size
5670    INTEGER(i_std), INTENT(in)                         :: ins          !! Soiltile index (1-nstm, unitless)
5671    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc         !! Index of the dominant soil textural class in grid cell
5672                                                                       !! (1-nscm, unitless)   
5673   
5674    !! 0.2 Output variables
5675
5676    LOGICAL, DIMENSION(kjpindex,nstm), INTENT(out)     :: is_under_mcr !! Flag diagnosing under residual soil moisture
5677    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check        !! delta SM - flux
5678
5679    !! 0.3 Modified variables
5680
5681    !! 0.4 Local variables
5682
5683    INTEGER(i_std)                       :: ji,jsl
5684    REAL(r_std)                          :: excess
5685    REAL(r_std), DIMENSION(kjpindex)     :: excessji
5686    REAL(r_std), DIMENSION(kjpindex)     :: tmci      !! total SM at beginning of routine
5687    REAL(r_std), DIMENSION(kjpindex)     :: tmcf      !! total SM at end of routine
5688
5689!_ ================================================================================================================================       
5690
5691    !! 1. We calculate the total SM at the beginning of the routine
5692    IF (check_cwrr2) THEN
5693       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5694       DO jsl = 2,nslm-1
5695          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5696               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5697       ENDDO
5698       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5699    ENDIF
5700
5701    !! 2. Smoothes the profile to avoid negative values of punctual soil moisture
5702
5703    ! 2.1 smoothing from top to bottom
5704    DO jsl = 1,nslm-2
5705       DO ji=1, kjpindex
5706          excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
5707          mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5708          mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) - excess * &
5709               &  (dz(jsl)+dz(jsl+1))/(dz(jsl+1)+dz(jsl+2))
5710       ENDDO
5711    ENDDO
5712
5713    jsl = nslm-1
5714    DO ji=1, kjpindex
5715       excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
5716       mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5717       mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) - excess * &
5718            &  (dz(jsl)+dz(jsl+1))/dz(jsl+1)
5719    ENDDO
5720
5721    jsl = nslm
5722    DO ji=1, kjpindex
5723       excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
5724       mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5725       mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) - excess * &
5726            &  dz(jsl)/(dz(jsl-1)+dz(jsl))
5727    ENDDO
5728
5729    ! 2.2 smoothing from bottom to top
5730    DO jsl = nslm-1,2,-1
5731       DO ji=1, kjpindex
5732          excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
5733          mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5734          mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) - excess * &
5735               &  (dz(jsl)+dz(jsl+1))/(dz(jsl-1)+dz(jsl))
5736       ENDDO
5737    ENDDO
5738
5739    ! 2.3 diagnoses is_under_mcr(ji), and updates the entire profile
5740    ! excess > 0
5741    DO ji=1, kjpindex
5742       excessji(ji) = mask_soiltile(ji,ins) * MAX(mcr(njsc(ji))-mc(ji,1,ins),zero)
5743    ENDDO
5744    DO ji=1, kjpindex
5745       mc(ji,1,ins) = mc(ji,1,ins) + excessji(ji) ! then mc(1)=mcr
5746       is_under_mcr(ji,ins) = (excessji(ji) .GT. min_sechiba)
5747    ENDDO
5748
5749    ! 2.4 The amount of water corresponding to excess in the top soil layer is redistributed in all soil layers
5750      ! -excess(ji) * dz(2) / deux donne le deficit total, negatif, en mm
5751      ! diviser par la profondeur totale en mm donne des delta_mc identiques en chaque couche, en mm
5752      ! retransformes en delta_mm par couche selon les bonnes eqs (eqs_hydrol.pdf, Eqs 13-15), puis sommes
5753      ! retourne bien le deficit total en mm
5754    DO jsl = 1, nslm
5755       DO ji=1, kjpindex
5756          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excessji(ji) * dz(2) / (deux * zmaxh*mille)
5757       ENDDO
5758    ENDDO
5759    ! This can lead to mc(jsl) < mcr depending on the value of excess,
5760    ! but this is no major pb for the diffusion
5761    ! Yet, we need to prevent evaporation if is_under_mcr
5762   
5763    !! Note that we check that mc > min_sechiba in hydrol_soil
5764
5765    ! We just make sure that mc remains at 0 where soiltile=0
5766    DO jsl = 1, nslm
5767       DO ji=1, kjpindex
5768          mc(ji,jsl,ins) = mask_soiltile(ji,ins) * mc(ji,jsl,ins)
5769       ENDDO
5770    ENDDO
5771
5772    !! 3. For water conservation check, We calculate the total SM at the beginning of the routine,
5773    !!    and export the difference with the flux
5774    IF (check_cwrr2) THEN
5775       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5776       DO jsl = 2,nslm-1
5777          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5778               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5779       ENDDO
5780       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5781       ! Normally, tcmf=tmci since we just redistribute the deficit
5782       check(:,ins) = tmcf(:)-tmci(:)
5783    ENDIF
5784       
5785  END SUBROUTINE hydrol_soil_smooth_under_mcr
5786
5787
5788!! ================================================================================================================================
5789!! SUBROUTINE   : hydrol_soil_smooth_over_mcs
5790!!
5791!>\BRIEF        : Modifies the soil moisture profile to avoid over-saturation values,
5792!!                by putting the excess in ru_ns
5793!!                Thus, no point remain where such "excess" values remain (is_over_mcs becomes useless)
5794!!
5795!! DESCRIPTION  :
5796!! The "excesses" over-saturation are corrected from top to bottom, by transfer of excesses
5797!! to the lower layers. The reverse transfer is performed to smooth any remaining "excess" in the bottom layer.
5798!! If some "excess" remain afterwards, the entire soil profile is at the threshold value (mcs or mcr),
5799!! and the remaining "excess" is necessarily concentrated in the top layer.
5800!! Eventually, the remaining "excess" creates rudr_corr, to be added to ru_ns or dr_ns
5801!! 1. We calculate the total SM at the beginning of the routine
5802!! 2. In case of over-saturation we put the water where it is possible by smoothing
5803!! 3. The excess is transformed into surface runoff, with conversion from m3/m3 to kg/m2
5804!! 4. For water conservation checks, we calculate the total SM at the beginning of the routine,
5805!!    and export the difference with the flux
5806!!
5807!! RECENT CHANGE(S) : 2016 by A. Ducharne
5808!!
5809!! MAIN OUTPUT VARIABLE(S) :
5810!!
5811!! REFERENCE(S) :
5812!!
5813!! FLOWCHART    : None
5814!! \n
5815!_ ================================================================================================================================
5816!_ hydrol_soil_smooth_over_mcs
5817
5818  SUBROUTINE hydrol_soil_smooth_over_mcs(kjpindex, ins, njsc, is_over_mcs, rudr_corr, check)
5819
5820    !- arguments
5821
5822    !! 0. Variable and parameter declaration
5823
5824    !! 0.1 Input variables
5825
5826    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size
5827    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless)
5828    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell
5829                                                                            !! (1-nscm, unitless)
5830   
5831    !! 0.2 Output variables
5832
5833    LOGICAL, DIMENSION(kjpindex), INTENT(out)            :: is_over_mcs     !! Flag diagnosing over saturated soil moisture 
5834    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out)   :: check           !! delta SM - flux
5835   
5836    !! 0.3 Modified variables   
5837    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(inout):: rudr_corr         !! Surface runoff produced to correct excess (mm/dtstep)
5838
5839    !! 0.4 Local variables
5840
5841    INTEGER(i_std)                        :: ji,jsl
5842    REAL(r_std)                           :: excess
5843    REAL(r_std), DIMENSION(kjpindex)      :: tmci    !! total SM at beginning of routine
5844    REAL(r_std), DIMENSION(kjpindex)      :: tmcf    !! total SM at end of routine
5845
5846    !_ ================================================================================================================================
5847
5848    !! 1. We calculate the total SM at the beginning of the routine
5849    IF (check_cwrr2) THEN
5850       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5851       DO jsl = 2,nslm-1
5852          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5853               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5854       ENDDO
5855       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5856    ENDIF
5857
5858    !! 2. In case of over-saturation we put the water where it is possible by smoothing
5859
5860    ! 2.1 smoothing from top to bottom
5861    DO jsl = 1, nslm-2
5862       DO ji=1, kjpindex
5863          excess = MAX(mc(ji,jsl,ins)-mcs(njsc(ji)),zero)
5864          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5865          mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) + excess * &
5866               &  (dz(jsl)+dz(jsl+1))/(dz(jsl+1)+dz(jsl+2))
5867       ENDDO
5868    ENDDO
5869
5870    jsl = nslm-1
5871    DO ji=1, kjpindex
5872       excess = MAX(mc(ji,jsl,ins)-mcs(njsc(ji)),zero)
5873       mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5874       mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) + excess * &
5875            &  (dz(jsl)+dz(jsl+1))/dz(jsl+1)
5876    ENDDO
5877
5878    jsl = nslm
5879    DO ji=1, kjpindex
5880       excess = MAX(mc(ji,jsl,ins)-mcs(njsc(ji)),zero)
5881       mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5882       mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) + excess * &
5883            &  dz(jsl)/(dz(jsl-1)+dz(jsl))
5884    ENDDO
5885
5886    ! 2.2 smoothing from bottom to top, leading  to keep most of the excess in the soil column
5887    DO jsl = nslm-1,2,-1
5888       DO ji=1, kjpindex
5889          excess = MAX(mc(ji,jsl,ins)-mcs(njsc(ji)),zero)
5890          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5891          mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) + excess * &
5892               &  (dz(jsl)+dz(jsl+1))/(dz(jsl-1)+dz(jsl))
5893       ENDDO
5894    ENDDO
5895
5896    !! 3. The excess is transformed into surface runoff, with conversion from m3/m3 to kg/m2
5897
5898    DO ji=1, kjpindex
5899       excess = mask_soiltile(ji,ins) * MAX(mc(ji,1,ins)-mcs(njsc(ji)),zero)
5900       mc(ji,1,ins) = mc(ji,1,ins) - excess ! then mc(1)=mcs
5901       rudr_corr(ji,ins) = rudr_corr(ji,ins) + excess * dz(2) / deux 
5902       is_over_mcs(ji) = .FALSE.
5903    ENDDO
5904
5905    !! 4. For water conservation checks, we calculate the total SM at the beginning of the routine,
5906    !!    and export the difference with the flux
5907
5908    IF (check_cwrr2) THEN
5909       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5910       DO jsl = 2,nslm-1
5911          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5912               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5913       ENDDO
5914       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5915       ! Normally, tcmf=tmci-rudr_corr
5916       check(:,ins) = tmcf(:)-(tmci(:)-rudr_corr(:,ins))
5917    ENDIF
5918   
5919  END SUBROUTINE hydrol_soil_smooth_over_mcs
5920
5921 !! ================================================================================================================================
5922!! SUBROUTINE   : hydrol_soil_smooth_over_mcs2
5923!!
5924!>\BRIEF        : Modifies the soil moisture profile to avoid over-saturation values,
5925!!                by putting the excess in ru_ns
5926!!                Thus, no point remain where such "excess" values remain (is_over_mcs becomes useless)
5927!!
5928!! DESCRIPTION  :
5929!! The "excesses" over-saturation are corrected, by directly discarding the excess as rudr_corr,
5930!! to be added to ru_ns or dr_nsrunoff (via rudr_corr).
5931!! Therefore, there is no more smoothing, and this helps preventing the saturation of too many layers,
5932!! which leads to numerical errors with tridiag.
5933!! 1. We calculate the total SM at the beginning of the routine
5934!! 2. In case of over-saturation, we directly eliminate the excess via rudr_corr
5935!!    The calculation of the adjustement flux needs to account for nodes n-1 and n+1.
5936!! 3. For water conservation checks, we calculate the total SM at the beginning of the routine,
5937!!    and export the difference with the flux   
5938!!
5939!! RECENT CHANGE(S) : 2016 by A. Ducharne
5940!!
5941!! MAIN OUTPUT VARIABLE(S) :
5942!!
5943!! REFERENCE(S) :
5944!!
5945!! FLOWCHART    : None
5946!! \n
5947!_ ================================================================================================================================
5948!_ hydrol_soil_smooth_over_mcs2
5949
5950  SUBROUTINE hydrol_soil_smooth_over_mcs2(kjpindex, ins, njsc, is_over_mcs, rudr_corr, check)
5951
5952    !- arguments
5953
5954    !! 0. Variable and parameter declaration
5955
5956    !! 0.1 Input variables
5957
5958    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size
5959    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless)
5960    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell
5961                                                                            !! (1-nscm, unitless)
5962   
5963    !! 0.2 Output variables
5964
5965    LOGICAL, DIMENSION(kjpindex), INTENT(out)            :: is_over_mcs     !! Flag diagnosing over saturated soil moisture 
5966    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out)   :: check           !! delta SM - flux
5967   
5968    !! 0.3 Modified variables   
5969    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(inout):: rudr_corr         !! Surface runoff produced to correct excess (mm/dtstep)
5970
5971    !! 0.4 Local variables
5972
5973    INTEGER(i_std)                        :: ji,jsl
5974    REAL(r_std), DIMENSION(kjpindex,nslm) :: excess
5975    REAL(r_std), DIMENSION(kjpindex)      :: tmci    !! total SM at beginning of routine
5976    REAL(r_std), DIMENSION(kjpindex)      :: tmcf    !! total SM at end of routine
5977
5978!_ ================================================================================================================================       
5979    !-
5980
5981    !! 1. We calculate the total SM at the beginning of the routine
5982    IF (check_cwrr2) THEN
5983       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5984       DO jsl = 2,nslm-1
5985          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5986               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5987       ENDDO
5988       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5989    ENDIF 
5990
5991    !! 2. In case of over-saturation, we don't do any smoothing,
5992    !! but directly eliminate the excess as runoff (via rudr_corr)
5993    !    we correct the calculation of the adjustement flux, which needs to account for nodes n-1 and n+1 
5994    !    for the calculation to remain simple and accurate, we directly drain all the oversaturated mc,
5995    !    without transfering to lower layers       
5996
5997    !! 2.1 thresholding from top to bottom, with excess defined along jsl
5998    DO jsl = 1, nslm
5999       DO ji=1, kjpindex
6000          excess(ji,jsl) = MAX(mc(ji,jsl,ins)-mcs(njsc(ji)),zero) ! >=0
6001          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess(ji,jsl) ! here mc either does not change or decreases
6002       ENDDO
6003    ENDDO
6004
6005    !! 2.2 To ensure conservation, this needs to be balanced by additional drainage (in kg/m2/dt)                       
6006    DO ji = 1, kjpindex
6007       rudr_corr(ji,ins) = dz(2) * ( trois*excess(ji,1) + excess(ji,2) )/huit ! top layer = initialisation 
6008    ENDDO
6009    DO jsl = 2,nslm-1 ! intermediate layers     
6010       DO ji = 1, kjpindex
6011          rudr_corr(ji,ins) = rudr_corr(ji,ins) + dz(jsl) &
6012               & * (trois*excess(ji,jsl)+excess(ji,jsl-1))/huit &
6013               & + dz(jsl+1) * (trois*excess(ji,jsl)+excess(ji,jsl+1))/huit
6014       ENDDO
6015    ENDDO
6016    DO ji = 1, kjpindex
6017       rudr_corr(ji,ins) = rudr_corr(ji,ins) + dz(nslm) &    ! bottom layer
6018            & * (trois * excess(ji,nslm) + excess(ji,nslm-1))/huit
6019       is_over_mcs(ji) = .FALSE. 
6020    END DO
6021
6022    !! 3. For water conservation checks, we calculate the total SM at the beginning of the routine,
6023    !!    and export the difference with the flux
6024
6025    IF (check_cwrr2) THEN
6026       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
6027       DO jsl = 2,nslm-1
6028          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
6029               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
6030       ENDDO
6031       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
6032       ! Normally, tcmf=tmci-rudr_corr
6033       check(:,ins) = tmcf(:)-(tmci(:)-rudr_corr(:,ins))
6034    ENDIF
6035   
6036  END SUBROUTINE hydrol_soil_smooth_over_mcs2
6037
6038
6039!! ================================================================================================================================
6040!! SUBROUTINE   : hydrol_soil_flux
6041!!
6042!>\BRIEF        : This subroutine diagnoses the vertical liquid water fluxes between the
6043!!                different soil layers, based on each layer water budget. It also checks the
6044!!                corresponding water conservation (during redistribution).
6045!!
6046!! DESCRIPTION  :
6047!! 1. Initialize qflux from the bottom, with dr_ns
6048!! 2. Between layer nslm and nslm-1, by means of water budget knowing mc changes and flux at the lowest interface
6049!! 3. We go up, and deduct qflux(1:nslm-2), still by means of water budget
6050!! 4. Water balance verification: pursuing upward water budget, the flux at the surface should equal -flux_top 
6051!!
6052!! RECENT CHANGE(S) : 2016 by A. Ducharne to fit hydrol_soil
6053!!
6054!! MAIN OUTPUT VARIABLE(S) :
6055!!
6056!! REFERENCE(S) :
6057!!
6058!! FLOWCHART    : None
6059!! \n
6060!_ ================================================================================================================================
6061!_ hydrol_soil_flux
6062
6063  SUBROUTINE hydrol_soil_flux(kjpindex,ins,mclint,flux_top)
6064    !
6065    !! 0. Variable and parameter declaration
6066
6067    !! 0.1 Input variables
6068
6069    INTEGER(i_std), INTENT(in)                         :: kjpindex        !! Domain size
6070    INTEGER(i_std), INTENT(in)                         :: ins             !! index of soil type
6071    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT(in) :: mclint          !! mc values at the beginning of the time step
6072    REAL(r_std), DIMENSION (kjpindex), INTENT(in)      :: flux_top        !! Exfiltration (bare soil evaporation minus infiltration)
6073   
6074    !! 0.2 Output variables
6075
6076    !! 0.3 Modified variables
6077
6078    !! 0.4 Local variables
6079
6080    INTEGER(i_std)                                     :: jsl,ji
6081    REAL(r_std), DIMENSION(kjpindex)                   :: temp
6082
6083    !_ ================================================================================================================================
6084
6085    !- Compute the diffusion flux at every level from bottom to top (using mcl,mclint, and sink values)
6086    DO ji = 1, kjpindex
6087
6088       !! 1. Initialize qflux from the bottom, with dr_ns
6089       jsl = nslm
6090       qflux(ji,jsl,ins) = dr_ns(ji,ins)
6091       !! 2. Between layer nslm and nslm-1, by means of water budget knowing mc changes and flux at the lowest interface
6092       !     qflux is downward
6093       jsl = nslm-1
6094       qflux(ji,jsl,ins) = qflux(ji,jsl+1,ins) & 
6095            &  + (mcl(ji,jsl,ins)-mclint(ji,jsl) &
6096            &  + trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1)) &
6097            &  * (dz(jsl+1)/huit) &
6098            &  + rootsink(ji,jsl+1,ins) 
6099    ENDDO
6100
6101    !! 3. We go up, and deduct qflux(1:nslm-2), still by means of water budget
6102    ! Here, qflux(ji,1,ins) is the downward flux between the top soil layer and the 2nd one
6103    DO jsl = nslm-2,1,-1
6104       DO ji = 1, kjpindex
6105          qflux(ji,jsl,ins) = qflux(ji,jsl+1,ins) & 
6106               &  + (mcl(ji,jsl,ins)-mclint(ji,jsl) &
6107               &  + trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1)) &
6108               &  * (dz(jsl+1)/huit) &
6109               &  + rootsink(ji,jsl+1,ins) &
6110               &  + (dz(jsl+2)/huit) &
6111               &  * (trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1) &
6112               &  + mcl(ji,jsl+2,ins)-mclint(ji,jsl+2)) 
6113       END DO
6114    ENDDO
6115   
6116    !! 4. Water balance verification: pursuing upward water budget, the flux at the surface (temp) should equal -flux_top
6117    DO ji = 1, kjpindex
6118       temp(ji) =  qflux(ji,1,ins) + (dz(2)/huit) &
6119            &  * (trois* (mcl(ji,1,ins)-mclint(ji,1)) + (mcl(ji,2,ins)-mclint(ji,2))) &
6120            &  + rootsink(ji,1,ins)
6121    ENDDO
6122
6123    ! flux_top is positive when upward, while temp is positive when downward
6124    DO ji = 1, kjpindex
6125       IF (ABS(flux_top(ji)+temp(ji)).GT. deux*min_sechiba) THEN
6126          WRITE(numout,*) 'Problem in the water balance, qflux computation', flux_top(ji),temp(ji)
6127          WRITE(numout,*) 'ji', ji, 'jsl',jsl,'ins',ins
6128          WRITE(numout,*) 'mclint', mclint(ji,:)
6129          WRITE(numout,*) 'mcl', mcl(ji,:,ins)
6130          WRITE (numout,*) 'rootsink', rootsink(ji,1,ins)
6131          CALL ipslerr_p(3, 'hydrol_soil_flux', 'We will STOP now.',&
6132               & 'Problem in the water balance, qflux computation','')
6133       ENDIF
6134    ENDDO
6135
6136  END SUBROUTINE hydrol_soil_flux
6137
6138
6139!! ================================================================================================================================
6140!! SUBROUTINE   : hydrol_soil_tridiag
6141!!
6142!>\BRIEF        This subroutine solves a set of linear equations which has a tridiagonal coefficient matrix.
6143!!
6144!! DESCRIPTION  : It is only applied in the grid-cells where resolv(ji)=TRUE
6145!!
6146!! RECENT CHANGE(S) : None
6147!!
6148!! MAIN OUTPUT VARIABLE(S) : mcl (global module variable)
6149!!
6150!! REFERENCE(S) :
6151!!
6152!! FLOWCHART    : None
6153!! \n
6154!_ ================================================================================================================================
6155!_ hydrol_soil_tridiag
6156
6157  SUBROUTINE hydrol_soil_tridiag(kjpindex,ins)
6158
6159    !- arguments
6160
6161    !! 0. Variable and parameter declaration
6162
6163    !! 0.1 Input variables
6164
6165    INTEGER(i_std), INTENT(in)                         :: kjpindex        !! Domain size
6166    INTEGER(i_std), INTENT(in)                         :: ins             !! number of soil type
6167
6168    !! 0.2 Output variables
6169
6170    !! 0.3 Modified variables
6171
6172    !! 0.4 Local variables
6173
6174    INTEGER(i_std)                                     :: ji,jsl
6175    REAL(r_std), DIMENSION(kjpindex)                   :: bet
6176    REAL(r_std), DIMENSION(kjpindex,nslm)              :: gam
6177
6178!_ ================================================================================================================================
6179    DO ji = 1, kjpindex
6180
6181       IF (resolv(ji)) THEN
6182          bet(ji) = tmat(ji,1,2)
6183          mcl(ji,1,ins) = rhs(ji,1)/bet(ji)
6184       ENDIF
6185    ENDDO
6186
6187    DO jsl = 2,nslm
6188       DO ji = 1, kjpindex
6189         
6190          IF (resolv(ji)) THEN
6191
6192             gam(ji,jsl) = tmat(ji,jsl-1,3)/bet(ji)
6193             bet(ji) = tmat(ji,jsl,2) - tmat(ji,jsl,1)*gam(ji,jsl)
6194             mcl(ji,jsl,ins) = (rhs(ji,jsl)-tmat(ji,jsl,1)*mcl(ji,jsl-1,ins))/bet(ji)
6195          ENDIF
6196
6197       ENDDO
6198    ENDDO
6199
6200    DO ji = 1, kjpindex
6201       IF (resolv(ji)) THEN
6202          DO jsl = nslm-1,1,-1
6203             mcl(ji,jsl,ins) = mcl(ji,jsl,ins) - gam(ji,jsl+1)*mcl(ji,jsl+1,ins)
6204          ENDDO
6205       ENDIF
6206    ENDDO
6207
6208  END SUBROUTINE hydrol_soil_tridiag
6209
6210
6211!! ================================================================================================================================
6212!! SUBROUTINE   : hydrol_soil_coef
6213!!
6214!>\BRIEF        Computes coef for the linearised hydraulic conductivity
6215!! k_lin=a_lin mc_lin+b_lin and the linearised diffusivity d_lin.
6216!!
6217!! DESCRIPTION  :
6218!! First, we identify the interval i in which the current value of mc is located.
6219!! Then, we give the values of the linearized parameters to compute
6220!! conductivity and diffusivity as K=a*mc+b and d.
6221!!
6222!! RECENT CHANGE(S) : Addition of the dependence to profil_froz_hydro_ns
6223!!
6224!! MAIN OUTPUT VARIABLE(S) :
6225!!
6226!! REFERENCE(S) :
6227!!
6228!! FLOWCHART    : None
6229!! \n
6230!_ ================================================================================================================================
6231!_ hydrol_soil_coef
6232 
6233  SUBROUTINE hydrol_soil_coef(kjpindex,ins,njsc)
6234
6235    IMPLICIT NONE
6236    !
6237    !! 0. Variable and parameter declaration
6238
6239    !! 0.1 Input variables
6240
6241    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size
6242    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type
6243    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
6244
6245    !! 0.2 Output variables
6246
6247    !! 0.3 Modified variables
6248
6249    !! 0.4 Local variables
6250
6251    INTEGER(i_std)                                    :: jsl,ji,i
6252    REAL(r_std)                                       :: mc_ratio
6253    REAL(r_std)                                       :: mc_used    !! Used liquid water content
6254    REAL(r_std)                                       :: x,m
6255   
6256!_ ================================================================================================================================
6257
6258    IF (ok_freeze_cwrr) THEN
6259   
6260       ! Calculation of liquid and frozen saturation degrees with respect to residual
6261       ! x=liquid saturation degree/residual=(mcl-mcr)/(mcs-mcr)
6262       ! 1-x=frozen saturation degree/residual=(mcfc-mcr)/(mcs-mcr) (=profil_froz_hydro)
6263       
6264       DO jsl=1,nslm
6265          DO ji=1,kjpindex
6266             
6267             x = 1._r_std - profil_froz_hydro_ns(ji, jsl,ins)
6268             
6269             ! mc_used is used in the calculation of hydrological properties
6270             ! It corresponds to a liquid mc, but the expression is different from mcl in hydrol_soil,
6271             ! to ensure that we get the a, b, d of the first bin when mcl<mcr
6272             mc_used = mcr(njsc(ji))+x*MAX((mc(ji,jsl, ins)-mcr(njsc(ji))),zero) 
6273             !
6274             ! calcul de k based on mc_liq
6275             !
6276             i= MAX(imin, MIN(imax-1, INT(imin +(imax-imin)*(mc_used-mcr(njsc(ji)))/(mcs(njsc(ji))-mcr(njsc(ji))))))
6277             a(ji,jsl) = a_lin(i,jsl,njsc(ji)) * kfact_root(ji,jsl,ins) ! in mm/d
6278             b(ji,jsl) = b_lin(i,jsl,njsc(ji)) * kfact_root(ji,jsl,ins) ! in mm/d
6279             d(ji,jsl) = d_lin(i,jsl,njsc(ji)) * kfact_root(ji,jsl,ins) ! in mm^2/d
6280             k(ji,jsl) = kfact_root(ji,jsl,ins) * MAX(k_lin(imin+1,jsl,njsc(ji)), &
6281                  a_lin(i,jsl,njsc(ji)) * mc_used + b_lin(i,jsl,njsc(ji))) ! in mm/d
6282          ENDDO ! loop on grid
6283       ENDDO
6284             
6285    ELSE
6286       ! .NOT. ok_freeze_cwrr
6287       DO jsl=1,nslm
6288          DO ji=1,kjpindex 
6289             
6290             ! it is impossible to consider a mc<mcr for the binning
6291             mc_ratio = MAX(mc(ji,jsl,ins)-mcr(njsc(ji)), zero)/(mcs(njsc(ji))-mcr(njsc(ji)))
6292             
6293             i= MAX(MIN(INT((imax-imin)*mc_ratio)+imin , imax-1), imin)
6294             a(ji,jsl) = a_lin(i,jsl,njsc(ji)) * kfact_root(ji,jsl,ins) ! in mm/d
6295             b(ji,jsl) = b_lin(i,jsl,njsc(ji)) * kfact_root(ji,jsl,ins) ! in mm/d
6296             d(ji,jsl) = d_lin(i,jsl,njsc(ji)) * kfact_root(ji,jsl,ins) ! in mm^2/d
6297             k(ji,jsl) = kfact_root(ji,jsl,ins) * MAX(k_lin(imin+1,jsl,njsc(ji)), &
6298                  a_lin(i,jsl,njsc(ji)) * mc(ji,jsl,ins) + b_lin(i,jsl,njsc(ji)))  ! in mm/d
6299          END DO
6300       END DO
6301    ENDIF
6302   
6303  END SUBROUTINE hydrol_soil_coef
6304
6305!! ================================================================================================================================
6306!! SUBROUTINE   : hydrol_soil_froz
6307!!
6308!>\BRIEF        Computes profil_froz_hydro_ns, the fraction of frozen water in the soil layers.
6309!!
6310!! DESCRIPTION  :
6311!!
6312!! RECENT CHANGE(S) : Created by A. Ducharne in 2016.
6313!!
6314!! MAIN OUTPUT VARIABLE(S) : profil_froz_hydro_ns
6315!!
6316!! REFERENCE(S) :
6317!!
6318!! FLOWCHART    : None
6319!! \n
6320!_ ================================================================================================================================
6321!_ hydrol_soil_froz
6322 
6323  SUBROUTINE hydrol_soil_froz(kjpindex,ins,njsc)
6324
6325    IMPLICIT NONE
6326    !
6327    !! 0. Variable and parameter declaration
6328
6329    !! 0.1 Input variables
6330
6331    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size
6332    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type
6333    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
6334
6335    !! 0.2 Output variables
6336
6337    !! 0.3 Modified variables
6338
6339    !! 0.4 Local variables
6340
6341    INTEGER(i_std)                                    :: jsl,ji,i
6342    REAL(r_std)                                       :: x,m
6343    REAL(r_std)                                       :: denom
6344    REAL(r_std),DIMENSION (kjpindex)                  :: froz_frac_moy
6345    REAL(r_std),DIMENSION (kjpindex)                  :: smtot_moy
6346    REAL(r_std),DIMENSION (kjpindex,nslm)             :: mc_ns
6347   
6348!_ ================================================================================================================================
6349
6350!    ONLY FOR THE (ok_freeze_cwrr) CASE
6351   
6352       ! Calculation of liquid and frozen saturation degrees above residual moisture
6353       !   x=liquid saturation degree/residual=(mcl-mcr)/(mcs-mcr)
6354       !   1-x=frozen saturation degree/residual=(mcfc-mcr)/(mcs-mcr) (=profil_froz_hydro)
6355       ! It's important for the good work of the water diffusion scheme (tridiag) that the total
6356       ! liquid water also includes mcr, so mcl > 0 even when x=0
6357       
6358       DO jsl=1,nslm
6359          DO ji=1,kjpindex
6360             ! Van Genuchten parameter for thermodynamical calculation
6361             m = 1. -1./nvan(njsc(ji))
6362           
6363             IF ((.NOT. ok_thermodynamical_freezing).OR.(mc(ji,jsl, ins).LT.(mcr(njsc(ji))+min_sechiba))) THEN
6364                ! Linear soil freezing or soil moisture below residual
6365                IF (temp_hydro(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN
6366                   x=1._r_std
6367                ELSE IF ( (temp_hydro(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &
6368                     (temp_hydro(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN
6369                   x=(temp_hydro(ji, jsl)-(ZeroCelsius-fr_dT/2.))/fr_dT
6370                ELSE
6371                   x=0._r_std
6372                ENDIF
6373             ELSE IF (ok_thermodynamical_freezing) THEN
6374                ! Thermodynamical soil freezing
6375                IF (temp_hydro(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN
6376                   x=1._r_std
6377                ELSE IF ( (temp_hydro(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &
6378                     (temp_hydro(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN
6379                   ! Factor 2.2 from the PhD of Isabelle Gouttevin
6380                   x=MIN(((mcs(njsc(ji))-mcr(njsc(ji))) &
6381                        *((2.2*1000.*avan(njsc(ji))*(ZeroCelsius+fr_dT/2.-temp_hydro(ji, jsl)) &
6382                        *lhf/ZeroCelsius/10.)**nvan(njsc(ji))+1.)**(-m)) / &
6383                        (mc(ji,jsl, ins)-mcr(njsc(ji))),1._r_std)               
6384                ELSE
6385                   x=0._r_std 
6386                ENDIF
6387             ENDIF
6388             
6389             profil_froz_hydro_ns(ji,jsl,ins) = 1._r_std-x
6390             
6391             mc_ns(ji,jsl)=mc(ji,jsl,ins)/mcs(njsc(ji))
6392
6393          ENDDO ! loop on grid
6394       ENDDO
6395   
6396       ! Applay correction on the frozen fraction
6397       ! Depends on two external parameters: froz_frac_corr and smtot_corr
6398       froz_frac_moy(:)=zero
6399       denom=zero
6400       DO jsl=1,nslm
6401          froz_frac_moy(:)=froz_frac_moy(:)+dh(jsl)*profil_froz_hydro_ns(:,jsl,ins)
6402          denom=denom+dh(jsl)
6403       ENDDO
6404       froz_frac_moy(:)=froz_frac_moy(:)/denom
6405
6406       smtot_moy(:)=zero
6407       denom=zero
6408       DO jsl=1,nslm-1
6409          smtot_moy(:)=smtot_moy(:)+dh(jsl)*mc_ns(:,jsl)
6410          denom=denom+dh(jsl)
6411       ENDDO
6412       smtot_moy(:)=smtot_moy(:)/denom
6413
6414       DO jsl=1,nslm
6415          profil_froz_hydro_ns(:,jsl,ins)=MIN(profil_froz_hydro_ns(:,jsl,ins)* &
6416                                              (froz_frac_moy(:)**froz_frac_corr)*(smtot_moy(:)**smtot_corr), max_froz_hydro)
6417       ENDDO
6418
6419     END SUBROUTINE hydrol_soil_froz
6420     
6421
6422!! ================================================================================================================================
6423!! SUBROUTINE   : hydrol_soil_setup
6424!!
6425!>\BRIEF        This subroutine computes the matrix coef. 
6426!!
6427!! DESCRIPTION  : None
6428!!
6429!! RECENT CHANGE(S) : None
6430!!
6431!! MAIN OUTPUT VARIABLE(S) : matrix coef
6432!!
6433!! REFERENCE(S) :
6434!!
6435!! FLOWCHART    : None
6436!! \n
6437!_ ================================================================================================================================
6438
6439  SUBROUTINE hydrol_soil_setup(kjpindex,ins)
6440
6441
6442    IMPLICIT NONE
6443    !
6444    !! 0. Variable and parameter declaration
6445
6446    !! 0.1 Input variables
6447    INTEGER(i_std), INTENT(in)                        :: kjpindex          !! Domain size
6448    INTEGER(i_std), INTENT(in)                        :: ins               !! index of soil type
6449
6450    !! 0.2 Output variables
6451
6452    !! 0.3 Modified variables
6453
6454    !! 0.4 Local variables
6455
6456    INTEGER(i_std) :: jsl,ji
6457    REAL(r_std)                        :: temp3, temp4
6458
6459!_ ================================================================================================================================
6460    !-we compute tridiag matrix coefficients (LEFT and RIGHT)
6461    ! of the system to solve [LEFT]*mc_{t+1}=[RIGHT]*mc{t}+[add terms]:
6462    ! e(nslm),f(nslm),g1(nslm) for the [left] vector
6463    ! and ep(nslm),fp(nslm),gp(nslm) for the [right] vector
6464
6465    ! w_time=1 (in constantes_soil) indicates implicit computation for diffusion
6466    temp3 = w_time*(dt_sechiba/one_day)/deux
6467    temp4 = (un-w_time)*(dt_sechiba/one_day)/deux
6468
6469    ! Passage to arithmetic means for layer averages also in this subroutine : Aurelien 11/05/10
6470
6471    !- coefficient for first layer
6472    DO ji = 1, kjpindex
6473       e(ji,1) = zero
6474       f(ji,1) = trois * dz(2)/huit  + temp3 &
6475            & * ((d(ji,1)+d(ji,2))/(dz(2))+a(ji,1))
6476       g1(ji,1) = dz(2)/(huit)       - temp3 &
6477            & * ((d(ji,1)+d(ji,2))/(dz(2))-a(ji,2))
6478       ep(ji,1) = zero
6479       fp(ji,1) = trois * dz(2)/huit - temp4 &
6480            & * ((d(ji,1)+d(ji,2))/(dz(2))+a(ji,1))
6481       gp(ji,1) = dz(2)/(huit)       + temp4 &
6482            & * ((d(ji,1)+d(ji,2))/(dz(2))-a(ji,2))
6483    ENDDO
6484
6485    !- coefficient for medium layers
6486
6487    DO jsl = 2, nslm-1
6488       DO ji = 1, kjpindex
6489          e(ji,jsl) = dz(jsl)/(huit)                        - temp3 &
6490               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl))+a(ji,jsl-1))
6491
6492          f(ji,jsl) = trois * (dz(jsl)+dz(jsl+1))/huit  + temp3 &
6493               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl)) + &
6494               & (d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1)) )
6495
6496          g1(ji,jsl) = dz(jsl+1)/(huit)                     - temp3 &
6497               & * ((d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1))-a(ji,jsl+1))
6498
6499          ep(ji,jsl) = dz(jsl)/(huit)                       + temp4 &
6500               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl))+a(ji,jsl-1))
6501
6502          fp(ji,jsl) = trois * (dz(jsl)+dz(jsl+1))/huit - temp4 &
6503               & * ( (d(ji,jsl)+d(ji,jsl-1))/(dz(jsl)) + &
6504               & (d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1)) )
6505
6506          gp(ji,jsl) = dz(jsl+1)/(huit)                     + temp4 &
6507               & *((d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1))-a(ji,jsl+1))
6508       ENDDO
6509    ENDDO
6510
6511    !- coefficient for last layer
6512    DO ji = 1, kjpindex
6513       e(ji,nslm) = dz(nslm)/(huit)        - temp3 &
6514            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm))+a(ji,nslm-1))
6515       f(ji,nslm) = trois * dz(nslm)/huit  + temp3 &
6516            & * ((d(ji,nslm)+d(ji,nslm-1)) / (dz(nslm)) &
6517            & -a(ji,nslm)*(un-deux*free_drain_coef(ji,ins)))
6518       g1(ji,nslm) = zero
6519       ep(ji,nslm) = dz(nslm)/(huit)       + temp4 &
6520            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm))+a(ji,nslm-1))
6521       fp(ji,nslm) = trois * dz(nslm)/huit - temp4 &
6522            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm)) &
6523            & -a(ji,nslm)*(un-deux*free_drain_coef(ji,ins)))
6524       gp(ji,nslm) = zero
6525    ENDDO
6526
6527  END SUBROUTINE hydrol_soil_setup
6528
6529 
6530!! ================================================================================================================================
6531!! SUBROUTINE   : hydrol_split_soil
6532!!
6533!>\BRIEF        Splits 2d variables into 3d variables, per soiltile (_ns suffix), at the beginning of hydrol
6534!!              At this stage, the forcing fluxes to hydrol are transformed from grid-cell averages
6535!!              to mean fluxes over vegtot=sum(soiltile) 
6536!!
6537!! DESCRIPTION  :
6538!! 1. Split 2d variables into 3d variables, per soiltile
6539!! 1.1 Throughfall
6540!! 1.2 Bare soil evaporation
6541!! 1.2.1 vevapnu_old
6542!! 1.2.2 ae_ns new
6543!! 1.3 transpiration
6544!! 1.4 root sink
6545!! 2. Verification: Check if the deconvolution is correct and conserves the fluxes
6546!! 2.1 precisol
6547!! 2.2 ae_ns and evapnu
6548!! 2.3 transpiration
6549!! 2.4 root sink
6550!!
6551!! RECENT CHANGE(S) : 2016 by A. Ducharne to match the simplification of hydrol_soil
6552!!
6553!! MAIN OUTPUT VARIABLE(S) :
6554!!
6555!! REFERENCE(S) :
6556!!
6557!! FLOWCHART    : None
6558!! \n
6559!_ ================================================================================================================================
6560!_ hydrol_split_soil
6561
6562  SUBROUTINE hydrol_split_soil (kjpindex, veget_max, soiltile, vevapnu, transpir, humrel, evap_bare_lim, tot_bare_soil)
6563    !
6564    ! interface description
6565
6566    !! 0. Variable and parameter declaration
6567
6568    !! 0.1 Input variables
6569
6570    INTEGER(i_std), INTENT(in)                               :: kjpindex
6571    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(in)       :: veget_max        !! max Vegetation map
6572    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soiltile within vegtot (0-1, unitless)
6573    REAL(r_std), DIMENSION (kjpindex), INTENT (in)           :: vevapnu          !! Bare soil evaporation
6574    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: transpir         !! Transpiration
6575    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: humrel           !! Relative humidity
6576    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evap_bare_lim    !!   
6577    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_bare_soil    !! Total evaporating bare soil fraction
6578
6579    !! 0.4 Local variables
6580
6581    INTEGER(i_std)                                :: ji, jv, jsl, jst
6582    REAL(r_std), DIMENSION (kjpindex)             :: vevapnu_old
6583    REAL(r_std), DIMENSION (kjpindex)             :: tmp_check1
6584    REAL(r_std), DIMENSION (kjpindex)             :: tmp_check2
6585    REAL(r_std), DIMENSION (kjpindex,nstm)        :: tmp_check3
6586    LOGICAL                                       :: error=.FALSE. !! If true, exit in the end of subroutine
6587
6588!_ ================================================================================================================================
6589   
6590    !! 1. Split 2d variables into 3d variables, per soiltile
6591   
6592    ! Reminders:
6593    !  corr_veg_soil(:,nvm,nstm) = PFT fraction per soiltile in each grid-cell
6594    !      corr_veg_soil(ji,jv,jst)=veget_max(ji,jv)/soiltile(ji,jst)
6595    !  soiltile(:,nstm) = fraction of vegtot covered by each soiltile (0-1, unitless)
6596    !  vegtot(:) = total fraction of grid-cell covered by PFTs (fraction with bare soil + vegetation)
6597    !  veget_max(:,nvm) = PFT fractions of vegtot+frac_nobio
6598    !  veget(:,nvm) =  fractions (of vegtot+frac_nobio) covered by vegetation in each PFT
6599    !       BUT veget(:,1)=veget_max(:,1)
6600    !  frac_bare(:,nvm) = fraction (of veget_max) with bare soil in each PFT
6601    !  tot_bare_soil(:) = fraction of grid mesh covered by all bare soil (=SUM(frac_bare*veget_max))
6602    !  frac_bare_ns(:,nstm) = evaporating bare soil fraction (of vegtot) per soiltile (defined in hydrol_vegupd)
6603   
6604    !! 1.1 Throughfall
6605    ! Transformation from precisol (flux from PFT jv in m2 of grid-mesh)
6606    ! to  precisol_ns (flux from contributing PFTs with another unit, in m2 of soiltile)
6607    precisol_ns(:,:)=zero
6608    DO jv=1,nvm
6609       DO ji=1,kjpindex
6610          jst=pref_soil_veg(jv)
6611          IF((veget_max(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT. min_sechiba)) THEN
6612             precisol_ns(ji,jst) = precisol_ns(ji,jst) + &
6613                     precisol(ji,jv) / (soiltile(ji,jst)*vegtot(ji))               
6614          ENDIF
6615       END DO
6616    END DO
6617   
6618    !! 1.2 Bare soil evaporation
6619    !! 1.2.1 vevapnu_old
6620! AD16*** vevapnu_old ne sert que pour le split suivant de vevapnu (issu de enerbil) en ae_ns pour hydrol_soil
6621!           mais il ne semble y avoir aucune bonne raison de contraindre ae_ns en fonction de vevapnu_old
6622    vevapnu_old(:)=zero
6623    DO jst=1,nstm
6624       DO ji=1,kjpindex
6625          IF ( vegtot(ji) .GT. min_sechiba) THEN
6626             vevapnu_old(ji)=vevapnu_old(ji)+ &
6627                  & ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6628          ENDIF
6629       END DO
6630    END DO
6631   
6632    !! 1.2.2 ae_ns new
6633! AD16*** les lignes ci-dessous sont excessivement compliquees et ne garantissent pas que ae_ns = 0 si evap_bare_lim=0
6634!           c'est notamment le cas pour les 3emes et 6emes conditions
6635    DO jst=1,nstm
6636       DO ji=1,kjpindex
6637          IF (vevapnu_old(ji).GT.min_sechiba) THEN   
6638             IF(evap_bare_lim(ji).GT.min_sechiba) THEN       
6639                ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji) 
6640             ELSE
6641                IF(vevapnu_old(ji).GT.min_sechiba) THEN 
6642                   ae_ns(ji,jst)=ae_ns(ji,jst) * vevapnu(ji)/vevapnu_old(ji) ! 3Úme condition
6643                ELSE
6644                   ae_ns(ji,jst)=zero
6645                ENDIF
6646             ENDIF
6647          ELSEIF(frac_bare_ns(ji,jst).GT.min_sechiba) THEN
6648             IF(evap_bare_lim(ji).GT.min_sechiba) THEN 
6649                ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji)
6650             ELSE
6651                IF(tot_bare_soil(ji).GT.min_sechiba) THEN 
6652                   ae_ns(ji,jst) = vevapnu(ji) * frac_bare_ns(ji,jst)/tot_bare_soil(ji) ! 6Úme condition
6653                ELSE
6654                   ae_ns(ji,jst) = zero
6655                ENDIF
6656             ENDIF
6657          ENDIF
6658       END DO
6659    END DO
6660! ADNV27072016: we believe the following block should be used (tests needed before committ, since AD16*** had pb with it)   
6661!!$    ! given the definition of evap_bare_lim, it leads to sum(ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji))=vevapnu(ji)
6662!!$    ae_ns(:,:)=zero
6663!!$    DO jst=1,nstm
6664!!$       DO ji=1,kjpindex
6665!!$          IF(evap_bare_lim(ji).GT.min_sechiba) THEN       
6666!!$             ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji)
6667!            ELSE
6668!               ae_ns(ji,jst) = zero
6669!!$          ENDIF
6670!!$       ENDDO
6671!!$    ENDDO
6672   
6673    !! 1.3 transpiration
6674    ! Transformation from transpir (flux from PFT jv in m2 of grid-mesh)
6675    ! to tr_ns (flux from contributing PFTs with another unit, in m2 of soiltile)
6676    ! To do next: simplify the use of humrelv(ji,jv,jst) /humrel(ji,jv), since both are equal
6677    tr_ns(:,:)=zero
6678    DO jv=1,nvm
6679       jst=pref_soil_veg(jv)
6680       DO ji=1,kjpindex
6681          IF ((humrel(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT.min_sechiba))THEN
6682             tr_ns(ji,jst)= tr_ns(ji,jst) &
6683                  + transpir(ji,jv) * (humrelv(ji,jv,jst) / humrel(ji,jv)) &
6684                  / (soiltile(ji,jst)*vegtot(ji))
6685                     
6686             ENDIF
6687       END DO
6688    END DO
6689
6690    !! 1.4 root sink
6691    ! Transformation from transpir (flux from PFT jv in m2 of grid-mesh)
6692    ! to root_sink (flux from contributing PFTs and soil layer with another unit, in m2 of soiltile)
6693    rootsink(:,:,:)=zero
6694    DO jv=1,nvm
6695       jst=pref_soil_veg(jv)
6696       DO jsl=1,nslm
6697          DO ji=1,kjpindex
6698             IF ((humrel(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT.min_sechiba)) THEN
6699                rootsink(ji,jsl,jst) = rootsink(ji,jsl,jst) &
6700                        + transpir(ji,jv) * (us(ji,jv,jst,jsl) / humrel(ji,jv)) &
6701                        / (soiltile(ji,jst)*vegtot(ji))                     
6702                   ! rootsink(ji,1,jst)=0 as us(ji,jv,jst,1)=0
6703             END IF
6704          END DO
6705       END DO
6706    END DO
6707
6708
6709    !!! ADNV270716 *** we are here
6710
6711    !! 2. Verification: Check if the deconvolution is correct and conserves the fluxes (grid-cell average)
6712
6713    IF (check_cwrr) THEN
6714
6715       !! 2.1 precisol
6716
6717       tmp_check1(:)=zero
6718       DO jst=1,nstm
6719          DO ji=1,kjpindex
6720             tmp_check1(ji)=tmp_check1(ji) + precisol_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6721          END DO
6722       END DO
6723       
6724       tmp_check2(:)=zero 
6725       DO jv=1,nvm
6726          DO ji=1,kjpindex
6727             tmp_check2(ji)=tmp_check2(ji) + precisol(ji,jv)
6728          END DO
6729       END DO
6730
6731       DO ji=1,kjpindex   
6732          IF(ABS(tmp_check1(ji) - tmp_check2(ji)).GT.allowed_err) THEN
6733             WRITE(numout,*) 'PRECISOL SPLIT FALSE:ji=',ji,tmp_check1(ji),tmp_check2(ji)
6734             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- tmp_check2(ji))
6735             WRITE(numout,*) 'vegtot',vegtot(ji)
6736             DO jv=1,nvm
6737                WRITE(numout,'(a,i2.2,"|",F13.4,"|",F13.4,"|",3(F9.6))') &
6738                     'jv,veget_max, precisol, vegetmax_soil ', &
6739                     jv,veget_max(ji,jv),precisol(ji,jv),vegetmax_soil(ji,jv,:)
6740             END DO
6741             DO jst=1,nstm
6742                WRITE(numout,*) 'jst,precisol_ns',jst,precisol_ns(ji,jst)
6743                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
6744             END DO
6745             error=.TRUE.
6746             CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6747                  & 'check_CWRR','PRECISOL SPLIT FALSE')
6748          ENDIF
6749       END DO
6750       
6751       !! 2.2 ae_ns and evapnu
6752
6753       tmp_check1(:)=zero
6754       DO jst=1,nstm
6755          DO ji=1,kjpindex
6756             tmp_check1(ji)=tmp_check1(ji) + ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6757          END DO
6758       END DO
6759
6760       DO ji=1,kjpindex   
6761
6762          IF(ABS(tmp_check1(ji) - vevapnu(ji)).GT.allowed_err) THEN
6763             WRITE(numout,*) 'VEVAPNU SPLIT FALSE:ji, Sum(ae_ns), vevapnu =',ji,tmp_check1(ji),vevapnu(ji)
6764             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- vevapnu(ji))
6765             WRITE(numout,*) 'ae_ns',ae_ns(ji,:)
6766             WRITE(numout,*) 'vegtot',vegtot(ji)
6767             WRITE(numout,*) 'evap_bare_lim, evap_bare_lim_ns',evap_bare_lim(ji), evap_bare_lim_ns(ji,:)
6768             WRITE(numout,*) 'tot_bare_soil,frac_bare_ns',tot_bare_soil(ji),frac_bare_ns(ji,:)
6769             WRITE(numout,*) 'vevapnu_old',vevapnu_old(ji)
6770             DO jst=1,nstm
6771                WRITE(numout,*) 'jst,ae_ns',jst,ae_ns(ji,jst)
6772                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
6773                WRITE(numout,*) 'veget_max/vegtot/soiltile', veget_max(ji,:)/vegtot(ji)/soiltile(ji,jst)
6774                WRITE(numout,*) "vegetmax_soil",vegetmax_soil(ji,:,jst)
6775             END DO
6776             error=.TRUE.
6777             CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6778                  & 'check_CWRR','VEVAPNU SPLIT FALSE')
6779          ENDIF
6780       ENDDO
6781
6782    !! 2.3 transpiration
6783
6784       tmp_check1(:)=zero
6785       DO jst=1,nstm
6786          DO ji=1,kjpindex
6787             tmp_check1(ji)=tmp_check1(ji) + tr_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6788          END DO
6789       END DO
6790       
6791       tmp_check2(:)=zero 
6792       DO jv=1,nvm
6793          DO ji=1,kjpindex
6794             tmp_check2(ji)=tmp_check2(ji) + transpir(ji,jv)
6795          END DO
6796       END DO
6797
6798       DO ji=1,kjpindex   
6799          IF(ABS(tmp_check1(ji)- tmp_check2(ji)).GT.allowed_err) THEN
6800             WRITE(numout,*) 'TRANSPIR SPLIT FALSE:ji=',ji,tmp_check1(ji),tmp_check2(ji)
6801             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- tmp_check2(ji))
6802             WRITE(numout,*) 'vegtot',vegtot(ji)
6803             DO jv=1,nvm
6804                WRITE(numout,*) 'jv,veget_max, transpir',jv,veget_max(ji,jv),transpir(ji,jv)
6805                DO jst=1,nstm
6806                   WRITE(numout,*) 'vegetmax_soil:ji,jv,jst',ji,jv,jst,vegetmax_soil(ji,jv,jst)
6807                END DO
6808             END DO
6809             DO jst=1,nstm
6810                WRITE(numout,*) 'jst,tr_ns',jst,tr_ns(ji,jst)
6811                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
6812             END DO
6813             error=.TRUE.
6814             CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6815                  & 'check_CWRR','TRANSPIR SPLIT FALSE')
6816          ENDIF
6817
6818       END DO
6819
6820    !! 2.4 root sink
6821
6822       tmp_check3(:,:)=zero
6823       DO jst=1,nstm
6824          DO jsl=1,nslm
6825             DO ji=1,kjpindex
6826                tmp_check3(ji,jst)=tmp_check3(ji,jst) + rootsink(ji,jsl,jst)
6827             END DO
6828          END DO
6829       ENDDO
6830
6831       DO jst=1,nstm
6832          DO ji=1,kjpindex
6833             IF(ABS(tmp_check3(ji,jst) - tr_ns(ji,jst)).GT.allowed_err) THEN
6834                WRITE(numout,*) 'ROOTSINK SPLIT FALSE:ji,jst=', ji,jst,&
6835                     & tmp_check3(ji,jst),tr_ns(ji,jst)
6836                WRITE(numout,*) 'err',ABS(tmp_check3(ji,jst)- tr_ns(ji,jst))
6837                WRITE(numout,*) 'HUMREL(jv=1:13)',humrel(ji,:)
6838                WRITE(numout,*) 'TRANSPIR',transpir(ji,:)
6839                DO jv=1,nvm 
6840                   WRITE(numout,*) 'jv=',jv,'us=',us(ji,jv,jst,:)
6841                ENDDO
6842                error=.TRUE.
6843                CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6844                  & 'check_CWRR','ROOTSINK SPLIT FALSE')
6845             ENDIF
6846          END DO
6847       END DO
6848
6849    ENDIF ! end of check_cwrr
6850
6851!! Exit if error was found previously in this subroutine
6852    IF ( error ) THEN
6853       WRITE(numout,*) 'One or more errors have been detected in hydrol_split_soil. Model stops.'
6854       CALL ipslerr_p(3, 'hydrol_split_soil', 'We will STOP now.',&
6855                  & 'One or several fatal errors were found previously.','')
6856    END IF
6857
6858  END SUBROUTINE hydrol_split_soil
6859 
6860
6861!! ================================================================================================================================
6862!! SUBROUTINE   : hydrol_diag_soil
6863!!
6864!>\BRIEF        Calculates diagnostic variables at the grid-cell scale
6865!!
6866!! DESCRIPTION  :
6867!! - 1. Apply mask_soiltile
6868!! - 2. Sum 3d variables in 2d variables with fraction of vegetation per soil type
6869!!
6870!! RECENT CHANGE(S) : 2016 by A. Ducharne for the claculation of shumdiag_perma
6871!!
6872!! MAIN OUTPUT VARIABLE(S) :
6873!!
6874!! REFERENCE(S) :
6875!!
6876!! FLOWCHART    : None
6877!! \n
6878!_ ================================================================================================================================
6879!_ hydrol_diag_soil
6880
6881  SUBROUTINE hydrol_diag_soil (kjpindex, veget_max, soiltile, njsc, runoff, drainage, &
6882       & evapot, vevapnu, returnflow, reinfiltration, irrigation, &
6883       & shumdiag,shumdiag_perma, k_litt, litterhumdiag, humrel, vegstress, drysoil_frac, tot_melt)
6884    !
6885    ! interface description
6886
6887    !! 0. Variable and parameter declaration
6888
6889    !! 0.1 Input variables
6890
6891    ! input scalar
6892    INTEGER(i_std), INTENT(in)                               :: kjpindex 
6893    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: veget_max       !! Max. vegetation type
6894    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc            !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
6895    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile        !! Fraction of each soil tile within vegtot (0-1, unitless)
6896    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot          !!
6897    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow      !! Water returning to the deep reservoir
6898    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: reinfiltration  !! Water returning to the top of the soil
6899    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: irrigation      !! Water from irrigation
6900    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_melt        !!
6901
6902    !! 0.2 Output variables
6903
6904    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: drysoil_frac    !! Function of litter wetness
6905    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: runoff          !! complete runoff
6906    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drainage        !! Drainage
6907    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)      :: shumdiag        !! relative soil moisture
6908    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)      :: shumdiag_perma  !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
6909    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: k_litt          !! litter cond.
6910    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: litterhumdiag   !! litter humidity
6911    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)       :: humrel          !! Relative humidity
6912    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(out)      :: vegstress       !! Veg. moisture stress (only for vegetation growth)
6913 
6914    !! 0.3 Modified variables
6915
6916    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapnu         !!
6917
6918    !! 0.4 Local variables
6919
6920    INTEGER(i_std)                                           :: ji, jv, jsl, jst, i
6921    REAL(r_std), DIMENSION (kjpindex)                        :: mask_vegtot
6922    REAL(r_std)                                              :: k_tmp, tmc_litter_ratio
6923
6924!_ ================================================================================================================================
6925    !
6926    ! Put the prognostics variables of soil to zero if soiltype is zero
6927
6928    !! 1. Apply mask_soiltile
6929   
6930    DO jst=1,nstm 
6931       DO ji=1,kjpindex
6932
6933             ae_ns(ji,jst) = ae_ns(ji,jst) * mask_soiltile(ji,jst)
6934             dr_ns(ji,jst) = dr_ns(ji,jst) * mask_soiltile(ji,jst)
6935             ru_ns(ji,jst) = ru_ns(ji,jst) * mask_soiltile(ji,jst)
6936             tmc(ji,jst) =  tmc(ji,jst) * mask_soiltile(ji,jst)
6937
6938             DO jv=1,nvm
6939                humrelv(ji,jv,jst) = humrelv(ji,jv,jst) * mask_soiltile(ji,jst)
6940                DO jsl=1,nslm
6941                   us(ji,jv,jst,jsl) = us(ji,jv,jst,jsl)  * mask_soiltile(ji,jst)
6942                END DO
6943             END DO
6944
6945             DO jsl=1,nslm         
6946                mc(ji,jsl,jst) = mc(ji,jsl,jst)  * mask_soiltile(ji,jst)
6947             END DO
6948
6949       END DO
6950    END DO
6951
6952    runoff(:) = zero
6953    drainage(:) = zero
6954    humtot(:) = zero
6955    shumdiag(:,:)= zero
6956    shumdiag_perma(:,:)=zero
6957    k_litt(:) = zero
6958    litterhumdiag(:) = zero
6959    tmc_litt_dry_mea(:) = zero
6960    tmc_litt_wet_mea(:) = zero
6961    tmc_litt_mea(:) = zero
6962    humrel(:,:) = zero
6963    vegstress(:,:) = zero
6964    IF (ok_freeze_cwrr) THEN
6965       profil_froz_hydro(:,:)=zero ! initialisation for the mean of profil_froz_hydro_ns
6966    ENDIF
6967   
6968    !! 2. Sum 3d variables in 2d variables with fraction of vegetation per soil type
6969
6970    DO ji = 1, kjpindex
6971       mask_vegtot(ji) = 0
6972       IF(vegtot(ji) .GT. min_sechiba) THEN
6973          mask_vegtot(ji) = 1
6974       ENDIF
6975    END DO
6976   
6977    DO ji = 1, kjpindex 
6978       ! Here we weight ae_ns by the fraction of bare evaporating soil.
6979       ! This is given by frac_bare_ns, taking into account bare soil under vegetation
6980       ae_ns(ji,:) = mask_vegtot(ji) * ae_ns(ji,:) * frac_bare_ns(ji,:)
6981    END DO
6982
6983    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6984    DO jst = 1, nstm
6985       DO ji = 1, kjpindex 
6986          drainage(ji) = mask_vegtot(ji) * (drainage(ji) + vegtot(ji)*soiltile(ji,jst) * dr_ns(ji,jst))
6987          runoff(ji) = mask_vegtot(ji) *  (runoff(ji) +   vegtot(ji)*soiltile(ji,jst) * ru_ns(ji,jst)) &
6988               &   + (1 - mask_vegtot(ji)) * (tot_melt(ji) + irrigation(ji) + returnflow(ji) + reinfiltration(ji))
6989          humtot(ji) = mask_vegtot(ji) * (humtot(ji) + vegtot(ji)*soiltile(ji,jst) * tmc(ji,jst)) 
6990          IF (ok_freeze_cwrr) THEN 
6991             !  profil_froz_hydro_ns comes from hydrol_soil, to remain the same as in the prognotic loop
6992             profil_froz_hydro(ji,:)=mask_vegtot(ji) * &
6993                  (profil_froz_hydro(ji,:) + vegtot(ji)*soiltile(ji,jst) * profil_froz_hydro_ns(ji,:, jst))
6994          ENDIF
6995       END DO
6996    END DO
6997
6998    ! we add the excess of snow sublimation to vevapnu
6999    ! - because vevapsno is modified in hydrol_snow if subsinksoil
7000    ! - it is multiplied by vegtot because it is devided by 1-tot_frac_nobio at creation in hydrol_snow
7001
7002    DO ji = 1,kjpindex
7003       vevapnu(ji) = vevapnu (ji) + subsinksoil(ji)*vegtot(ji)
7004    END DO
7005
7006    DO jst=1,nstm
7007       DO jv=1,nvm
7008          DO ji=1,kjpindex
7009             IF(veget_max(ji,jv).GT.min_sechiba) THEN
7010                vegstress(ji,jv)=vegstress(ji,jv)+vegstressv(ji,jv,jst)
7011                vegstress(ji,jv)= MAX(vegstress(ji,jv),zero)
7012             ENDIF
7013          END DO
7014       END DO
7015    END DO
7016
7017    DO jst=1,nstm
7018       DO jv=1,nvm
7019          DO ji=1,kjpindex
7020             humrel(ji,jv)=humrel(ji,jv)+humrelv(ji,jv,jst)
7021             humrel(ji,jv)=MAX(humrel(ji,jv),zero)
7022          END DO
7023       END DO
7024    END DO
7025
7026    !! Litter... the goal is to calculate drysoil_frac, to calculate the albedo in condveg
7027    ! In condveg, drysoil_frac serve to calculate the albedo of drysoil, excluding the nobio contribution which is further added
7028    ! In conclusion, we calculate drysoil_frac based on moisture averages restricted to the soiltile (no multiplication by vegtot)
7029    ! BUT THIS IS NOT USED ANYMORE WITH THE NEW BACKGROUNG ALBEDO
7030    !! k_litt is calculated here as a grid-cell average (for consistency with drainage)   
7031    !! litterhumdiag, like shumdiag, is averaged over the soiltiles for transmission to stomate
7032    DO jst=1,nstm       
7033       DO ji=1,kjpindex
7034          ! We compute here a mean k for the 'litter' used for reinfiltration from floodplains of ponds       
7035          IF ( tmc_litter(ji,jst) < tmc_litter_res(ji,jst)) THEN
7036             i = imin
7037          ELSE
7038             tmc_litter_ratio = (tmc_litter(ji,jst)-tmc_litter_res(ji,jst)) / &
7039                  & (tmc_litter_sat(ji,jst)-tmc_litter_res(ji,jst))
7040             i= MAX(MIN(INT((imax-imin)*tmc_litter_ratio)+imin, imax-1), imin)
7041          ENDIF       
7042          k_tmp = MAX(k_lin(i,1,njsc(ji))*ks(njsc(ji)), zero)
7043          k_litt(ji) = k_litt(ji) + vegtot(ji)*soiltile(ji,jst) * SQRT(k_tmp) ! grid-cell average
7044       ENDDO     
7045       DO ji=1,kjpindex
7046          litterhumdiag(ji) = litterhumdiag(ji) + &
7047               & soil_wet_litter(ji,jst) * soiltile(ji,jst)
7048
7049          tmc_litt_wet_mea(ji) =  tmc_litt_wet_mea(ji) + & 
7050               & tmc_litter_awet(ji,jst)* soiltile(ji,jst)
7051
7052          tmc_litt_dry_mea(ji) = tmc_litt_dry_mea(ji) + &
7053               & tmc_litter_adry(ji,jst) * soiltile(ji,jst) 
7054
7055          tmc_litt_mea(ji) = tmc_litt_mea(ji) + &
7056               & tmc_litter(ji,jst) * soiltile(ji,jst) 
7057       ENDDO
7058    ENDDO
7059   
7060    DO ji=1,kjpindex
7061       IF ( tmc_litt_wet_mea(ji) - tmc_litt_dry_mea(ji) > zero ) THEN
7062          drysoil_frac(ji) = un + MAX( MIN( (tmc_litt_dry_mea(ji) - tmc_litt_mea(ji)) / &
7063               & (tmc_litt_wet_mea(ji) - tmc_litt_dry_mea(ji)), zero), - un)
7064       ELSE
7065          drysoil_frac(ji) = zero
7066       ENDIF
7067    END DO
7068   
7069    ! Calculate soilmoist, as a function of total water content (mc)
7070    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
7071    soilmoist(:,:) = zero
7072    DO jst=1,nstm
7073       DO ji=1,kjpindex
7074             soilmoist(ji,1) = soilmoist(ji,1) + soiltile(ji,jst) * &
7075                  dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
7076             DO jsl = 2,nslm-1
7077                soilmoist(ji,jsl) = soilmoist(ji,jsl) + soiltile(ji,jst) * &
7078                     ( dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
7079                     + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit )
7080             END DO
7081             soilmoist(ji,nslm) = soilmoist(ji,nslm) + soiltile(ji,jst) * &
7082                  dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
7083       END DO
7084    END DO
7085    DO ji=1,kjpindex
7086       soilmoist(ji,:) = soilmoist(ji,:) * vegtot(ji) ! conversion to grid-cell average
7087    ENDDO
7088
7089    soilmoist_liquid(:,:) = zero
7090    DO jst=1,nstm
7091       DO ji=1,kjpindex
7092          soilmoist_liquid(ji,1) = soilmoist_liquid(ji,1) + soiltile(ji,jst) * &
7093               dz(2) * ( trois*mcl(ji,1,jst) + mcl(ji,2,jst) )/huit
7094          DO jsl = 2,nslm-1
7095             soilmoist_liquid(ji,jsl) = soilmoist_liquid(ji,jsl) + soiltile(ji,jst) * &
7096                  ( dz(jsl) * (trois*mcl(ji,jsl,jst)+mcl(ji,jsl-1,jst))/huit &
7097                  + dz(jsl+1) * (trois*mcl(ji,jsl,jst)+mcl(ji,jsl+1,jst))/huit )
7098          END DO
7099          soilmoist_liquid(ji,nslm) = soilmoist_liquid(ji,nslm) + soiltile(ji,jst) * &
7100               dz(nslm) * (trois*mcl(ji,nslm,jst) + mcl(ji,nslm-1,jst))/huit
7101       ENDDO
7102    ENDDO
7103    DO ji=1,kjpindex
7104        soilmoist_liquid(ji,:) = soilmoist_liquid(ji,:) * vegtot_old(ji) ! grid cell average
7105    ENDDO
7106   
7107   
7108    ! Shumdiag: we start from soil_wet_ns, change the range over which the relative moisture is calculated,
7109    ! then do a spatial average, excluding the nobio fraction on which stomate doesn't act
7110    DO jst=1,nstm     
7111       DO jsl=1,nslm
7112          DO ji=1,kjpindex
7113             shumdiag(ji,jsl) = shumdiag(ji,jsl) + soil_wet_ns(ji,jsl,jst) * soiltile(ji,jst) * &
7114                               ((mcs(njsc(ji))-mcw(njsc(ji)))/(mcfc(njsc(ji))-mcw(njsc(ji))))
7115             shumdiag(ji,jsl) = MAX(MIN(shumdiag(ji,jsl), un), zero) 
7116          ENDDO
7117       ENDDO
7118    ENDDO
7119   
7120    ! Shumdiag_perma is based on soilmoist / moisture at saturation in the layer
7121    ! Her we start from grid averages by hydrol soil layer and transform it to the diag levels
7122    ! We keep a grid-cell average, like for all variables transmitted to ok_freeze
7123    DO jsl=1,nslm             
7124       DO ji=1,kjpindex
7125          shumdiag_perma(ji,jsl) = soilmoist(ji,jsl) / (dh(jsl)*mcs(njsc(ji)))
7126          shumdiag_perma(ji,jsl) = MAX(MIN(shumdiag_perma(ji,jsl), un), zero) 
7127       ENDDO
7128    ENDDO
7129   
7130  END SUBROUTINE hydrol_diag_soil 
7131
7132
7133!! ================================================================================================================================
7134!! SUBROUTINE   : hydrol_alma
7135!!
7136!>\BRIEF        This routine computes the changes in soil moisture and interception storage for the ALMA outputs. 
7137!!
7138!! DESCRIPTION  : None
7139!!
7140!! RECENT CHANGE(S) : None
7141!!
7142!! MAIN OUTPUT VARIABLE(S) :
7143!!
7144!! REFERENCE(S) :
7145!!
7146!! FLOWCHART    : None
7147!! \n
7148!_ ================================================================================================================================
7149!_ hydrol_alma
7150
7151  SUBROUTINE hydrol_alma (kjpindex, index, lstep_init, qsintveg, snow, snow_nobio, soilwet)
7152    !
7153    !! 0. Variable and parameter declaration
7154
7155    !! 0.1 Input variables
7156
7157    INTEGER(i_std), INTENT (in)                        :: kjpindex     !! Domain size
7158    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index        !! Indeces of the points on the map
7159    LOGICAL, INTENT (in)                               :: lstep_init   !! At which time is this routine called ?
7160    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintveg     !! Water on vegetation due to interception
7161    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: snow         !! Snow water equivalent
7162    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio !! Water balance on ice, lakes, .. [Kg/m^2]
7163
7164    !! 0.2 Output variables
7165
7166    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: soilwet     !! Soil wetness
7167
7168    !! 0.3 Modified variables
7169
7170    !! 0.4 Local variables
7171
7172    INTEGER(i_std) :: ji
7173    REAL(r_std) :: watveg
7174
7175!_ ================================================================================================================================
7176    !
7177    !
7178    IF ( lstep_init ) THEN
7179       ! Initialize variables if they were not found in the restart file
7180
7181       DO ji = 1, kjpindex
7182          watveg = SUM(qsintveg(ji,:))
7183          tot_watveg_beg(ji) = watveg
7184          tot_watsoil_beg(ji) = humtot(ji)
7185          snow_beg(ji)        = snow(ji) + SUM(snow_nobio(ji,:))
7186       ENDDO
7187
7188       RETURN
7189
7190    ENDIF
7191    !
7192    ! Calculate the values for the end of the time step
7193    !
7194    DO ji = 1, kjpindex
7195       watveg = SUM(qsintveg(ji,:)) ! average within the mesh
7196       tot_watveg_end(ji) = watveg
7197       tot_watsoil_end(ji) = humtot(ji) ! average within the mesh
7198       snow_end(ji) = snow(ji)+ SUM(snow_nobio(ji,:)) ! average within the mesh
7199
7200       delintercept(ji) = tot_watveg_end(ji) - tot_watveg_beg(ji) ! average within the mesh
7201       delsoilmoist(ji) = tot_watsoil_end(ji) - tot_watsoil_beg(ji)
7202       delswe(ji)       = snow_end(ji) - snow_beg(ji) ! average within the mesh
7203    ENDDO
7204    !
7205    !
7206    ! Transfer the total water amount at the end of the current timestep top the begining of the next one.
7207    !
7208    tot_watveg_beg = tot_watveg_end
7209    tot_watsoil_beg = tot_watsoil_end
7210    snow_beg(:) = snow_end(:)
7211    !
7212    DO ji = 1,kjpindex
7213       IF ( mx_eau_var(ji) > 0 ) THEN
7214          soilwet(ji) = tot_watsoil_end(ji) / mx_eau_var(ji)
7215       ELSE
7216          soilwet(ji) = zero
7217       ENDIF
7218    ENDDO
7219    !
7220  END SUBROUTINE hydrol_alma
7221  !
7222
7223
7224!! ================================================================================================================================
7225!! SUBROUTINE   : hydrol_calculate_temp_hydro
7226!!
7227!>\BRIEF         Calculate the temperature at hydrological levels 
7228!!
7229!! DESCRIPTION  : None
7230!!
7231!! RECENT CHANGE(S) : None
7232!!
7233!! MAIN OUTPUT VARIABLE(S) :
7234!!
7235!! REFERENCE(S) :
7236!!
7237!! FLOWCHART    : None
7238!! \n
7239!_ ================================================================================================================================
7240
7241
7242  SUBROUTINE hydrol_calculate_temp_hydro(kjpindex, stempdiag, snow,snowdz)
7243
7244    !! 0.1 Input variables
7245
7246    INTEGER(i_std), INTENT(in)                             :: kjpindex 
7247    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in)     :: stempdiag
7248    REAL(r_std),DIMENSION (kjpindex), INTENT (in)          :: snow
7249    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in)    :: snowdz
7250
7251
7252    !! 0.2 Local variables
7253   
7254    INTEGER jh, jsl, ji
7255    REAL(r_std) :: snow_h
7256    REAL(r_std)  :: lev_diag, prev_diag, lev_prog, prev_prog
7257    REAL(r_std), DIMENSION(nslm,nslm) :: intfactt
7258   
7259   
7260    DO ji=1,kjpindex
7261       IF (ok_explicitsnow) THEN 
7262          !The snow pack is above the surface soil in the new snow model.
7263          snow_h=0
7264       ELSE 
7265          snow_h=snow(ji)/sn_dens
7266       ENDIF
7267       
7268       intfactt(:,:)=0.
7269       prev_diag = snow_h
7270       DO jh = 1, nslm
7271          IF (jh.EQ.1) THEN
7272             lev_diag = zz(2)/1000./2.+snow_h
7273          ELSEIF (jh.EQ.nslm) THEN
7274             lev_diag = zz(nslm)/1000.+snow_h
7275             
7276          ELSE
7277             lev_diag = zz(jh)/1000. &
7278                  & +(zz(jh+1)-zz(jh))/1000./2.+snow_h
7279             
7280          ENDIF
7281          prev_prog = 0.0
7282          DO jsl = 1, nslm
7283             lev_prog = diaglev(jsl)
7284             IF ((lev_diag.GT.diaglev(nslm).AND. &
7285                  & prev_diag.LT.diaglev(nslm)-min_sechiba)) THEN
7286                lev_diag=diaglev(nslm)         
7287             ENDIF
7288             intfactt(jh,jsl) = MAX(MIN(lev_diag,lev_prog)-MAX(prev_diag, prev_prog),&
7289                  & 0.0)/(lev_diag-prev_diag)
7290             prev_prog = lev_prog
7291          ENDDO
7292          IF (lev_diag.GT.diaglev(nslm).AND. &
7293               & prev_diag.GE.diaglev(nslm)-min_sechiba) intfactt(jh,nslm)=1.
7294          prev_diag = lev_diag
7295       ENDDO
7296    ENDDO
7297   
7298    temp_hydro(:,:)=0.
7299    DO jsl= 1, nslm
7300       DO jh= 1, nslm
7301          DO ji = 1, kjpindex
7302             temp_hydro(ji,jh) = temp_hydro(ji,jh) + stempdiag(ji,jsl)*intfactt(jh,jsl)
7303          ENDDO
7304       ENDDO
7305    ENDDO
7306   
7307  END SUBROUTINE hydrol_calculate_temp_hydro
7308
7309
7310!! ================================================================================================================================
7311!! SUBROUTINE   : hydrol_nudge
7312!!
7313!>\BRIEF         Applay nudging of soil moisture and/or snow variables
7314!!
7315!! DESCRIPTION  : Nudging of soil moisture and/or snow variables is done if OK_NUDGE_MC=y and/or OK_NUDGE_SNOW=y in run.def
7316!!
7317!! RECENT CHANGE(S) : None
7318!!
7319!! MAIN IN-OUTPUT VARIABLE(S) : mc, snowdz, snowrho, snowtemp
7320!!
7321!! REFERENCE(S) :
7322!!
7323!! \n
7324!_ ================================================================================================================================
7325
7326  SUBROUTINE hydrol_nudge(kjit,   kjpindex, &
7327                          mc_loc, snowdz, snowrho, snowtemp, soiltile)
7328
7329    !! 0.1 Input variables
7330    INTEGER(i_std), INTENT(in)                         :: kjit        !! Timestep number
7331    INTEGER(i_std), INTENT(in)                         :: kjpindex    !! Domain size
7332    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT (in) :: soiltile    !! Fraction of each soil tile within vegtot (0-1, unitless)
7333
7334    !! 0.2 Modified variables
7335    REAL(r_std), DIMENSION(kjpindex,nslm,nstm), INTENT(inout) :: mc_loc      !! Soil moisture
7336    REAL(r_std), DIMENSION(kjpindex,nsnow), INTENT(inout)     :: snowdz      !! Snow layer thickness
7337    REAL(r_std), DIMENSION(kjpindex,nsnow), INTENT(inout)     :: snowrho     !! Snow density
7338    REAL(r_std), DIMENSION(kjpindex,nsnow), INTENT(inout)     :: snowtemp    !! Snow temperature
7339
7340
7341
7342    !! 0.3 Locals variables
7343    REAL(r_std)                                :: tau                   !! Position between to values in nudge mc file
7344    REAL(r_std), DIMENSION(kjpindex,nslm,nstm) :: mc_read_current       !! mc from file interpolated to current timestep
7345    REAL(r_std), DIMENSION(kjpindex,nsnow)     :: snowdz_read_current   !! snowdz from file interpolated to current timestep
7346    REAL(r_std), DIMENSION(kjpindex,nsnow)     :: snowrho_read_current  !! snowrho from file interpolated to current timestep
7347    REAL(r_std), DIMENSION(kjpindex,nsnow)     :: snowtemp_read_current !! snowtemp from file interpolated to current timestep
7348    REAL(r_std), DIMENSION(kjpindex)           :: nudgincsm             !! Nudging increment of water in soil moisture
7349    REAL(r_std), DIMENSION(kjpindex)           :: nudgincswe            !! Nudging increment of water in snow
7350    REAL(r_std), DIMENSION(kjpindex,nslm,nstm) :: mc_aux                !! Temorary variable for calculation of nudgincsm
7351    REAL(r_std), DIMENSION(kjpindex,nstm)      :: tmc_aux               !! Temorary variable for calculation of nudgincsm
7352    REAL(r_std), DIMENSION(iim_g,jjm_g,nslm,1) :: mc_read_glo2D_1       !! mc from file at global 2D(lat,lon) grid per soiltile
7353    REAL(r_std), DIMENSION(iim_g,jjm_g,nslm,1) :: mc_read_glo2D_2       !! mc from file at global 2D(lat,lon) grid per soiltile
7354    REAL(r_std), DIMENSION(iim_g,jjm_g,nslm,1) :: mc_read_glo2D_3       !! mc from file at global 2D(lat,lon) grid per soiltile
7355    REAL(r_std), DIMENSION(iim_g,jjm_g,nsnow,1):: snowdz_read_glo2D     !! snowdz from file at global 2D(lat,lon) grid
7356    REAL(r_std), DIMENSION(iim_g,jjm_g,nsnow,1):: snowrho_read_glo2D    !! snowrho from file at global 2D(lat,lon) grid
7357    REAL(r_std), DIMENSION(iim_g,jjm_g,nsnow,1):: snowtemp_read_glo2D   !! snowrho from file at global 2D(lat,lon) grid
7358    REAL(r_std), DIMENSION(nbp_glo,nslm,nstm)  :: mc_read_glo1D         !! mc_read_glo2D on land-only vector form, in global
7359    REAL(r_std), DIMENSION(nbp_glo,nsnow)      :: snowdz_read_glo1D     !! snowdz_read_glo2D on land-only vector form, in global
7360    REAL(r_std), DIMENSION(nbp_glo,nsnow)      :: snowrho_read_glo1D    !! snowdz_read_glo2D on land-only vector form, in global
7361    REAL(r_std), DIMENSION(nbp_glo,nsnow)      :: snowtemp_read_glo1D   !! snowdz_read_glo2D on land-only vector form, in global
7362    INTEGER(i_std), SAVE                       :: istart_mc, istart_snow!! start index to read from input file
7363    INTEGER(i_std)                             :: iend                  !! end index to read from input file
7364    INTEGER(i_std)                             :: i, j, ji, jg, jst, jsl!! loop index
7365    INTEGER(i_std)                             :: iim_file, jjm_file, llm_file !! Dimensions in input file
7366    INTEGER(i_std), SAVE                       :: ttm_mc, ttm_snow      !! Time dimensions in input file
7367    INTEGER(i_std), SAVE                       :: mc_id, snow_id        !! index for netcdf files
7368    LOGICAL, SAVE                              :: firsttime_mc=.TRUE.
7369    LOGICAL, SAVE                              :: firsttime_snow=.TRUE.
7370
7371 
7372    !! 1. Nudging of soil moisture
7373    IF (ok_nudge_mc) THEN
7374
7375       !! 1.2 Read mc from file, once a day only
7376       !!     The forcing file must contain daily frequency variable for the full year of the simulation
7377       IF (MOD(kjit,INT(one_day/dt_sechiba)) == 1) THEN 
7378          ! Save mc read from file from previous day
7379          mc_read_prev = mc_read_next
7380
7381          IF (nudge_interpol_with_xios) THEN
7382             ! Read mc from input file. XIOS interpolates it to the model grid before it is received here.
7383             CALL xios_orchidee_recv_field("moistc_interp", mc_read_next)
7384
7385             ! Read and interpolation the mask for variable mc from input file.
7386             ! This is only done to be able to output the mask it later for validation purpose.
7387             ! The mask corresponds to the fraction of the input source file which was underlaying the model grid cell.
7388             ! If the msask is 0 for a model grid cell, then the default value 0.2 set in field_def_orchidee.xml, is used for that grid cell.
7389             CALL xios_orchidee_recv_field("mask_moistc_interp", mask_mc_interp)
7390
7391          ELSE
7392
7393             ! Only read fields from the file. We here suppose that no interpolation is needed.
7394             IF (is_root_prc) THEN
7395                IF (firsttime_mc) THEN
7396                   ! Open and read dimenions in file
7397                   CALL flininfo('nudge_moistc.nc',  iim_file, jjm_file, llm_file, ttm_mc, mc_id)
7398                   
7399                   ! Coherence test between dimension in the file and in the model run
7400                   IF ((iim_file /= iim_g) .OR. (jjm_file /= jjm_g)) THEN
7401                      WRITE(numout,*) 'hydrol_nudge: iim_file, jjm_file, llm_file, ttm_mc=', &
7402                           iim_file, jjm_file, llm_file, ttm_mc
7403                      WRITE(numout,*) 'hydrol_nudge: iim_g, jjm_g=', iim_g, jjm_g
7404                      CALL ipslerr_p(2,'hydrol_nudge','Problem in coherence between dimensions in nudge_moistc.nc file and model',&
7405                           'iim_file should be equal to iim_g','jjm_file should be equal to jjm_g')
7406                   END IF
7407                   
7408                   firsttime_mc=.FALSE.
7409                   istart_mc=julian_diff-1 ! initialize time counter to read
7410                   IF (printlev>=2) WRITE(numout,*) "Start read nudge_moistc.nc file at time step: ", istart_mc+1
7411                END IF
7412
7413                istart_mc=istart_mc+1  ! read next time step in the file
7414                iend=istart_mc         ! only read 1 time step
7415               
7416                ! Read mc from file, one variable per soiltile
7417                IF (printlev>=3) WRITE(numout,*) &
7418                     "Read variables moistc_1, moistc_2 and moistc_3 from nudge_moistc.nc at time step: ", istart_mc
7419                CALL flinget (mc_id, 'moistc_1', iim_g, jjm_g, nslm, ttm_mc, istart_mc, iend, mc_read_glo2D_1)
7420                CALL flinget (mc_id, 'moistc_2', iim_g, jjm_g, nslm, ttm_mc, istart_mc, iend, mc_read_glo2D_2)
7421                CALL flinget (mc_id, 'moistc_3', iim_g, jjm_g, nslm, ttm_mc, istart_mc, iend, mc_read_glo2D_3)
7422
7423                ! Transform from global 2D(iim_g, jjm_g) into into land-only global 1D(nbp_glo)
7424                ! Put the variables on the 3 soiltiles in the same file
7425                DO ji = 1, nbp_glo
7426                   j = ((index_g(ji)-1)/iim_g) + 1
7427                   i = (index_g(ji) - (j-1)*iim_g)
7428                   mc_read_glo1D(ji,:,1) = mc_read_glo2D_1(i,j,:,1)
7429                   mc_read_glo1D(ji,:,2) = mc_read_glo2D_2(i,j,:,1)
7430                   mc_read_glo1D(ji,:,3) = mc_read_glo2D_3(i,j,:,1)
7431                END DO
7432             END IF
7433
7434             ! Distribute the fields on all processors
7435             CALL scatter(mc_read_glo1D, mc_read_next)
7436
7437             ! No interpolation is done, set the mask to 1
7438             mask_mc_interp(:,:,:) = 1
7439
7440          END IF ! nudge_interpol_with_xios
7441       END IF ! MOD(kjit,INT(one_day/dt_sechiba)) == 1
7442       
7443     
7444       !! 1.3 Linear time interpolation between daily fields to the current time step
7445       tau   = (kjit-1)*dt_sechiba/one_day - AINT((kjit-1)*dt_sechiba/one_day)
7446       mc_read_current(:,:,:) = (1.-tau)*mc_read_prev(:,:,:) + tau*mc_read_next(:,:,:)
7447
7448       !! 1.4 Output daily fields and time interpolated fields only for debugging and validation purpose
7449       CALL xios_orchidee_send_field("mc_read_next", mc_read_next)
7450       CALL xios_orchidee_send_field("mc_read_current", mc_read_current)
7451       CALL xios_orchidee_send_field("mc_read_prev", mc_read_prev)
7452       CALL xios_orchidee_send_field("mask_mc_interp_out", mask_mc_interp)
7453
7454       
7455       !! 1.5 Applay nudging of soil moisture using alpha_nudge_mc at each model sechiba time step.
7456       !!     alpha_mc_nudge calculated using the parameter for relaxation time NUDGE_TAU_MC set in module constantes.
7457       !!     alpha_nudge_mc is between 0-1
7458       !!     If alpha_nudge_mc=1, the new mc will be replaced by the one read from file
7459       mc_loc(:,:,:) = (1-alpha_nudge_mc)*mc_loc(:,:,:) + alpha_nudge_mc * mc_read_current(:,:,:)
7460   
7461
7462       !! 1.6 Calculate diagnostic for nudging increment of water in soil moisture
7463       mc_aux(:,:,:)  = alpha_nudge_mc * ( mc_read_current(:,:,:) - mc_loc(:,:,:))
7464       DO jst=1,nstm
7465          DO ji=1,kjpindex
7466             tmc_aux(ji,jst) = dz(2) * ( trois*mc_aux(ji,1,jst) + mc_aux(ji,2,jst) )/huit
7467             DO jsl = 2,nslm-1
7468                tmc_aux(ji,jst) = tmc_aux(ji,jst) + dz(jsl) *  (trois*mc_aux(ji,jsl,jst)+mc_aux(ji,jsl-1,jst))/huit &
7469                     + dz(jsl+1) * (trois*mc_aux(ji,jsl,jst)+mc_aux(ji,jsl+1,jst))/huit
7470             ENDDO
7471             tmc_aux(ji,jst) = tmc_aux(ji,jst) + dz(nslm) * (trois*mc_aux(ji,nslm,jst) + mc_aux(ji,nslm-1,jst))/huit
7472          ENDDO
7473       ENDDO
7474       
7475       ! Average over grid-cell
7476       nudgincsm(:) = zero
7477       DO jst=1,nstm
7478          DO ji=1,kjpindex
7479             nudgincsm(ji) = nudgincsm(ji) + vegtot(ji) * soiltile(ji,jst) * tmc_aux(ji,jst)
7480          ENDDO
7481       ENDDO
7482       
7483       CALL xios_orchidee_send_field("nudgincsm", nudgincsm)
7484       
7485       
7486    END IF ! IF (ok_nudge_mc)
7487
7488
7489    !! 2. Nudging of snow variables
7490    IF (ok_nudge_snow) THEN
7491
7492       !! 2.1 Read snow variables from file, once a day only
7493       !!     The forcing file must contain daily frequency values for the full year of the simulation
7494       IF (MOD(kjit,INT(one_day/dt_sechiba)) == 1) THEN 
7495          ! Save variables from previous day
7496          snowdz_read_prev   = snowdz_read_next
7497          snowrho_read_prev  = snowrho_read_next
7498          snowtemp_read_prev = snowtemp_read_next
7499         
7500          IF (nudge_interpol_with_xios) THEN
7501             ! Read and interpolation snow variables and the mask from input file
7502             CALL xios_orchidee_recv_field("snowdz_interp", snowdz_read_next)
7503             CALL xios_orchidee_recv_field("snowrho_interp", snowrho_read_next)
7504             CALL xios_orchidee_recv_field("snowtemp_interp", snowtemp_read_next)
7505             CALL xios_orchidee_recv_field("mask_snow_interp", mask_snow_interp)
7506
7507          ELSE
7508             ! Only read fields from the file. We here suppose that no interpolation is needed.
7509             IF (is_root_prc) THEN
7510                IF (firsttime_snow) THEN
7511                   ! Open and read dimenions in file
7512                   CALL flininfo('nudge_snow.nc',  iim_file, jjm_file, llm_file, ttm_snow, snow_id)
7513                   
7514                   ! Coherence test between dimension in the file and in the model run
7515                   IF ((iim_file /= iim_g) .OR. (jjm_file /= jjm_g)) THEN
7516                      WRITE(numout,*) 'hydrol_nudge: iim_file, jjm_file, llm_file, ttm_snow=', &
7517                           iim_file, jjm_file, llm_file, ttm_snow
7518                      WRITE(numout,*) 'hydrol_nudge: iim_g, jjm_g=', iim_g, jjm_g
7519                      CALL ipslerr_p(3,'hydrol_nudge','Problem in coherence between dimensions in nudge_snow.nc file and model',&
7520                           'iim_file should be equal to iim_g','jjm_file should be equal to jjm_g')
7521                   END IF
7522                                         
7523                   firsttime_snow=.FALSE.
7524                   istart_snow=julian_diff-1  ! initialize time counter to read
7525                   IF (printlev>=2) WRITE(numout,*) "Start read nudge_snow.nc file at time step: ", istart_snow+1
7526                END IF
7527
7528                istart_snow=istart_snow+1  ! read next time step in the file
7529                iend=istart_snow      ! only read 1 time step
7530               
7531                ! Read snowdz, snowrho and snowtemp from file
7532                IF (printlev>=3) WRITE(numout,*) &
7533                     "Read variables snowdz, snowrho and snowtemp from nudge_snow.nc at time step: ", istart_snow
7534                CALL flinget (snow_id, 'snowdz', iim_g, jjm_g, nsnow, ttm_snow, istart_snow, iend, snowdz_read_glo2D)
7535                CALL flinget (snow_id, 'snowrho', iim_g, jjm_g, nsnow, ttm_snow, istart_snow, iend, snowrho_read_glo2D)
7536                CALL flinget (snow_id, 'snowtemp', iim_g, jjm_g, nsnow, ttm_snow, istart_snow, iend, snowtemp_read_glo2D)
7537
7538
7539                ! Transform from global 2D(iim_g, jjm_g) variables into into land-only global 1D variables (nbp_glo)
7540                DO ji = 1, nbp_glo
7541                   j = ((index_g(ji)-1)/iim_g) + 1
7542                   i = (index_g(ji) - (j-1)*iim_g)
7543                   snowdz_read_glo1D(ji,:) = snowdz_read_glo2D(i,j,:,1)
7544                   snowrho_read_glo1D(ji,:) = snowrho_read_glo2D(i,j,:,1)
7545                   snowtemp_read_glo1D(ji,:) = snowtemp_read_glo2D(i,j,:,1)
7546                END DO
7547             END IF
7548
7549             ! Distribute the fields on all processors
7550             CALL scatter(snowdz_read_glo1D, snowdz_read_next)
7551             CALL scatter(snowrho_read_glo1D, snowrho_read_next)
7552             CALL scatter(snowtemp_read_glo1D, snowtemp_read_next)
7553
7554             ! No interpolation is done, set the mask to 1
7555             mask_snow_interp=1
7556
7557          END IF ! nudge_interpol_with_xios
7558       END IF ! MOD(kjit,INT(one_day/dt_sechiba)) == 1
7559       
7560     
7561       !! 2.2 Linear time interpolation between daily fields for current time step
7562       tau   = (kjit-1)*dt_sechiba/one_day - AINT((kjit-1)*dt_sechiba/one_day)
7563       snowdz_read_current(:,:) = (1.-tau)*snowdz_read_prev(:,:) + tau*snowdz_read_next(:,:)
7564       snowrho_read_current(:,:) = (1.-tau)*snowrho_read_prev(:,:) + tau*snowrho_read_next(:,:)
7565       snowtemp_read_current(:,:) = (1.-tau)*snowtemp_read_prev(:,:) + tau*snowtemp_read_next(:,:)
7566
7567       !! 2.3 Output daily fields and time interpolated fields only for debugging and validation purpose
7568       CALL xios_orchidee_send_field("snowdz_read_next", snowdz_read_next)
7569       CALL xios_orchidee_send_field("snowdz_read_current", snowdz_read_current)
7570       CALL xios_orchidee_send_field("snowdz_read_prev", snowdz_read_prev)
7571       CALL xios_orchidee_send_field("snowrho_read_next", snowrho_read_next)
7572       CALL xios_orchidee_send_field("snowrho_read_current", snowrho_read_current)
7573       CALL xios_orchidee_send_field("snowrho_read_prev", snowrho_read_prev)
7574       CALL xios_orchidee_send_field("snowtemp_read_next", snowtemp_read_next)
7575       CALL xios_orchidee_send_field("snowtemp_read_current", snowtemp_read_current)
7576       CALL xios_orchidee_send_field("snowtemp_read_prev", snowtemp_read_prev)
7577       CALL xios_orchidee_send_field("mask_snow_interp_out", mask_snow_interp)
7578
7579       !! 2.4 Applay nudging of snow variables using alpha_nudge_snow at each model sechiba time step.
7580       !!     alpha_snow_nudge calculated using the parameter for relaxation time NUDGE_TAU_SNOW set in module constantes.
7581       !!     alpha_nudge_snow is between 0-1
7582       !!     If alpha_nudge_snow=1, the new snow variables will be replaced by the ones read from file.
7583       snowdz(:,:) = (1-alpha_nudge_snow)*snowdz(:,:) + alpha_nudge_snow * snowdz_read_current(:,:)
7584       snowrho(:,:) = (1-alpha_nudge_snow)*snowrho(:,:) + alpha_nudge_snow * snowrho_read_current(:,:)
7585       snowtemp(:,:) = (1-alpha_nudge_snow)*snowtemp(:,:) + alpha_nudge_snow * snowtemp_read_current(:,:)
7586
7587       !! 2.5 Calculate diagnostic for the nudging increment of water in snow
7588       nudgincswe=0.
7589       DO jg = 1, nsnow 
7590          nudgincswe(:) = nudgincswe(:) +  &
7591               alpha_nudge_snow*(snowdz_read_current(:,jg)*snowrho_read_current(:,jg)-snowdz(:,jg)*snowrho(:,jg))
7592       END DO
7593       CALL xios_orchidee_send_field("nudgincswe", nudgincswe)
7594       
7595    END IF
7596
7597
7598  END SUBROUTINE hydrol_nudge
7599 
7600END MODULE hydrol
Note: See TracBrowser for help on using the repository browser.