source: branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/hydrol.f90 @ 7476

Last change on this file since 7476 was 7476, checked in by josefine.ghattas, 2 years ago

Moved getin KFACT_ROOT_TYPE from hydrol_main to hydrol_var_init and changed it to KFACT_ROOT_CONST (logical instead of character string). See ticket #817

  • Property svn:keywords set to Revision Date HeadURL Date Author Revision
File size: 348.4 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_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) : November 2020: It is possible to define soil hydraulic parameters from maps,
22!!                    as needed for the SP-MIP project (Tafasca Salma and Ducharne Agnes).
23!!                    Here, it leads to change dimensions and indices.
24!!                    We can also impose kfact_root=1 in all soil layers to cancel the effect of
25!!                    roots on ks profile (keyword KFACT_ROOT_CONST).
26!!                 
27!! REFERENCE(S) :
28!! - de Rosnay, P., J. Polcher, M. Bruen, and K. Laval, Impact of a physically based soil
29!! water flow and soil-plant interaction representation for modeling large-scale land surface
30!! processes, J. Geophys. Res, 107 (10.1029), 2002. \n
31!! - de Rosnay, P. and Polcher J. (1998) Modeling root water uptake in a complex land surface scheme coupled
32!! to a GCM. Hydrology and Earth System Sciences, 2(2-3):239-256. \n
33!! - de Rosnay, P., M. Bruen, and J. Polcher, Sensitivity of surface fluxes to the number of layers in the soil
34!! model used in GCMs, Geophysical research letters, 27 (20), 3329 - 3332, 2000. \n
35!! - d’Orgeval, T., J. Polcher, and P. De Rosnay, Sensitivity of the West African hydrological
36!! cycle in ORCHIDEE to infiltration processes, Hydrol. Earth Syst. Sci. Discuss, 5, 2251 - 2292, 2008. \n
37!! - Carsel, R., and R. Parrish, Developing joint probability distributions of soil water retention
38!! characteristics, Water Resources Research, 24 (5), 755 - 769, 1988. \n
39!! - Mualem, Y., A new model for predicting the hydraulic conductivity of unsaturated porous
40!! media, Water Resources Research, 12 (3), 513 - 522, 1976. \n
41!! - Van Genuchten, M., A closed-form equation for predicting the hydraulic conductivity of
42!! unsaturated soils, Soil Science Society of America Journal, 44 (5), 892 - 898, 1980. \n
43!! - Campoy, A., Ducharne, A., Cheruy, F., Hourdin, F., Polcher, J., and Dupont, J.-C., Response
44!! of land surface fluxes and precipitation to different soil bottom hydrological conditions in a
45!! general circulation model,  J. Geophys. Res, in press, 2013. \n
46!! - Gouttevin, I., Krinner, G., Ciais, P., Polcher, J., and Legout, C. , 2012. Multi-scale validation
47!! of a new soil freezing scheme for a land-surface model with physically-based hydrology.
48!! The Cryosphere, 6, 407-430, doi: 10.5194/tc-6-407-2012. \n
49!! - Tafasca S. (2020). Evaluation de l’impact des propriétés du sol sur l’hydrologie simulee dans le
50!! modÚle ORCHIDEE, PhD thesis, Sorbonne Universite. \n
51!!
52!! SVN          :
53!! $HeadURL$
54!! $Date$
55!! $Revision$
56!! \n
57!_ ===============================================================================================\n
58MODULE hydrol
59
60  USE ioipsl
61  USE xios_orchidee
62  USE constantes
63  USE time, ONLY : one_day, dt_sechiba, julian_diff
64  USE constantes_soil
65  USE pft_parameters
66  USE sechiba_io_p
67  USE grid
68  USE explicitsnow
69
70  IMPLICIT NONE
71
72  PRIVATE
73  PUBLIC :: hydrol_main, hydrol_initialize, hydrol_finalize, hydrol_clear
74
75  !
76  ! variables used inside hydrol module : declaration and initialisation
77  !
78  LOGICAL, SAVE                                   :: doponds=.FALSE.           !! Reinfiltration flag (true/false)
79!$OMP THREADPRIVATE(doponds)
80  REAL(r_std), SAVE                               :: froz_frac_corr            !! Coefficient for water frozen fraction correction
81!$OMP THREADPRIVATE(froz_frac_corr)
82  REAL(r_std), SAVE                               :: max_froz_hydro            !! Coefficient for water frozen fraction correction
83!$OMP THREADPRIVATE(max_froz_hydro)
84  REAL(r_std), SAVE                               :: smtot_corr                !! Coefficient for water frozen fraction correction
85!$OMP THREADPRIVATE(smtot_corr)
86  LOGICAL, SAVE                                   :: do_rsoil=.FALSE.          !! Flag to calculate rsoil for bare soile evap
87                                                                               !! (true/false)
88!$OMP THREADPRIVATE(do_rsoil)
89  LOGICAL, SAVE                                   :: ok_dynroot                !! Flag to activate dynamic root profile to optimize soil 
90                                                                               !! moisture usage, similar to Beer et al.2007
91!$OMP THREADPRIVATE(ok_dynroot)
92  LOGICAL, SAVE                                   :: kfact_root_const          !! Control kfact_root calculation, set constant kfact_root=1 if kfact_root_const=true
93!$OMP THREADPRIVATE(kfact_root_const)
94  CHARACTER(LEN=80) , SAVE                        :: var_name                  !! To store variables names for I/O
95!$OMP THREADPRIVATE(var_name)
96  !
97  REAL(r_std), PARAMETER                          :: allowed_err =  2.0E-8_r_std
98  REAL(r_std), PARAMETER                          :: EPS1 = EPSILON(un)      !! A small number
99 
100  ! one dimension array allocated, computed, saved and got in hydrol module
101  ! Values per soil type
102  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: pcent               !! Fraction of saturated volumetric soil moisture above
103                                                                         !! which transpir is max (0-1, unitless)
104!$OMP THREADPRIVATE(pcent)                                                               
105  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_awet             !! Vol. wat. cont. above which albedo is cst
106                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
107!$OMP THREADPRIVATE(mc_awet)                                             
108  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_adry             !! Vol. wat. cont. below which albedo is cst
109                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
110!$OMP THREADPRIVATE(mc_adry)                                             
111  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watveg_beg   !! Total amount of water on vegetation at start of time
112                                                                         !! step @tex $(kg m^{-2})$ @endtex
113!$OMP THREADPRIVATE(tot_watveg_beg)                                     
114  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watveg_end   !! Total amount of water on vegetation at end of time step
115                                                                         !!  @tex $(kg m^{-2})$ @endtex
116!$OMP THREADPRIVATE(tot_watveg_end)                                     
117  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watsoil_beg  !! Total amount of water in the soil at start of time step
118                                                                         !!  @tex $(kg m^{-2})$ @endtex
119!$OMP THREADPRIVATE(tot_watsoil_beg)                                     
120  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watsoil_end  !! Total amount of water in the soil at end of time step
121                                                                         !!  @tex $(kg m^{-2})$ @endtex
122!$OMP THREADPRIVATE(tot_watsoil_end)                                     
123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snow_beg         !! Total amount of snow at start of time step
124                                                                         !!  @tex $(kg m^{-2})$ @endtex
125!$OMP THREADPRIVATE(snow_beg)                                           
126  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snow_end         !! Total amount of snow at end of time step
127                                                                         !!  @tex $(kg m^{-2})$ @endtex
128!$OMP THREADPRIVATE(snow_end)                                           
129  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delsoilmoist     !! Change in soil moisture @tex $(kg m^{-2})$ @endtex
130!$OMP THREADPRIVATE(delsoilmoist)                                         
131  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delintercept     !! Change in interception storage
132                                                                         !!  @tex $(kg m^{-2})$ @endtex
133!$OMP THREADPRIVATE(delintercept)                                       
134  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delswe           !! Change in SWE @tex $(kg m^{-2})$ @endtex
135!$OMP THREADPRIVATE(delswe)
136  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:)       :: undermcr         !! Nb of tiles under mcr for a given time step
137!$OMP THREADPRIVATE(undermcr)
138  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mask_veget       !! zero/one when veget fraction is zero/higher (1)
139!$OMP THREADPRIVATE(mask_veget)
140  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mask_soiltile    !! zero/one where soil tile is zero/higher (1)
141!$OMP THREADPRIVATE(mask_soiltile)
142  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: humrelv          !! Water stress index for transpiration
143                                                                         !! for each soiltile x PFT couple (0-1, unitless)
144!$OMP THREADPRIVATE(humrelv)
145  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: vegstressv       !! Water stress index for vegetation growth
146                                                                         !! for each soiltile x PFT couple (0-1, unitless)
147!$OMP THREADPRIVATE(vegstressv)
148  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:,:):: us               !! Water stress index for transpiration
149                                                                         !! (by soil layer and PFT) (0-1, unitless)
150!$OMP THREADPRIVATE(us)
151  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: precisol         !! Throughfall+Totmelt per PFT
152                                                                         !!  @tex $(kg m^{-2})$ @endtex
153!$OMP THREADPRIVATE(precisol)
154  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: throughfall      !! Throughfall per PFT
155                                                                         !!  @tex $(kg m^{-2})$ @endtex
156!$OMP THREADPRIVATE(throughfall)
157  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: precisol_ns      !! Throughfall per soiltile
158                                                                         !!  @tex $(kg m^{-2})$ @endtex
159!$OMP THREADPRIVATE(precisol_ns)
160  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ae_ns            !! Bare soil evaporation per soiltile
161                                                                         !!  @tex $(kg m^{-2})$ @endtex
162!$OMP THREADPRIVATE(ae_ns)
163  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: free_drain_coef  !! Coefficient for free drainage at bottom
164                                                                         !!  (0-1, unitless)
165!$OMP THREADPRIVATE(free_drain_coef)
166  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: zwt_force        !! Prescribed water table depth (m)
167!$OMP THREADPRIVATE(zwt_force)
168  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: frac_bare_ns     !! Evaporating bare soil fraction per soiltile
169                                                                         !!  (0-1, unitless)
170!$OMP THREADPRIVATE(frac_bare_ns)
171  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: rootsink         !! Transpiration sink by soil layer and soiltile
172                                                                         !! @tex $(kg m^{-2})$ @endtex
173!$OMP THREADPRIVATE(rootsink)
174  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: subsnowveg       !! Sublimation of snow on vegetation
175                                                                         !!  @tex $(kg m^{-2})$ @endtex
176!$OMP THREADPRIVATE(subsnowveg)
177  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: subsnownobio     !! Sublimation of snow on other surface types 
178                                                                         !! (ice, lakes,...) @tex $(kg m^{-2})$ @endtex
179!$OMP THREADPRIVATE(subsnownobio)
180  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: icemelt          !! Ice melt @tex $(kg m^{-2})$ @endtex
181!$OMP THREADPRIVATE(icemelt)
182  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: subsinksoil      !! Excess of sublimation as a sink for the soil
183                                                                         !! @tex $(kg m^{-2})$ @endtex
184!$OMP THREADPRIVATE(subsinksoil)
185  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: vegtot           !! Total Total fraction of grid-cell covered by PFTs
186                                                                         !! (bare soil + vegetation) (1; 1)
187!$OMP THREADPRIVATE(vegtot)
188  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: resdist          !! Soiltile values from previous time-step (1; 1)
189!$OMP THREADPRIVATE(resdist)
190  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: vegtot_old       !! Total Total fraction of grid-cell covered by PFTs
191                                                                         !! from previous time-step (1; 1)
192!$OMP THREADPRIVATE(vegtot_old)
193  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: mx_eau_var       !! Maximum water content of the soil @tex $(kg m^{-2})$ @endtex
194!$OMP THREADPRIVATE(mx_eau_var)
195
196  ! arrays used by cwrr scheme
197  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: nroot            !! Normalized root length fraction in each soil layer
198                                                                         !! (0-1, unitless)
199                                                                         !! DIM = kjpindex * nvm * nslm
200!$OMP THREADPRIVATE(nroot)
201  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: kfact_root       !! Factor to increase Ks towards the surface
202                                                                         !! (unitless)
203                                                                         !! DIM = kjpindex * nslm * nstm
204!$OMP THREADPRIVATE(kfact_root)
205  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: kfact            !! Factor to reduce Ks with depth (unitless)
206                                                                         !! DIM = nslm * kjpindex
207!$OMP THREADPRIVATE(kfact)
208  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: zz               !! Depth of nodes [znh in vertical_soil] transformed into (mm)
209!$OMP THREADPRIVATE(zz)
210  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: dz               !! Internode thickness [dnh in vertical_soil] transformed into (mm)
211!$OMP THREADPRIVATE(dz)
212  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: dh               !! Layer thickness [dlh in vertical_soil] transformed into (mm)
213!$OMP THREADPRIVATE(dh)
214  INTEGER(i_std), SAVE                               :: itopmax          !! Number of layers where the node is above 0.1m depth
215!$OMP THREADPRIVATE(itopmax)
216  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: mc_lin   !! 50 Vol. Wat. Contents to linearize K and D, for each texture
217                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
218                                                                 !! DIM = imin:imax * kjpindex
219!$OMP THREADPRIVATE(mc_lin)
220  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: k_lin    !! 50 values of unsaturated K, for each soil layer and texture
221                                                                 !!  @tex $(mm d^{-1})$ @endtex
222                                                                 !! DIM = imin:imax * nslm * kjpindex
223!$OMP THREADPRIVATE(k_lin)
224  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: d_lin    !! 50 values of diffusivity D, for each soil layer and texture
225                                                                 !!  @tex $(mm^2 d^{-1})$ @endtex
226                                                                 !! DIM = imin:imax * nslm * kjpindex
227!$OMP THREADPRIVATE(d_lin)
228  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: a_lin    !! 50 values of the slope in K=a*mc+b, for each soil layer and texture
229                                                                 !!  @tex $(mm d^{-1})$ @endtex
230                                                                 !! DIM = imin:imax * nslm * kjpindex
231!$OMP THREADPRIVATE(a_lin)
232  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: b_lin    !! 50 values of y-intercept in K=a*mc+b, for each soil layer and texture
233                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
234                                                                 !! DIM = imin:imax * nslm * kjpindex
235!$OMP THREADPRIVATE(b_lin)
236
237  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: humtot   !! Total Soil Moisture @tex $(kg m^{-2})$ @endtex
238!$OMP THREADPRIVATE(humtot)
239  LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:)          :: resolv   !! Mask of land points where to solve the diffusion equation
240                                                                 !! (true/false)
241!$OMP THREADPRIVATE(resolv)
242
243!! for output
244  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: kk_moy   !! Mean hydraulic conductivity over soiltiles (mm/d)
245!$OMP THREADPRIVATE(kk_moy)
246  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: kk       !! Hydraulic conductivity for each soiltiles (mm/d)
247!$OMP THREADPRIVATE(kk)
248  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: avan_mod_tab  !! VG parameter a modified from  exponantial profile
249                                                                      !! @tex $(mm^{-1})$ @endtex !! DIMENSION (nslm,kjpindex)
250!$OMP THREADPRIVATE(avan_mod_tab) 
251  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: nvan_mod_tab  !! VG parameter n  modified from  exponantial profile
252                                                                      !! (unitless) !! DIMENSION (nslm,kjpindex) 
253!$OMP THREADPRIVATE(nvan_mod_tab)
254 
255!! linarization coefficients of hydraulic conductivity K (hydrol_soil_coef)
256  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: k        !! Hydraulic conductivity K for each soil layer
257                                                                 !!  @tex $(mm d^{-1})$ @endtex
258                                                                 !! DIM = (:,nslm)
259!$OMP THREADPRIVATE(k)
260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: a        !! Slope in K=a*mc+b(:,nslm)
261                                                                 !!  @tex $(mm d^{-1})$ @endtex
262                                                                 !! DIM = (:,nslm)
263!$OMP THREADPRIVATE(a)
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: b        !! y-intercept in K=a*mc+b
265                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
266                                                                 !! DIM = (:,nslm)
267!$OMP THREADPRIVATE(b)
268!! linarization coefficients of hydraulic diffusivity D (hydrol_soil_coef)
269  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: d        !! Diffusivity D for each soil layer
270                                                                 !!  @tex $(mm^2 d^{-1})$ @endtex
271                                                                 !! DIM = (:,nslm)
272!$OMP THREADPRIVATE(d)
273!! matrix coefficients (hydrol_soil_tridiag and hydrol_soil_setup), see De Rosnay (1999), p155-157
274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: e        !! Left-hand tridiagonal matrix coefficients
275!$OMP THREADPRIVATE(e)
276  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: f        !! Left-hand tridiagonal matrix coefficients
277!$OMP THREADPRIVATE(f)
278  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: g1       !! Left-hand tridiagonal matrix coefficients
279!$OMP THREADPRIVATE(g1)
280
281  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ep       !! Right-hand matrix coefficients
282!$OMP THREADPRIVATE(ep)
283  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: fp       !! Right-hand atrix coefficients
284!$OMP THREADPRIVATE(fp)
285  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: gp       !! Right-hand atrix coefficients
286!$OMP THREADPRIVATE(gp)
287  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: rhs      !! Right-hand system
288!$OMP THREADPRIVATE(rhs)
289  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: srhs     !! Temporarily stored rhs
290!$OMP THREADPRIVATE(srhs)
291  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: tmat             !! Left-hand tridiagonal matrix
292!$OMP THREADPRIVATE(tmat)
293  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: stmat            !! Temporarily stored tmat
294  !$OMP THREADPRIVATE(stmat)
295  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: water2infilt     !! Water to be infiltrated
296                                                                         !! @tex $(kg m^{-2})$ @endtex
297!$OMP THREADPRIVATE(water2infilt)
298  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc              !! Total moisture content per soiltile
299                                                                         !!  @tex $(kg m^{-2})$ @endtex
300!$OMP THREADPRIVATE(tmc)
301  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcr             !! Total moisture content at residual per soiltile
302                                                                         !!  @tex $(kg m^{-2})$ @endtex
303!$OMP THREADPRIVATE(tmcr)
304  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcs             !! Total moisture content at saturation per soiltile
305                                                                         !!  @tex $(kg m^{-2})$ @endtex
306!$OMP THREADPRIVATE(tmcs)
307  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcfc            !! Total moisture content at field capacity per soiltile
308                                                                         !!  @tex $(kg m^{-2})$ @endtex
309!$OMP THREADPRIVATE(tmcfc)
310  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcw             !! Total moisture content at wilting point per soiltile
311                                                                         !!  @tex $(kg m^{-2})$ @endtex
312!$OMP THREADPRIVATE(tmcw)
313  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter       !! Total moisture in the litter per soiltile
314                                                                         !!  @tex $(kg m^{-2})$ @endtex
315!$OMP THREADPRIVATE(tmc_litter)
316  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_mea     !! Total moisture in the litter over the grid
317                                                                         !!  @tex $(kg m^{-2})$ @endtex
318!$OMP THREADPRIVATE(tmc_litt_mea)
319  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_wilt  !! Total moisture of litter at wilt point per soiltile
320                                                                         !!  @tex $(kg m^{-2})$ @endtex
321!$OMP THREADPRIVATE(tmc_litter_wilt)
322  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_field !! Total moisture of litter at field cap. per soiltile
323                                                                         !!  @tex $(kg m^{-2})$ @endtex
324!$OMP THREADPRIVATE(tmc_litter_field)
325!!! A CHANGER DANS TOUT HYDROL: tmc_litter_res et sat ne devraient pas dependre de ji - tdo
326  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_res   !! Total moisture of litter at residual moisture per soiltile
327                                                                         !!  @tex $(kg m^{-2})$ @endtex
328!$OMP THREADPRIVATE(tmc_litter_res)
329  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_sat   !! Total moisture of litter at saturation per soiltile
330                                                                         !!  @tex $(kg m^{-2})$ @endtex
331!$OMP THREADPRIVATE(tmc_litter_sat)
332  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_awet  !! Total moisture of litter at mc_awet per soiltile
333                                                                         !!  @tex $(kg m^{-2})$ @endtex
334!$OMP THREADPRIVATE(tmc_litter_awet)
335  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_adry  !! Total moisture of litter at mc_adry per soiltile
336                                                                         !!  @tex $(kg m^{-2})$ @endtex
337!$OMP THREADPRIVATE(tmc_litter_adry)
338  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_wet_mea !! Total moisture in the litter over the grid below which
339                                                                         !! albedo is fixed constant
340                                                                         !!  @tex $(kg m^{-2})$ @endtex
341!$OMP THREADPRIVATE(tmc_litt_wet_mea)
342  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_dry_mea !! Total moisture in the litter over the grid above which
343                                                                         !! albedo is constant
344                                                                         !!  @tex $(kg m^{-2})$ @endtex
345!$OMP THREADPRIVATE(tmc_litt_dry_mea)
346  LOGICAL, SAVE                                      :: tmc_init_updated = .FALSE. !! Flag allowing to determine if tmc is initialized.
347!$OMP THREADPRIVATE(tmc_init_updated)
348
349  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: v1               !! Temporary variable (:)
350!$OMP THREADPRIVATE(v1)
351
352  !! par type de sol :
353  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ru_ns            !! Surface runoff per soiltile
354                                                                         !!  @tex $(kg m^{-2})$ @endtex
355!$OMP THREADPRIVATE(ru_ns)
356  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: dr_ns            !! Drainage per soiltile
357                                                                         !!  @tex $(kg m^{-2})$ @endtex
358!$OMP THREADPRIVATE(dr_ns)
359  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tr_ns            !! Transpiration per soiltile
360!$OMP THREADPRIVATE(tr_ns)
361  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: vegetmax_soil    !! (:,nvm,nstm) percentage of each veg. type on each soil
362                                                                         !! of each grid point
363!$OMP THREADPRIVATE(vegetmax_soil)
364  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: mc               !! Total volumetric water content at the calculation nodes
365                                                                         !! (eg : liquid + frozen)
366                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
367!$OMP THREADPRIVATE(mc)
368
369   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mc_read_prev       !! Soil moisture from file at previous timestep in the file
370!$OMP THREADPRIVATE(mc_read_prev)
371   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mc_read_next       !! Soil moisture from file at next time step in the file
372!$OMP THREADPRIVATE(mc_read_next)
373   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mc_read_current    !! For nudging, linear time interpolation bewteen mc_read_prev and mc_read_next
374!$OMP THREADPRIVATE(mc_read_current)
375   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: mask_mc_interp     !! Mask of valid data in soil moisture nudging file
376!$OMP THREADPRIVATE(mask_mc_interp)
377   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: tmc_aux            !! Temporary variable needed for the calculation of diag nudgincsm for nudging
378!$OMP THREADPRIVATE(tmc_aux)
379   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowdz_read_prev   !! snowdz read from file at previous timestep in the file
380!$OMP THREADPRIVATE(snowdz_read_prev)
381   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowdz_read_next   !! snowdz read from file at next time step in the file
382!$OMP THREADPRIVATE(snowdz_read_next)
383   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowrho_read_prev  !! snowrho read from file at previous timestep in the file
384!$OMP THREADPRIVATE(snowrho_read_prev)
385   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowrho_read_next  !! snowrho read from file at next time step in the file
386!$OMP THREADPRIVATE(snowrho_read_next)
387   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowtemp_read_prev !! snowtemp read from file at previous timestep in the file
388!$OMP THREADPRIVATE(snowtemp_read_prev)
389   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: snowtemp_read_next !! snowtemp read from file at next time step in the file
390!$OMP THREADPRIVATE(snowtemp_read_next)
391   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)   :: mask_snow_interp   !! Mask of valid data in snow nudging file
392!$OMP THREADPRIVATE(mask_snow_interp)
393
394   REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: mcl              !! Liquid water content
395                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
396!$OMP THREADPRIVATE(mcl)
397  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soilmoist        !! (:,nslm) Mean of each soil layer's moisture
398                                                                         !! across soiltiles
399                                                                         !!  @tex $(kg m^{-2})$ @endtex
400!$OMP THREADPRIVATE(soilmoist)
401  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soilmoist_liquid !! (:,nslm) Mean of each soil layer's liquid moisture
402                                                                         !! across soiltiles
403                                                                         !!  @tex $(kg m^{-2})$ @endtex
404!$OMP THREADPRIVATE(soilmoist_liquid)
405  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: soil_wet_ns      !! Soil wetness above mcw (0-1, unitless)
406!$OMP THREADPRIVATE(soil_wet_ns)
407  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soil_wet_litter  !! Soil wetness aove mvw in the litter (0-1, unitless)
408!$OMP THREADPRIVATE(soil_wet_litter)
409  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: qflux_ns         !! Diffusive water fluxes between soil layers
410                                                                         !! (at lower interface)
411!$OMP THREADPRIVATE(qflux_ns)
412  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: check_top_ns     !! Diagnostic calculated in hydrol_diag_soil_flux
413                                                                         !! (water balance residu of top soil layer)
414!$OMP THREADPRIVATE(check_top_ns)
415  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: profil_froz_hydro     !! Frozen fraction for each hydrological soil layer
416!$OMP THREADPRIVATE(profil_froz_hydro)
417  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: profil_froz_hydro_ns  !! As  profil_froz_hydro per soiltile
418!$OMP THREADPRIVATE(profil_froz_hydro_ns)
419
420
421CONTAINS
422
423!! ================================================================================================================================
424!! SUBROUTINE   : hydrol_initialize
425!!
426!>\BRIEF         Allocate module variables, read from restart file or initialize with default values
427!!
428!! DESCRIPTION :
429!!
430!! MAIN OUTPUT VARIABLE(S) :
431!!
432!! REFERENCE(S) :
433!!
434!! FLOWCHART    : None
435!! \n
436!_ ================================================================================================================================
437
438  SUBROUTINE hydrol_initialize ( ks,             nvan,      avan,          mcr,              &
439                                 mcs,            mcfc,      mcw,           kjit,             &
440                                 kjpindex,       index,     rest_id,                         &
441                                 njsc,           soiltile,  veget,         veget_max,        &
442                                 humrel,    vegstress,  drysoil_frac,        &
443                                 shumdiag_perma,    qsintveg,                        &
444                                 evap_bare_lim,  evap_bare_lim_ns,  snow,      snow_age,      snow_nobio,       &
445                                 snow_nobio_age, snowrho,   snowtemp,      snowgrain,        &
446                                 snowdz,         snowheat,  &
447                                 mc_layh,        mcl_layh,  soilmoist_out)
448
449    !! 0. Variable and parameter declaration
450    !! 0.1 Input variables
451
452    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number
453    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size
454    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map
455    INTEGER(i_std),INTENT (in)                         :: rest_id          !! Restart file identifier
456    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the
457                                                                           !! grid cell (1-nscm, unitless) 
458    ! 2D soil parameters
459    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1})
460    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless)
461    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: avan             !! Van Genuchten coeficients a (mm-1})
462    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
463    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
464    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
465    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
466   
467    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
468    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type           
469    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty)
470
471   
472    !! 0.2 Output variables
473    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: humrel         !! Relative humidity
474    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: vegstress      !! Veg. moisture stress (only for vegetation growth)
475    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: drysoil_frac   !! function of litter wetness
476    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: shumdiag_perma !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
477    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: qsintveg       !! Water on vegetation due to interception
478    REAL(r_std),DIMENSION (kjpindex), INTENT(out)        :: evap_bare_lim  !! Limitation factor for bare soil evaporation
479    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(out)   :: evap_bare_lim_ns !! Limitation factor for bare soil evaporation
480    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: snow           !! Snow mass [Kg/m^2]
481    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: snow_age       !! Snow age
482    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out):: snow_nobio     !! Water balance on ice, lakes, .. [Kg/m^2]
483    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out):: snow_nobio_age !! Snow age on ice, lakes, ...
484    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowrho        !! Snow density
485    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowtemp       !! Snow temperature
486    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowgrain      !! Snow grainsize
487    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowdz         !! Snow layer thickness
488    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowheat       !! Snow heat content
489    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: mc_layh        !! Volumetric moisture content for each layer in hydrol (liquid+ice) m3/m3
490    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: mcl_layh       !! Volumetric moisture content for each layer in hydrol (liquid) m3/m3
491    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: soilmoist_out  !! Total soil moisture content for each layer in hydrol (liquid+ice), mm
492    REAL(r_std),DIMENSION (kjpindex)                     :: soilwetdummy   !! Temporary variable never used
493
494    !! 0.4 Local variables
495    INTEGER(i_std)                                       :: jsl
496   
497!_ ================================================================================================================================
498
499    CALL hydrol_init (ks, nvan, avan, mcr, mcs, mcfc, mcw, njsc, kjit, kjpindex, index, rest_id, veget_max, soiltile, &
500         humrel, vegstress, snow,       snow_age,   snow_nobio, snow_nobio_age, qsintveg, &
501         snowdz, snowgrain, snowrho,    snowtemp,   snowheat, &
502         drysoil_frac, evap_bare_lim, evap_bare_lim_ns)
503   
504    CALL hydrol_var_init (ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, veget, veget_max, &
505         soiltile, njsc, mx_eau_var, shumdiag_perma, &
506         drysoil_frac, qsintveg, mc_layh, mcl_layh) 
507
508    !! Initialize hydrol_alma routine if the variables were not found in the restart file. This is done in the end of
509    !! hydrol_initialize so that all variables(humtot,..) that will be used are initialized.
510    IF (ALL(tot_watveg_beg(:)==val_exp) .OR.  ALL(tot_watsoil_beg(:)==val_exp) .OR. ALL(snow_beg(:)==val_exp)) THEN
511       ! The output variable soilwetdummy is not calculated at first call to hydrol_alma.
512       CALL hydrol_alma(kjpindex, index, .TRUE., qsintveg, snow, snow_nobio, soilwetdummy)
513    END IF
514   
515    !! Calculate itopmax indicating the number of layers where the node is above 0.1m depth
516    itopmax=1
517    DO jsl = 1, nslm
518       ! znh : depth of nodes
519       IF (znh(jsl) <= 0.1) THEN
520          itopmax=jsl
521       END IF
522    END DO
523    IF (printlev>=3) WRITE(numout,*) "Number of layers where the node is above 0.1m depth: itopmax=",itopmax
524
525    ! Copy soilmoist into a local variable to be sent to thermosoil
526    soilmoist_out(:,:) = soilmoist(:,:)
527
528  END SUBROUTINE hydrol_initialize
529
530
531!! ================================================================================================================================
532!! SUBROUTINE   : hydrol_main
533!!
534!>\BRIEF         
535!!
536!! DESCRIPTION :
537!! - called every time step
538!! - initialization and finalization part are not done in here
539!!
540!! - 1 computes snow  ==> explicitsnow
541!! - 2 computes vegetations reservoirs  ==> hydrol_vegupd
542!! - 3 computes canopy  ==> hydrol_canop
543!! - 4 computes surface reservoir  ==> hydrol_flood
544!! - 5 computes soil hydrology ==> hydrol_soil
545!!
546!! IMPORTANT NOTICE : The water fluxes are used in their integrated form, over the time step
547!! dt_sechiba, with a unit of kg m^{-2}.
548!!
549!! RECENT CHANGE(S) : None
550!!
551!! MAIN OUTPUT VARIABLE(S) :
552!!
553!! REFERENCE(S) :
554!!
555!! FLOWCHART    : None
556!! \n
557!_ ================================================================================================================================
558
559  SUBROUTINE hydrol_main (ks, nvan, avan, mcr, mcs, mcfc, mcw,  &
560       & kjit, kjpindex, &
561       & index, indexveg, indexsoil, indexlayer, indexnslm, &
562       & temp_sol_new, floodout, runoff, drainage, frac_nobio, totfrac_nobio, vevapwet, veget, veget_max, njsc, &
563       & qsintmax, qsintveg, vevapnu, vevapsno, vevapflo, snow, snow_age, snow_nobio, snow_nobio_age,  &
564       & tot_melt, transpir, precip_rain, precip_snow, returnflow, reinfiltration, irrigation, &
565       & humrel, vegstress, drysoil_frac, evapot, evapot_penm, evap_bare_lim, evap_bare_lim_ns, &
566       & flood_frac, flood_res, &
567       & shumdiag,shumdiag_perma, k_litt, litterhumdiag, soilcap, soiltile, fraclut, reinf_slope, rest_id, hist_id, hist2_id,&
568       & contfrac, stempdiag, &
569       & temp_air, pb, u, v, tq_cdrag, swnet, pgflux, &
570       & snowrho,snowtemp,snowgrain,snowdz,snowheat,snowliq, &
571       & grndflux,gtemp,tot_bare_soil, &
572       & lambda_snow,cgrnd_snow,dgrnd_snow,frac_snow_veg,temp_sol_add, &
573       & mc_layh, mcl_layh, soilmoist_out )
574
575    !! 0. Variable and parameter declaration
576
577    !! 0.1 Input variables
578 
579    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number
580    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size
581    INTEGER(i_std),INTENT (in)                         :: rest_id,hist_id  !! _Restart_ file and _history_ file identifier
582    INTEGER(i_std),INTENT (in)                         :: hist2_id         !! _history_ file 2 identifier
583    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map
584    INTEGER(i_std),DIMENSION (kjpindex*nvm), INTENT (in):: indexveg        !! Indeces of the points on the 3D map for veg
585    INTEGER(i_std),DIMENSION (kjpindex*nstm), INTENT (in):: indexsoil      !! Indeces of the points on the 3D map for soil
586    INTEGER(i_std),DIMENSION (kjpindex*nslm), INTENT (in):: indexlayer     !! Indeces of the points on the 3D map for soil layers
587    INTEGER(i_std),DIMENSION (kjpindex*nslm), INTENT (in):: indexnslm      !! Indeces of the points on the 3D map for of diagnostic soil layers
588
589    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_rain      !! Rain precipitation
590    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_snow      !! Snow precipitation
591    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: returnflow       !! Routed water which comes back into the soil (from the
592                                                                           !! bottom)
593    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinfiltration   !! Routed water which comes back into the soil (at the
594                                                                           !! top)
595    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: irrigation       !! Water from irrigation returning to soil moisture 
596    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: temp_sol_new     !! New soil temperature
597
598    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
599    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: frac_nobio     !! Fraction of ice, lakes, ...
600    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: totfrac_nobio    !! Total fraction of ice+lakes+...
601    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: soilcap          !! Soil capacity
602    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
603    REAL(r_std),DIMENSION (kjpindex,nlut), INTENT (in) :: fraclut          !! Fraction of each landuse tile (0-1, unitless)
604    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: vevapwet         !! Interception loss
605    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type           
606    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty)
607    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintmax         !! Maximum water on vegetation for interception
608    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: transpir         !! Transpiration
609    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinf_slope      !! Slope coef
610
611    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1})
612    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless)
613    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: avan             !! Van Genuchten coeficients a (mm-1})
614    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
615    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
616    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
617    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
618 
619    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot           !! Soil Potential Evaporation
620    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot_penm      !! Soil Potential Evaporation Correction
621    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: flood_frac       !! flood fraction
622    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: contfrac         !! Fraction of continent in the grid
623    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in) :: stempdiag        !! Diagnostic temp profile from thermosoil
624    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: temp_air         !! Air temperature
625    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: u,v              !! Horizontal wind speed
626    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: tq_cdrag         !! Surface drag coefficient (-)
627    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: pb               !! Surface pressure
628    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: swnet            !! Net shortwave radiation
629    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: pgflux           !! Net energy into snowpack
630    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: gtemp            !! First soil layer temperature
631    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: tot_bare_soil    !! Total evaporating bare soil fraction
632    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: lambda_snow      !! Coefficient of the linear extrapolation of surface temperature
633    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in):: cgrnd_snow       !! Integration coefficient for snow numerical scheme
634    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in):: dgrnd_snow       !! Integration coefficient for snow numerical scheme
635    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: frac_snow_veg    !! Snow cover fraction on vegetation   
636
637    !! 0.2 Output variables
638
639    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: vegstress        !! Veg. moisture stress (only for vegetation growth)
640    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: drysoil_frac     !! function of litter wetness
641    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out):: shumdiag         !! Relative soil moisture in each soil layer
642                                                                           !! with respect to (mcfc-mcw)
643                                                                           !! (unitless; can be out of 0-1)
644    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out):: shumdiag_perma   !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
645    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: k_litt           !! litter approximate conductivity
646    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: litterhumdiag    !! litter humidity
647    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: tot_melt         !! Total melt   
648    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: floodout         !! Flux out of floodplains
649   
650    !! 0.3 Modified variables
651
652    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout):: qsintveg         !! Water on vegetation due to interception
653    REAL(r_std),DIMENSION (kjpindex), INTENT(inout)    :: evap_bare_lim    !! Limitation factor (beta) for bare soil evaporation
654    REAL(r_std),DIMENSION (kjpindex,nstm),INTENT(inout):: evap_bare_lim_ns !! Limitation factor (beta) for bare soil evaporation   
655    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout):: humrel           !! Relative humidity
656    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapnu          !! Bare soil evaporation
657    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapsno         !! Snow evaporation
658    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapflo         !! Floodplain evaporation
659    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: flood_res        !! flood reservoir estimate
660    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: snow             !! Snow mass [kg/m^2]
661    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: snow_age         !! Snow age
662    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (inout) :: snow_nobio  !! Water balance on ice, lakes, .. [Kg/m^2]
663    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (inout) :: snow_nobio_age !! Snow age on ice, lakes, ...
664    !! We consider that any water on the ice is snow and we only peforme a water balance to have consistency.
665    !! The water balance is limite to + or - 10^6 so that accumulation is not endless
666
667    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: runoff       !! Complete surface runoff
668    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: drainage     !! Drainage
669    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowrho      !! Snow density
670    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowtemp     !! Snow temperature
671    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowgrain    !! Snow grainsize
672    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowdz       !! Snow layer thickness
673    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowheat     !! Snow heat content
674    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out)   :: snowliq      !! Snow liquid content (m)
675    REAL(r_std), DIMENSION (kjpindex), INTENT(out)         :: grndflux     !! Net flux into soil W/m2
676    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: mc_layh      !! Volumetric moisture content for each layer in hydrol(liquid + ice) [m3/m3)]
677    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: mcl_layh     !! Volumetric moisture content for each layer in hydrol(liquid) [m3/m3]
678    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: soilmoist_out!! Total soil moisture content for each layer in hydrol(liquid + ice) [mm]
679    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)       :: temp_sol_add !! additional surface temperature due to the melt of first layer
680                                                                           !! at the present time-step @tex ($K$) @endtex
681
682    !! 0.4 Local variables
683    INTEGER(i_std)                                     :: jst              !! Index of soil tiles (unitless, 1-3)
684    INTEGER(i_std)                                     :: jsl              !! Index of soil layers (unitless)
685    INTEGER(i_std)                                     :: ji, jv
686    REAL(r_std),DIMENSION (kjpindex)                   :: soilwet          !! A temporary diagnostic of soil wetness
687    REAL(r_std),DIMENSION (kjpindex)                   :: snowdepth_diag   !! Depth of snow layer containing default values, only for diagnostics
688    REAL(r_std),DIMENSION (kjpindex, nsnow)            :: snowdz_diag      !! Depth of snow layer on all layers containing default values,
689                                                                           !! only for diagnostics
690    REAL(r_std),DIMENSION (kjpindex)                   :: njsc_tmp         !! Temporary REAL value for njsc to write it
691    REAL(r_std), DIMENSION (kjpindex)                  :: snowmelt         !! Snow melt [mm/dt_sechiba]
692    REAL(r_std), DIMENSION (kjpindex,nstm)             :: tmc_top          !! Moisture content in the itopmax upper layers, per tile
693    REAL(r_std), DIMENSION (kjpindex)                  :: humtot_top       !! Moisture content in the itopmax upper layers, for diagnistics
694    REAL(r_std), DIMENSION(kjpindex)                   :: histvar          !! Temporary variable when computations are needed
695    REAL(r_std), DIMENSION (kjpindex,nvm)              :: frac_bare        !! Fraction(of veget_max) of bare soil in each vegetation type
696    INTEGER(i_std), DIMENSION(kjpindex*imax)           :: mc_lin_axis_index
697    REAL(r_std), DIMENSION(kjpindex)                   :: twbr             !! Grid-cell mean of TWBR Total Water Budget Residu[kg/m2/dt]
698    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_nroot       !! To ouput the grid-cell mean of nroot
699    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_dlh         !! To ouput the soil layer thickness on all grid points [m]
700    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcs         !! To ouput the mean of mcs
701    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcfc        !! To ouput the mean of mcfc
702    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcw         !! To ouput the mean of mcw
703    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcr         !! To ouput the mean of mcr
704    REAL(r_std),DIMENSION (kjpindex)                   :: land_tmcs        !! To ouput the grid-cell mean of tmcs
705    REAL(r_std),DIMENSION (kjpindex)                   :: land_tmcfc       !! To ouput the grid-cell mean of tmcfc
706    REAL(r_std),DIMENSION (kjpindex)                   :: drain_upd        !! Change in drainage due to decrease in vegtot
707                                                                           !! on mc [kg/m2/dt]
708    REAL(r_std),DIMENSION (kjpindex)                   :: runoff_upd       !! Change in runoff due to decrease in vegtot
709                                                                           !! on water2infilt[kg/m2/dt]
710    REAL(r_std),DIMENSION (kjpindex)                   :: mrsow            !! Soil wetness above wilting point for CMIP6 (humtot-WP)/(SAT-WP)
711    REAL(r_std), DIMENSION (kjpindex,nlut)             :: humtot_lut       !! Moisture content on landuse tiles, for diagnostics
712    REAL(r_std), DIMENSION (kjpindex,nlut)             :: humtot_top_lut   !! Moisture content in upper layers on landuse tiles, for diagnostics
713    REAL(r_std), DIMENSION (kjpindex,nlut)             :: mrro_lut         !! Total runoff from landuse tiles, for diagnostics
714
715!_ ================================================================================================================================
716    !! 1. Update vegtot_old and recalculate vegtot
717    vegtot_old(:) = vegtot(:)
718
719    DO ji = 1, kjpindex
720       vegtot(ji) = SUM(veget_max(ji,:))
721    ENDDO
722
723
724    !! 2. Applay nudging for soil moisture and/or snow variables
725
726    ! For soil moisture, here only read and interpolate the soil moisture from file to current time step.
727    ! The values will be applayed in hydrol_soil after the soil moisture has been updated.
728    IF (ok_nudge_mc) THEN
729       CALL hydrol_nudge_mc_read(kjit)
730    END IF
731
732    ! Read, interpolate and applay nudging of snow variables
733    IF ( ok_nudge_snow) THEN
734     CALL hydrol_nudge_snow(kjit, kjpindex, snowdz, snowrho, snowtemp )
735    END IF
736
737
738    !! 3. Shared time step
739    IF (printlev>=3) WRITE (numout,*) 'hydrol pas de temps = ',dt_sechiba
740
741    !
742    !! 3.1 Calculate snow processes with explicit snow model
743    CALL explicitsnow_main(kjpindex,    precip_rain,  precip_snow,   temp_air,    pb,       &
744         u,           v,            temp_sol_new,  soilcap,     pgflux,   &
745         frac_nobio,  totfrac_nobio,gtemp,                                &
746         lambda_snow, cgrnd_snow,   dgrnd_snow,    contfrac,              & 
747         vevapsno,    snow_age,     snow_nobio_age,snow_nobio,  snowrho,  &
748         snowgrain,   snowdz,       snowtemp,      snowheat,    snow,     &
749         temp_sol_add,                                                         &
750         snowliq,     subsnownobio, grndflux,      snowmelt,    tot_melt, &
751         subsinksoil)           
752       
753    !
754    !! 3.2 computes vegetations reservoirs  ==>hydrol_vegupd
755    CALL hydrol_vegupd(kjpindex, veget, veget_max, soiltile, qsintveg, frac_bare, drain_upd, runoff_upd)
756
757
758   
759    !! Calculate kfact_root
760    IF (kfact_root_const) THEN
761       ! Set kfact_root constant to 1
762       kfact_root(:,:,:) = un
763    ELSE
764       ! An exponential factor is used to increase ks near the surface depending on the amount of roots in the soil
765       ! through a geometric average over the vegets
766       ! This comes from the PhD thesis of d'Orgeval, 2006, p82; d'Orgeval et al. 2008, Eqs. 3-4
767       ! (Calibrated against Hapex-Sahel measurements)
768       ! Since rev 2916: veget_max/2 is used instead of veget
769       kfact_root(:,:,:) = un
770       DO jsl = 1, nslm
771          DO jv = 2, nvm
772             jst = pref_soil_veg(jv)
773             DO ji = 1, kjpindex
774                IF (soiltile(ji,jst) .GT. min_sechiba) THEN
775                   kfact_root(ji,jsl,jst) = kfact_root(ji,jsl,jst) * &
776                        MAX((MAXVAL(ks_usda)/ks(ji))**(- vegetmax_soil(ji,jv,jst)/2 * (humcste(jv)*zz(jsl)/mille - un)/deux), &
777                        un) 
778                ENDIF
779             ENDDO
780          ENDDO
781       ENDDO
782    END IF
783
784
785    !
786    !! 3.3 computes canopy  ==>hydrol_canop
787    CALL hydrol_canop(kjpindex, precip_rain, vevapwet, veget_max, veget, qsintmax, qsintveg,precisol,tot_melt)
788
789    !
790    !! 3.4 computes surface reservoir  ==>hydrol_flood
791    CALL hydrol_flood(kjpindex,  vevapflo, flood_frac, flood_res, floodout)
792
793    !
794    !! 3.5 computes soil hydrology ==>hydrol_soil
795
796    CALL hydrol_soil(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, veget_max, soiltile, njsc, reinf_slope,  &
797         transpir, vevapnu, evapot, evapot_penm, runoff, drainage, & 
798         returnflow, reinfiltration, irrigation, &
799         tot_melt,evap_bare_lim,evap_bare_lim_ns, shumdiag, shumdiag_perma, &
800         k_litt, litterhumdiag, humrel, vegstress, drysoil_frac,&
801         stempdiag,snow,snowdz, tot_bare_soil,  u, v, tq_cdrag, &
802         mc_layh, mcl_layh)
803
804    ! The update fluxes come from hydrol_vegupd
805    drainage(:) =  drainage(:) +  drain_upd(:)
806    runoff(:) =  runoff(:) +  runoff_upd(:)
807
808
809    !! 4 write out file  ==> hydrol_alma/histwrite(*)
810    !
811    ! If we use the ALMA standards
812    CALL hydrol_alma(kjpindex, index, .FALSE., qsintveg, snow, snow_nobio, soilwet)
813   
814
815    ! Calculate the moisture in the upper itopmax layers corresponding to 0.1m (humtot_top):
816    ! For ORCHIDEE with nslm=11 and zmaxh=2, itopmax=6.
817    ! We compute tmc_top as tmc but only for the first itopmax layers. Then we compute a humtot with this variable.
818    DO jst=1,nstm
819       DO ji=1,kjpindex
820          tmc_top(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
821          DO jsl = 2, itopmax
822             tmc_top(ji,jst) = tmc_top(ji,jst) + dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
823                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
824          ENDDO
825       ENDDO
826    ENDDO
827 
828    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
829    humtot_top(:) = zero
830    DO jst=1,nstm
831       DO ji=1,kjpindex
832          humtot_top(ji) = humtot_top(ji) + soiltile(ji,jst) * tmc_top(ji,jst) * vegtot(ji)
833       ENDDO
834    ENDDO
835
836    ! Calculate the Total Water Budget Residu (in kg/m2 over dt_sechiba)
837    ! All the delstocks and fluxes below are averaged over the mesh
838    ! snow_nobio included in delswe
839    ! Does not include the routing reservoirs, although the flux to/from routing are integrated
840    DO ji=1,kjpindex
841       twbr(ji) = (delsoilmoist(ji) + delintercept(ji) + delswe(ji)) &
842            - ( precip_rain(ji) + precip_snow(ji) + irrigation(ji) + floodout(ji) &
843            + returnflow(ji) + reinfiltration(ji) ) &
844            + ( runoff(ji) + drainage(ji) + SUM(vevapwet(ji,:)) &
845            + SUM(transpir(ji,:)) + vevapnu(ji) + vevapsno(ji) + vevapflo(ji) ) 
846    ENDDO
847    ! Transform unit from kg/m2/dt to kg/m2/s (or mm/s)
848    CALL xios_orchidee_send_field("twbr",twbr/dt_sechiba)
849    CALL xios_orchidee_send_field("undermcr",undermcr) ! nb of tiles undermcr at end of timestep
850
851    ! Calculate land_nroot : grid-cell mean of nroot
852    ! Do not treat PFT1 because it has no roots
853    land_nroot(:,:) = zero
854    DO jsl=1,nslm
855       DO jv=2,nvm
856          DO ji=1,kjpindex
857               IF ( vegtot(ji) > min_sechiba ) THEN
858               land_nroot(ji,jsl) = land_nroot(ji,jsl) + veget_max(ji,jv) * nroot(ji,jv,jsl) / vegtot(ji) 
859            END IF
860          END DO
861       ENDDO
862    ENDDO
863    CALL xios_orchidee_send_field("nroot",land_nroot)   
864
865    DO jsl=1,nslm
866       land_dlh(:,jsl)=dlh(jsl)
867    ENDDO
868    CALL xios_orchidee_send_field("dlh",land_dlh)
869
870    ! Particular soil moisture values, spatially averaged over the grid-cell
871    ! (a) total SM in kg/m2
872    !     we average the total values of each soiltile and multiply by vegtot to transform to a grid-cell mean (over total land)
873    land_tmcs(:) = zero
874    land_tmcfc(:) = zero
875    DO jst=1,nstm
876       DO ji=1,kjpindex
877          land_tmcs(ji) = land_tmcs(ji) + soiltile(ji,jst) * tmcs(ji,jst) * vegtot(ji)
878          land_tmcfc(ji) = land_tmcfc(ji) + soiltile(ji,jst) * tmcfc(ji,jst) * vegtot(ji)
879       ENDDO
880    ENDDO
881    CALL xios_orchidee_send_field("tmcs",land_tmcs) ! in kg/m2
882    CALL xios_orchidee_send_field("tmcfc",land_tmcfc) ! in kg/m2
883
884    ! (b) volumetric moisture content by layers in m3/m3
885    !     mcs etc are identical in all layers (no normalization by vegtot to be comparable to mc)
886    DO jsl=1,nslm
887       land_mcs(:,jsl) = mcs(:)
888       land_mcfc(:,jsl) = mcfc(:)
889       land_mcw(:,jsl) = mcw(:)
890       land_mcr(:,jsl) = mcr(:)
891    ENDDO
892    CALL xios_orchidee_send_field("mcs",land_mcs) ! in m3/m3
893    CALL xios_orchidee_send_field("mcfc",land_mcfc) ! in m3/m3
894    CALL xios_orchidee_send_field("mcw",land_mcw) ! in m3/m3
895    CALL xios_orchidee_send_field("mcr",land_mcr) ! in m3/m3
896
897     
898    CALL xios_orchidee_send_field("water2infilt",water2infilt)   
899    CALL xios_orchidee_send_field("mc",mc)
900    CALL xios_orchidee_send_field("kfact_root",kfact_root)
901    CALL xios_orchidee_send_field("vegetmax_soil",vegetmax_soil)
902    CALL xios_orchidee_send_field("evapnu_soil",ae_ns/dt_sechiba)
903    CALL xios_orchidee_send_field("drainage_soil",dr_ns/dt_sechiba)
904    CALL xios_orchidee_send_field("transpir_soil",tr_ns/dt_sechiba)
905    CALL xios_orchidee_send_field("runoff_soil",ru_ns/dt_sechiba)
906    CALL xios_orchidee_send_field("humrel",humrel)     
907    CALL xios_orchidee_send_field("drainage",drainage/dt_sechiba) ! [kg m-2 s-1]
908    CALL xios_orchidee_send_field("runoff",runoff/dt_sechiba) ! [kg m-2 s-1]
909    CALL xios_orchidee_send_field("precisol",precisol/dt_sechiba)
910    CALL xios_orchidee_send_field("throughfall",throughfall/dt_sechiba)
911    CALL xios_orchidee_send_field("precip_rain",precip_rain/dt_sechiba)
912    CALL xios_orchidee_send_field("precip_snow",precip_snow/dt_sechiba)
913    CALL xios_orchidee_send_field("qsintmax",qsintmax)
914    CALL xios_orchidee_send_field("qsintveg",qsintveg)
915    CALL xios_orchidee_send_field("qsintveg_tot",SUM(qsintveg(:,:),dim=2))
916    histvar(:)=(precip_rain(:)-SUM(throughfall(:,:),dim=2))
917    CALL xios_orchidee_send_field("prveg",histvar/dt_sechiba)
918
919    IF ( do_floodplains ) THEN
920       CALL xios_orchidee_send_field("floodout",floodout/dt_sechiba)
921    END IF
922
923    CALL xios_orchidee_send_field("snowmelt",snowmelt/dt_sechiba)
924    CALL xios_orchidee_send_field("tot_melt",tot_melt/dt_sechiba)
925
926    CALL xios_orchidee_send_field("soilmoist",soilmoist)
927    CALL xios_orchidee_send_field("soilmoist_liquid",soilmoist_liquid)
928    CALL xios_orchidee_send_field("humtot_frozen",SUM(soilmoist(:,:),2)-SUM(soilmoist_liquid(:,:),2))
929    CALL xios_orchidee_send_field("tmc",tmc)
930    CALL xios_orchidee_send_field("humtot",humtot)
931    CALL xios_orchidee_send_field("humtot_top",humtot_top)
932
933    ! For the soil wetness above wilting point for CMIP6 (mrsow)
934    mrsow(:) = MAX( zero,humtot(:) - zmaxh*mille*mcw(:) ) &
935         / ( zmaxh*mille*( mcs(:) - mcw(:) ) )
936    CALL xios_orchidee_send_field("mrsow",mrsow)
937
938
939   
940    ! Prepare diagnostic snow variables
941    !  Add XIOS default value where no snow
942    DO ji=1,kjpindex
943       IF (snow(ji) > 0) THEN
944          snowdz_diag(ji,:) = snowdz(ji,:)
945          snowdepth_diag(ji) = SUM(snowdz(ji,:))*(1-totfrac_nobio(ji))*frac_snow_veg(ji)
946       ELSE
947          snowdz_diag(ji,:) = xios_default_val
948          snowdepth_diag(ji) = xios_default_val             
949       END IF
950    END DO
951    CALL xios_orchidee_send_field("snowdz",snowdz_diag)
952    CALL xios_orchidee_send_field("snowdepth",snowdepth_diag)
953
954    CALL xios_orchidee_send_field("frac_bare",frac_bare)
955    CALL xios_orchidee_send_field("soilwet",soilwet)
956    CALL xios_orchidee_send_field("delsoilmoist",delsoilmoist)
957    CALL xios_orchidee_send_field("delswe",delswe)
958    CALL xios_orchidee_send_field("delintercept",delintercept) 
959
960    IF (ok_freeze_cwrr) THEN
961       CALL xios_orchidee_send_field("profil_froz_hydro",profil_froz_hydro)
962    END IF
963    CALL xios_orchidee_send_field("profil_froz_hydro_ns", profil_froz_hydro_ns)
964    CALL xios_orchidee_send_field("kk_moy",kk_moy) ! in mm/d
965
966    !! Calculate diagnostic variables on Landuse tiles for LUMIP/CMIP6
967    humtot_lut(:,:)=0
968    humtot_top_lut(:,:)=0
969    mrro_lut(:,:)=0
970    DO jv=1,nvm
971       jst=pref_soil_veg(jv) ! soil tile index
972       IF (natural(jv)) THEN
973          humtot_lut(:,id_psl) = humtot_lut(:,id_psl) + tmc(:,jst)*veget_max(:,jv)
974          humtot_top_lut(:,id_psl) = humtot_top_lut(:,id_psl) + tmc_top(:,jst)*veget_max(:,jv)
975          mrro_lut(:,id_psl) = mrro_lut(:,id_psl) + (dr_ns(:,jst)+ru_ns(:,jst))*veget_max(:,jv)
976       ELSE
977          humtot_lut(:,id_crp) = humtot_lut(:,id_crp) + tmc(:,jst)*veget_max(:,jv)
978          humtot_top_lut(:,id_crp) = humtot_top_lut(:,id_crp) + tmc_top(:,jst)*veget_max(:,jv)
979          mrro_lut(:,id_crp) = mrro_lut(:,id_crp) + (dr_ns(:,jst)+ru_ns(:,jst))*veget_max(:,jv)
980       ENDIF
981    END DO
982
983    WHERE (fraclut(:,id_psl)>min_sechiba)
984       humtot_lut(:,id_psl) = humtot_lut(:,id_psl)/fraclut(:,id_psl)
985       humtot_top_lut(:,id_psl) = humtot_top_lut(:,id_psl)/fraclut(:,id_psl)
986       mrro_lut(:,id_psl) = mrro_lut(:,id_psl)/fraclut(:,id_psl)/dt_sechiba
987    ELSEWHERE
988       humtot_lut(:,id_psl) = val_exp
989       humtot_top_lut(:,id_psl) = val_exp
990       mrro_lut(:,id_psl) = val_exp
991    END WHERE
992    WHERE (fraclut(:,id_crp)>min_sechiba)
993       humtot_lut(:,id_crp) = humtot_lut(:,id_crp)/fraclut(:,id_crp)
994       humtot_top_lut(:,id_crp) = humtot_top_lut(:,id_crp)/fraclut(:,id_crp)
995       mrro_lut(:,id_crp) = mrro_lut(:,id_crp)/fraclut(:,id_crp)/dt_sechiba
996    ELSEWHERE
997       humtot_lut(:,id_crp) = val_exp
998       humtot_top_lut(:,id_crp) = val_exp
999       mrro_lut(:,id_crp) = val_exp
1000    END WHERE
1001
1002    humtot_lut(:,id_pst) = val_exp
1003    humtot_lut(:,id_urb) = val_exp
1004    humtot_top_lut(:,id_pst) = val_exp
1005    humtot_top_lut(:,id_urb) = val_exp
1006    mrro_lut(:,id_pst) = val_exp
1007    mrro_lut(:,id_urb) = val_exp
1008
1009    CALL xios_orchidee_send_field("humtot_lut",humtot_lut)
1010    CALL xios_orchidee_send_field("humtot_top_lut",humtot_top_lut)
1011    CALL xios_orchidee_send_field("mrro_lut",mrro_lut)
1012
1013    ! Write diagnistic for soil moisture nudging
1014    IF (ok_nudge_mc) CALL hydrol_nudge_mc_diag(kjpindex, soiltile)
1015
1016
1017    IF ( .NOT. almaoutput ) THEN
1018       CALL histwrite_p(hist_id, 'frac_bare', kjit, frac_bare, kjpindex*nvm, indexveg)
1019
1020       DO jst=1,nstm
1021          ! var_name= "mc_1" ... "mc_3"
1022          WRITE (var_name,"('moistc_',i1)") jst
1023          CALL histwrite_p(hist_id, TRIM(var_name), kjit,mc(:,:,jst), kjpindex*nslm, indexlayer)
1024
1025          ! var_name= "kfactroot_1" ... "kfactroot_3"
1026          WRITE (var_name,"('kfactroot_',i1)") jst
1027          CALL histwrite_p(hist_id, TRIM(var_name), kjit, kfact_root(:,:,jst), kjpindex*nslm, indexlayer)
1028
1029          ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1030          WRITE (var_name,"('vegetsoil_',i1)") jst
1031          CALL histwrite_p(hist_id, TRIM(var_name), kjit,vegetmax_soil(:,:,jst), kjpindex*nvm, indexveg)
1032       ENDDO
1033       CALL histwrite_p(hist_id, 'evapnu_soil', kjit, ae_ns, kjpindex*nstm, indexsoil)
1034       CALL histwrite_p(hist_id, 'drainage_soil', kjit, dr_ns, kjpindex*nstm, indexsoil)
1035       CALL histwrite_p(hist_id, 'transpir_soil', kjit, tr_ns, kjpindex*nstm, indexsoil)
1036       CALL histwrite_p(hist_id, 'runoff_soil', kjit, ru_ns, kjpindex*nstm, indexsoil)
1037       CALL histwrite_p(hist_id, 'humtot_soil', kjit, tmc, kjpindex*nstm, indexsoil)
1038       ! mrso is a perfect duplicate of humtot
1039       CALL histwrite_p(hist_id, 'humtot', kjit, humtot, kjpindex, index)
1040       CALL histwrite_p(hist_id, 'mrso', kjit, humtot, kjpindex, index)
1041       CALL histwrite_p(hist_id, 'mrsos', kjit, humtot_top, kjpindex, index)
1042       njsc_tmp(:)=njsc(:)
1043       CALL histwrite_p(hist_id, 'soilindex', kjit, njsc_tmp, kjpindex, index)
1044       CALL histwrite_p(hist_id, 'humrel',   kjit, humrel,   kjpindex*nvm, indexveg)
1045       CALL histwrite_p(hist_id, 'drainage', kjit, drainage, kjpindex, index)
1046       ! NB! According to histdef in intersurf, the variables 'runoff' and 'mrros' have different units
1047       CALL histwrite_p(hist_id, 'runoff', kjit, runoff, kjpindex, index)
1048       CALL histwrite_p(hist_id, 'mrros', kjit, runoff, kjpindex, index)
1049       histvar(:)=(runoff(:)+drainage(:))
1050       CALL histwrite_p(hist_id, 'mrro', kjit, histvar, kjpindex, index)
1051       CALL histwrite_p(hist_id, 'precisol', kjit, precisol, kjpindex*nvm, indexveg)
1052       CALL histwrite_p(hist_id, 'rain', kjit, precip_rain, kjpindex, index)
1053
1054       histvar(:)=(precip_rain(:)-SUM(throughfall(:,:),dim=2))
1055       CALL histwrite_p(hist_id, 'prveg', kjit, histvar, kjpindex, index)
1056
1057       CALL histwrite_p(hist_id, 'snowf', kjit, precip_snow, kjpindex, index)
1058       CALL histwrite_p(hist_id, 'qsintmax', kjit, qsintmax, kjpindex*nvm, indexveg)
1059       CALL histwrite_p(hist_id, 'qsintveg', kjit, qsintveg, kjpindex*nvm, indexveg)
1060       CALL histwrite_p(hist_id, 'snowmelt',kjit,snowmelt,kjpindex,index)
1061       CALL histwrite_p(hist_id, 'shumdiag_perma',kjit,shumdiag_perma,kjpindex*nslm,indexnslm)
1062
1063       IF ( do_floodplains ) THEN
1064          CALL histwrite_p(hist_id, 'floodout', kjit, floodout, kjpindex, index)
1065       ENDIF
1066       !
1067       IF ( hist2_id > 0 ) THEN
1068          DO jst=1,nstm
1069             ! var_name= "mc_1" ... "mc_3"
1070             WRITE (var_name,"('moistc_',i1)") jst
1071             CALL histwrite_p(hist2_id, TRIM(var_name), kjit,mc(:,:,jst), kjpindex*nslm, indexlayer)
1072
1073             ! var_name= "kfactroot_1" ... "kfactroot_3"
1074             WRITE (var_name,"('kfactroot_',i1)") jst
1075             CALL histwrite_p(hist2_id, TRIM(var_name), kjit, kfact_root(:,:,jst), kjpindex*nslm, indexlayer)
1076
1077             ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1078             WRITE (var_name,"('vegetsoil_',i1)") jst
1079             CALL histwrite_p(hist2_id, TRIM(var_name), kjit,vegetmax_soil(:,:,jst), kjpindex*nvm, indexveg)
1080          ENDDO
1081          CALL histwrite_p(hist2_id, 'evapnu_soil', kjit, ae_ns, kjpindex*nstm, indexsoil)
1082          CALL histwrite_p(hist2_id, 'drainage_soil', kjit, dr_ns, kjpindex*nstm, indexsoil)
1083          CALL histwrite_p(hist2_id, 'transpir_soil', kjit, tr_ns, kjpindex*nstm, indexsoil)
1084          CALL histwrite_p(hist2_id, 'runoff_soil', kjit, ru_ns, kjpindex*nstm, indexsoil)
1085          CALL histwrite_p(hist2_id, 'humtot_soil', kjit, tmc, kjpindex*nstm, indexsoil)
1086          ! mrso is a perfect duplicate of humtot
1087          CALL histwrite_p(hist2_id, 'humtot', kjit, humtot, kjpindex, index)
1088          CALL histwrite_p(hist2_id, 'mrso', kjit, humtot, kjpindex, index)
1089          CALL histwrite_p(hist2_id, 'mrsos', kjit, humtot_top, kjpindex, index)
1090          njsc_tmp(:)=njsc(:)
1091          CALL histwrite_p(hist2_id, 'soilindex', kjit, njsc_tmp, kjpindex, index)
1092          CALL histwrite_p(hist2_id, 'humrel',   kjit, humrel,   kjpindex*nvm, indexveg)
1093          CALL histwrite_p(hist2_id, 'drainage', kjit, drainage, kjpindex, index)
1094          ! NB! According to histdef in intersurf, the variables 'runoff' and 'mrros' have different units
1095          CALL histwrite_p(hist2_id, 'runoff', kjit, runoff, kjpindex, index)
1096          CALL histwrite_p(hist2_id, 'mrros', kjit, runoff, kjpindex, index)
1097          histvar(:)=(runoff(:)+drainage(:))
1098          CALL histwrite_p(hist2_id, 'mrro', kjit, histvar, kjpindex, index)
1099
1100          IF ( do_floodplains ) THEN
1101             CALL histwrite_p(hist2_id, 'floodout', kjit, floodout, kjpindex, index)
1102          ENDIF
1103          CALL histwrite_p(hist2_id, 'precisol', kjit, precisol, kjpindex*nvm, indexveg)
1104          CALL histwrite_p(hist2_id, 'rain', kjit, precip_rain, kjpindex, index)
1105          CALL histwrite_p(hist2_id, 'snowf', kjit, precip_snow, kjpindex, index)
1106          CALL histwrite_p(hist2_id, 'snowmelt',kjit,snowmelt,kjpindex,index)
1107          CALL histwrite_p(hist2_id, 'qsintmax', kjit, qsintmax, kjpindex*nvm, indexveg)
1108          CALL histwrite_p(hist2_id, 'qsintveg', kjit, qsintveg, kjpindex*nvm, indexveg)
1109       ENDIF
1110    ELSE
1111       CALL histwrite_p(hist_id, 'Snowf', kjit, precip_snow, kjpindex, index)
1112       CALL histwrite_p(hist_id, 'Rainf', kjit, precip_rain, kjpindex, index)
1113       CALL histwrite_p(hist_id, 'Qs', kjit, runoff, kjpindex, index)
1114       CALL histwrite_p(hist_id, 'Qsb', kjit, drainage, kjpindex, index)
1115       CALL histwrite_p(hist_id, 'Qsm', kjit, snowmelt, kjpindex, index)
1116       CALL histwrite_p(hist_id, 'DelSoilMoist', kjit, delsoilmoist, kjpindex, index)
1117       CALL histwrite_p(hist_id, 'DelSWE', kjit, delswe, kjpindex, index)
1118       CALL histwrite_p(hist_id, 'DelIntercept', kjit, delintercept, kjpindex, index)
1119       !
1120       CALL histwrite_p(hist_id, 'SoilMoist', kjit, soilmoist, kjpindex*nslm, indexlayer)
1121       CALL histwrite_p(hist_id, 'SoilWet', kjit, soilwet, kjpindex, index)
1122       !
1123       CALL histwrite_p(hist_id, 'RootMoist', kjit, tot_watsoil_end, kjpindex, index)
1124       CALL histwrite_p(hist_id, 'SubSnow', kjit, vevapsno, kjpindex, index)
1125
1126       IF ( hist2_id > 0 ) THEN
1127          CALL histwrite_p(hist2_id, 'Snowf', kjit, precip_snow, kjpindex, index)
1128          CALL histwrite_p(hist2_id, 'Rainf', kjit, precip_rain, kjpindex, index)
1129          CALL histwrite_p(hist2_id, 'Qs', kjit, runoff, kjpindex, index)
1130          CALL histwrite_p(hist2_id, 'Qsb', kjit, drainage, kjpindex, index)
1131          CALL histwrite_p(hist2_id, 'Qsm', kjit, snowmelt, kjpindex, index)
1132          CALL histwrite_p(hist2_id, 'DelSoilMoist', kjit, delsoilmoist, kjpindex, index)
1133          CALL histwrite_p(hist2_id, 'DelSWE', kjit, delswe, kjpindex, index)
1134          CALL histwrite_p(hist2_id, 'DelIntercept', kjit, delintercept, kjpindex, index)
1135          !
1136          CALL histwrite_p(hist2_id, 'SoilMoist', kjit, soilmoist, kjpindex*nslm, indexlayer)
1137          CALL histwrite_p(hist2_id, 'SoilWet', kjit, soilwet, kjpindex, index)
1138          !
1139          CALL histwrite_p(hist2_id, 'RootMoist', kjit, tot_watsoil_end, kjpindex, index)
1140          CALL histwrite_p(hist2_id, 'SubSnow', kjit, vevapsno, kjpindex, index)
1141       ENDIF
1142    ENDIF
1143
1144    IF (ok_freeze_cwrr) THEN
1145       CALL histwrite_p(hist_id, 'profil_froz_hydro', kjit,profil_froz_hydro , kjpindex*nslm, indexlayer)
1146    ENDIF
1147    CALL histwrite_p(hist_id, 'kk_moy', kjit, kk_moy,kjpindex*nslm, indexlayer) ! averaged over soiltiles
1148    DO jst=1,nstm
1149       WRITE (var_name,"('profil_froz_hydro_',i1)") jst
1150       CALL histwrite_p(hist_id, TRIM(var_name), kjit, profil_froz_hydro_ns(:,:,jst), kjpindex*nslm, indexlayer)
1151    ENDDO
1152
1153    ! Copy soilmoist into a local variable to be sent to thermosoil
1154    soilmoist_out(:,:) = soilmoist(:,:)
1155
1156    IF (printlev>=3) WRITE (numout,*) ' hydrol_main Done '
1157
1158  END SUBROUTINE hydrol_main
1159
1160
1161!! ================================================================================================================================
1162!! SUBROUTINE   : hydrol_finalize
1163!!
1164!>\BRIEF         
1165!!
1166!! DESCRIPTION : This subroutine writes the module variables and variables calculated in hydrol to restart file
1167!!
1168!! MAIN OUTPUT VARIABLE(S) :
1169!!
1170!! REFERENCE(S) :
1171!!
1172!! FLOWCHART    : None
1173!! \n
1174!_ ================================================================================================================================
1175
1176  SUBROUTINE hydrol_finalize( kjit,           kjpindex,   rest_id,  vegstress,  &
1177                              qsintveg,       humrel,     snow,     snow_age, snow_nobio, &
1178                              snow_nobio_age, snowrho,    snowtemp, snowdz,     &
1179                              snowheat,       snowgrain,  &
1180                              drysoil_frac, evap_bare_lim, evap_bare_lim_ns)
1181
1182    !! 0. Variable and parameter declaration
1183    !! 0.1 Input variables
1184    INTEGER(i_std), INTENT(in)                           :: kjit           !! Time step number
1185    INTEGER(i_std), INTENT(in)                           :: kjpindex       !! Domain size
1186    INTEGER(i_std),INTENT (in)                           :: rest_id        !! Restart file identifier
1187    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: vegstress      !! Veg. moisture stress (only for vegetation growth)
1188    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: qsintveg       !! Water on vegetation due to interception
1189    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: humrel
1190    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow           !! Snow mass [Kg/m^2]
1191    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow_age       !! Snow age
1192    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio     !! Water balance on ice, lakes, .. [Kg/m^2]
1193    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio_age !! Snow age on ice, lakes, ...
1194    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowrho        !! Snow density
1195    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowtemp       !! Snow temperature
1196    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowdz         !! Snow layer thickness
1197    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowheat       !! Snow heat content
1198    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowgrain      !! Snow grainsize
1199    REAL(r_std),DIMENSION (kjpindex),INTENT(in)          :: drysoil_frac   !! function of litter wetness
1200    REAL(r_std),DIMENSION (kjpindex),INTENT(in)          :: evap_bare_lim
1201    REAL(r_std),DIMENSION (kjpindex,nstm),INTENT(in)     :: evap_bare_lim_ns
1202
1203    !! 0.4 Local variables
1204    INTEGER(i_std)                                       :: jst, jsl
1205   
1206!_ ================================================================================================================================
1207
1208
1209    IF (printlev>=3) WRITE (numout,*) 'Write restart file with HYDROLOGIC variables '
1210
1211    DO jst=1,nstm
1212       ! var_name= "mc_1" ... "mc_3"
1213       WRITE (var_name,"('moistc_',i1)") jst
1214       CALL restput_p(rest_id, var_name, nbp_glo,  nslm, 1, kjit, mc(:,:,jst), 'scatter',  nbp_glo, index_g)
1215    END DO
1216
1217    DO jst=1,nstm
1218       ! var_name= "mcl_1" ... "mcl_3"
1219       WRITE (var_name,"('moistcl_',i1)") jst
1220       CALL restput_p(rest_id, var_name, nbp_glo,  nslm, 1, kjit, mcl(:,:,jst), 'scatter',  nbp_glo, index_g)
1221    END DO
1222   
1223    IF (ok_nudge_mc) THEN
1224       DO jst=1,nstm
1225          WRITE (var_name,"('mc_read_next_',i1)") jst
1226          CALL restput_p(rest_id, var_name, nbp_glo,  nslm, 1, kjit, mc_read_next(:,:,jst), 'scatter',  nbp_glo, index_g)
1227       END DO
1228    END IF
1229
1230    IF (ok_nudge_snow) THEN
1231       CALL restput_p(rest_id, 'snowdz_read_next', nbp_glo,  nsnow, 1, kjit, snowdz_read_next(:,:), &
1232            'scatter',  nbp_glo, index_g)
1233       CALL restput_p(rest_id, 'snowrho_read_next', nbp_glo,  nsnow, 1, kjit, snowrho_read_next(:,:), &
1234            'scatter',  nbp_glo, index_g)
1235       CALL restput_p(rest_id, 'snowtemp_read_next', nbp_glo,  nsnow, 1, kjit, snowtemp_read_next(:,:), &
1236            'scatter',  nbp_glo, index_g)
1237    END IF
1238
1239
1240           
1241    DO jst=1,nstm
1242       DO jsl=1,nslm
1243          ! var_name= "us_1_01" ... "us_3_11"
1244          WRITE (var_name,"('us_',i1,'_',i2.2)") jst,jsl
1245          CALL restput_p(rest_id, var_name, nbp_glo,nvm, 1,kjit,us(:,:,jst,jsl),'scatter',nbp_glo,index_g)
1246       END DO
1247    END DO
1248   
1249    CALL restput_p(rest_id, 'free_drain_coef', nbp_glo,   nstm, 1, kjit,  free_drain_coef, 'scatter',  nbp_glo, index_g)
1250    CALL restput_p(rest_id, 'zwt_force', nbp_glo,   nstm, 1, kjit,  zwt_force, 'scatter',  nbp_glo, index_g)
1251    CALL restput_p(rest_id, 'water2infilt', nbp_glo,   nstm, 1, kjit,  water2infilt, 'scatter',  nbp_glo, index_g)
1252    CALL restput_p(rest_id, 'ae_ns', nbp_glo,   nstm, 1, kjit,  ae_ns, 'scatter',  nbp_glo, index_g)
1253    CALL restput_p(rest_id, 'vegstress', nbp_glo,   nvm, 1, kjit,  vegstress, 'scatter',  nbp_glo, index_g)
1254    CALL restput_p(rest_id, 'snow', nbp_glo,   1, 1, kjit,  snow, 'scatter',  nbp_glo, index_g)
1255    CALL restput_p(rest_id, 'snow_age', nbp_glo,   1, 1, kjit,  snow_age, 'scatter',  nbp_glo, index_g)
1256    CALL restput_p(rest_id, 'snow_nobio', nbp_glo,   nnobio, 1, kjit,  snow_nobio, 'scatter', nbp_glo, index_g)
1257    CALL restput_p(rest_id, 'snow_nobio_age', nbp_glo,   nnobio, 1, kjit,  snow_nobio_age, 'scatter', nbp_glo, index_g)
1258    CALL restput_p(rest_id, 'qsintveg', nbp_glo, nvm, 1, kjit,  qsintveg, 'scatter',  nbp_glo, index_g)
1259    CALL restput_p(rest_id, 'evap_bare_lim_ns', nbp_glo, nstm, 1, kjit,  evap_bare_lim_ns, 'scatter',  nbp_glo, index_g)
1260    CALL restput_p(rest_id, 'evap_bare_lim', nbp_glo, 1, 1, kjit,  evap_bare_lim, 'scatter',  nbp_glo, index_g)
1261    CALL restput_p(rest_id, 'resdist', nbp_glo, nstm, 1, kjit,  resdist, 'scatter',  nbp_glo, index_g) 
1262    CALL restput_p(rest_id, 'vegtot_old', nbp_glo, 1, 1, kjit,  vegtot_old, 'scatter',  nbp_glo, index_g)           
1263    CALL restput_p(rest_id, 'drysoil_frac', nbp_glo,   1, 1, kjit, drysoil_frac, 'scatter', nbp_glo, index_g)
1264    CALL restput_p(rest_id, 'humrel', nbp_glo,   nvm, 1, kjit,  humrel, 'scatter',  nbp_glo, index_g)
1265
1266    CALL restput_p(rest_id, 'tot_watveg_beg', nbp_glo,  1, 1, kjit,  tot_watveg_beg, 'scatter',  nbp_glo, index_g)
1267    CALL restput_p(rest_id, 'tot_watsoil_beg', nbp_glo, 1, 1, kjit,  tot_watsoil_beg, 'scatter',  nbp_glo, index_g)
1268    CALL restput_p(rest_id, 'snow_beg', nbp_glo,        1, 1, kjit,  snow_beg, 'scatter',  nbp_glo, index_g)
1269   
1270   
1271    ! Write variables for explictsnow module to restart file
1272    CALL explicitsnow_finalize ( kjit,     kjpindex, rest_id,    snowrho,   &
1273         snowtemp, snowdz,   snowheat,   snowgrain)
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(ks, nvan, avan, mcr, mcs, mcfc, mcw, njsc,&
1306       kjit, kjpindex, index, rest_id, veget_max, soiltile, &
1307       humrel,  vegstress, snow,       snow_age,   snow_nobio, snow_nobio_age, qsintveg, &
1308       snowdz,  snowgrain, snowrho,    snowtemp,   snowheat, &
1309       drysoil_frac, evap_bare_lim, evap_bare_lim_ns)
1310   
1311
1312    !! 0. Variable and parameter declaration
1313
1314    !! 0.1 Input variables
1315    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: njsc               !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
1316    INTEGER(i_std), INTENT (in)                         :: kjit               !! Time step number
1317    INTEGER(i_std), INTENT (in)                         :: kjpindex           !! Domain size
1318    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: index              !! Indeces of the points on the map
1319    INTEGER(i_std), INTENT (in)                         :: rest_id            !! _Restart_ file identifier
1320    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max          !! Carte de vegetation max
1321    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in)  :: soiltile           !! Fraction of each soil tile within vegtot (0-1, unitless)
1322   
1323    !! 0.2 Output variables
1324
1325    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: ks               !! Hydraulic conductivity at saturation (mm {-1})
1326    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: nvan             !! Van Genuchten coeficients n (unitless)
1327    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: avan             !! Van Genuchten coeficients a (mm-1})
1328    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
1329    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
1330    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
1331    REAL(r_std),DIMENSION (kjpindex), INTENT (in)         :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
1332
1333    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: humrel             !! Stress hydrique, relative humidity
1334    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: vegstress          !! Veg. moisture stress (only for vegetation growth)
1335    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: snow               !! Snow mass [Kg/m^2]
1336    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: snow_age           !! Snow age
1337    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out) :: snow_nobio       !! Snow on ice, lakes, ...
1338    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out) :: snow_nobio_age   !! Snow age on ice, lakes, ...
1339    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)    :: qsintveg         !! Water on vegetation due to interception
1340    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowdz           !! Snow depth
1341    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowgrain        !! Snow grain size
1342    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowheat         !! Snow heat content
1343    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowtemp         !! Snow temperature
1344    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowrho          !! Snow density
1345    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: drysoil_frac     !! function of litter wetness
1346    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: evap_bare_lim
1347    REAL(r_std),DIMENSION (kjpindex,nstm),INTENT(out)     :: evap_bare_lim_ns
1348
1349    !! 0.4 Local variables
1350
1351    INTEGER(i_std)                                     :: ier                   !! Error code
1352    INTEGER(i_std)                                     :: ji                    !! Index of land grid cells (1)
1353    INTEGER(i_std)                                     :: jv                    !! Index of PFTs (1)
1354    INTEGER(i_std)                                     :: jst                   !! Index of soil tiles (1)
1355    INTEGER(i_std)                                     :: jsl                   !! Index of soil layers (1)
1356    INTEGER(i_std)                                     :: jsc                   !! Index of soil texture (1)
1357    INTEGER(i_std), PARAMETER                          :: error_level = 3       !! Error level for consistency check
1358    !! Switch to 2 tu turn fatal errors into warnings
1359    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: free_drain_max        !! Temporary var for initialization of free_drain_coef
1360    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: zwt_default           !! Temporary variable for initialization of zwt_force
1361    LOGICAL                                            :: zforce                !! To test if we force the WT in any of the soiltiles
1362   
1363
1364!_ ================================================================================================================================
1365
1366    !! 1 Some initializations
1367    !
1368    !Config Key   = DO_PONDS
1369    !Config Desc  = Should we include ponds
1370    !Config Def   = n
1371    !Config If    =
1372    !Config Help  = This parameters allows the user to ask the model
1373    !Config         to take into account the ponds and return
1374    !Config         the water into the soil moisture. If this is
1375    !Config         activated, then there is no reinfiltration
1376    !Config         computed inside the hydrol module.
1377    !Config Units = [FLAG]
1378    !
1379    doponds = .FALSE.
1380    CALL getin_p('DO_PONDS', doponds)
1381
1382    !Config Key   = FROZ_FRAC_CORR
1383    !Config Desc  = Coefficient for the frozen fraction correction
1384    !Config Def   = 1.0
1385    !Config If    = OK_FREEZE
1386    !Config Help  =
1387    !Config Units = [-]
1388    froz_frac_corr = 1.0
1389    CALL getin_p("FROZ_FRAC_CORR", froz_frac_corr)
1390
1391    !Config Key   = MAX_FROZ_HYDRO
1392    !Config Desc  = Coefficient for the frozen fraction correction
1393    !Config Def   = 1.0
1394    !Config If    = OK_FREEZE
1395    !Config Help  =
1396    !Config Units = [-]
1397    max_froz_hydro = 1.0
1398    CALL getin_p("MAX_FROZ_HYDRO", max_froz_hydro)
1399
1400    !Config Key   = SMTOT_CORR
1401    !Config Desc  = Coefficient for the frozen fraction correction
1402    !Config Def   = 2.0
1403    !Config If    = OK_FREEZE
1404    !Config Help  =
1405    !Config Units = [-]
1406    smtot_corr = 2.0
1407    CALL getin_p("SMTOT_CORR", smtot_corr)
1408
1409    !Config Key   = DO_RSOIL
1410    !Config Desc  = Should we reduce soil evaporation with a soil resistance
1411    !Config Def   = n
1412    !Config If    =
1413    !Config Help  = This parameters allows the user to ask the model
1414    !Config         to calculate a soil resistance to reduce the soil evaporation
1415    !Config Units = [FLAG]
1416    !
1417    do_rsoil = .FALSE.
1418    CALL getin_p('DO_RSOIL', do_rsoil) 
1419
1420    !Config Key   = OK_DYNROOT
1421    !Config Desc  = Calculate dynamic root profile to optimize soil moisture usage 
1422    !Config Def   = n
1423    !Config If    =
1424    !Config Help  =
1425    !Config Units = [FLAG]
1426    ok_dynroot = .FALSE.
1427    CALL getin_p('OK_DYNROOT',ok_dynroot)
1428
1429    !! 2 make dynamic allocation with good dimension
1430
1431    !! 2.1 array allocation for soil texture
1432
1433    ALLOCATE (pcent(nscm),stat=ier)
1434    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable pcent','','')
1435   
1436    ALLOCATE (mc_awet(nscm),stat=ier)
1437    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_awet','','')
1438
1439    ALLOCATE (mc_adry(nscm),stat=ier)
1440    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_adry','','')
1441       
1442    !! 2.2 Soil texture parameters
1443         
1444    pcent(:) = pcent_usda(:) 
1445    mc_awet(:) = mc_awet_usda(:)
1446    mc_adry(:) = mc_adry_usda(:) 
1447
1448    !! 2.3 Read in the run.def the parameters values defined by the user
1449
1450    !Config Key   = WETNESS_TRANSPIR_MAX
1451    !Config Desc  = Soil moisture above which transpir is max, for each soil texture class
1452    !Config If    =
1453    !Config Def   = 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8
1454    !Config Help  = This parameter is independent from soil texture for
1455    !Config         the time being.
1456    !Config Units = [-]   
1457    CALL getin_p("WETNESS_TRANSPIR_MAX",pcent)
1458
1459    !! Check parameter value (correct range)
1460    IF ( ANY(pcent(:) <= zero) .OR. ANY(pcent(:) > 1.) ) THEN
1461       CALL ipslerr_p(error_level, "hydrol_init.", &
1462            &     "Wrong parameter value for WETNESS_TRANSPIR_MAX.", &
1463            &     "This parameter should be positive and less or equals than 1. ", &
1464            &     "Please, check parameter value in run.def. ")
1465    END IF
1466   
1467
1468    !Config Key   = VWC_MIN_FOR_WET_ALB
1469    !Config Desc  = Vol. wat. cont. above which albedo is cst
1470    !Config If    =
1471    !Config Def   = 0.25, 0.25, 0.25
1472    !Config Help  = This parameter is independent from soil texture for
1473    !Config         the time being.
1474    !Config Units = [m3/m3] 
1475    CALL getin_p("VWC_MIN_FOR_WET_ALB",mc_awet)
1476
1477    !! Check parameter value (correct range)
1478    IF ( ANY(mc_awet(:) < 0) ) THEN
1479       CALL ipslerr_p(error_level, "hydrol_init.", &
1480            &     "Wrong parameter value for VWC_MIN_FOR_WET_ALB.", &
1481            &     "This parameter should be positive. ", &
1482            &     "Please, check parameter value in run.def. ")
1483    END IF
1484
1485
1486    !Config Key   = VWC_MAX_FOR_DRY_ALB
1487    !Config Desc  = Vol. wat. cont. below which albedo is cst
1488    !Config If    =
1489    !Config Def   = 0.1, 0.1, 0.1
1490    !Config Help  = This parameter is independent from soil texture for
1491    !Config         the time being.
1492    !Config Units = [m3/m3]   
1493    CALL getin_p("VWC_MAX_FOR_DRY_ALB",mc_adry)
1494
1495    !! Check parameter value (correct range)
1496    IF ( ANY(mc_adry(:) < 0) .OR. ANY(mc_adry(:) > mc_awet(:)) ) THEN
1497       CALL ipslerr_p(error_level, "hydrol_init.", &
1498            &     "Wrong parameter value for VWC_MAX_FOR_DRY_ALB.", &
1499            &     "This parameter should be positive and not greater than VWC_MIN_FOR_WET_ALB.", &
1500            &     "Please, check parameter value in run.def. ")
1501    END IF
1502
1503
1504    !! 3 Other array allocation
1505
1506
1507    ALLOCATE (mask_veget(kjpindex,nvm),stat=ier)
1508    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_veget','','')
1509
1510    ALLOCATE (mask_soiltile(kjpindex,nstm),stat=ier)
1511    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_soiltile','','')
1512
1513    ALLOCATE (humrelv(kjpindex,nvm,nstm),stat=ier)
1514    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable humrelv','','')
1515
1516    ALLOCATE (vegstressv(kjpindex,nvm,nstm),stat=ier) 
1517    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegstressv','','')
1518
1519    ALLOCATE (us(kjpindex,nvm,nstm,nslm),stat=ier) 
1520    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable us','','')
1521
1522    ALLOCATE (precisol(kjpindex,nvm),stat=ier) 
1523    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable precisol','','')
1524
1525    ALLOCATE (throughfall(kjpindex,nvm),stat=ier) 
1526    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable throughfall','','')
1527
1528    ALLOCATE (precisol_ns(kjpindex,nstm),stat=ier) 
1529    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable precisol_nc','','')
1530
1531    ALLOCATE (free_drain_coef(kjpindex,nstm),stat=ier) 
1532    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable free_drain_coef','','')
1533
1534    ALLOCATE (zwt_force(kjpindex,nstm),stat=ier) 
1535    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zwt_force','','')
1536
1537    ALLOCATE (frac_bare_ns(kjpindex,nstm),stat=ier) 
1538    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable frac_bare_ns','','')
1539
1540    ALLOCATE (water2infilt(kjpindex,nstm),stat=ier)
1541    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable water2infilt','','')
1542
1543    ALLOCATE (ae_ns(kjpindex,nstm),stat=ier) 
1544    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ae_ns','','')
1545
1546    ALLOCATE (rootsink(kjpindex,nslm,nstm),stat=ier) 
1547    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable rootsink','','')
1548
1549    ALLOCATE (subsnowveg(kjpindex),stat=ier) 
1550    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsnowveg','','')
1551
1552    ALLOCATE (subsnownobio(kjpindex,nnobio),stat=ier) 
1553    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsnownobio','','')
1554
1555    ALLOCATE (icemelt(kjpindex),stat=ier) 
1556    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable icemelt','','')
1557
1558    ALLOCATE (subsinksoil(kjpindex),stat=ier) 
1559    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsinksoil','','')
1560
1561    ALLOCATE (mx_eau_var(kjpindex),stat=ier)
1562    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mx_eau_var','','')
1563
1564    ALLOCATE (vegtot(kjpindex),stat=ier) 
1565    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegtot','','')
1566
1567    ALLOCATE (vegtot_old(kjpindex),stat=ier) 
1568    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegtot_old','','')
1569
1570    ALLOCATE (resdist(kjpindex,nstm),stat=ier)
1571    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable resdist','','')
1572
1573    ALLOCATE (humtot(kjpindex),stat=ier)
1574    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable humtot','','')
1575
1576    ALLOCATE (resolv(kjpindex),stat=ier) 
1577    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable resolv','','')
1578
1579    ALLOCATE (k(kjpindex,nslm),stat=ier) 
1580    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable k','','')
1581
1582    ALLOCATE (kk_moy(kjpindex,nslm),stat=ier) 
1583    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kk_moy','','')
1584    kk_moy(:,:) = 276.48
1585   
1586    ALLOCATE (kk(kjpindex,nslm,nstm),stat=ier) 
1587    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kk','','')
1588    kk(:,:,:) = 276.48
1589   
1590    ALLOCATE (avan_mod_tab(nslm,kjpindex),stat=ier) 
1591    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable avan_mod_tab','','')
1592   
1593    ALLOCATE (nvan_mod_tab(nslm,kjpindex),stat=ier) 
1594    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nvan_mod_tab','','')
1595
1596    ALLOCATE (a(kjpindex,nslm),stat=ier) 
1597    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable a','','')
1598
1599    ALLOCATE (b(kjpindex,nslm),stat=ier)
1600    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable b','','')
1601
1602    ALLOCATE (d(kjpindex,nslm),stat=ier)
1603    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable d','','')
1604
1605    ALLOCATE (e(kjpindex,nslm),stat=ier) 
1606    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable e','','')
1607
1608    ALLOCATE (f(kjpindex,nslm),stat=ier) 
1609    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable f','','')
1610
1611    ALLOCATE (g1(kjpindex,nslm),stat=ier) 
1612    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable g1','','')
1613
1614    ALLOCATE (ep(kjpindex,nslm),stat=ier)
1615    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ep','','')
1616
1617    ALLOCATE (fp(kjpindex,nslm),stat=ier)
1618    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fp','','')
1619
1620    ALLOCATE (gp(kjpindex,nslm),stat=ier)
1621    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable gp','','')
1622
1623    ALLOCATE (rhs(kjpindex,nslm),stat=ier)
1624    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable rhs','','')
1625
1626    ALLOCATE (srhs(kjpindex,nslm),stat=ier)
1627    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable srhs','','')
1628
1629    ALLOCATE (tmc(kjpindex,nstm),stat=ier)
1630    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc','','')
1631
1632    ALLOCATE (tmcs(kjpindex,nstm),stat=ier)
1633    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcs','','')
1634
1635    ALLOCATE (tmcr(kjpindex,nstm),stat=ier)
1636    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcr','','')
1637
1638    ALLOCATE (tmcfc(kjpindex,nstm),stat=ier)
1639    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcfc','','')
1640
1641    ALLOCATE (tmcw(kjpindex,nstm),stat=ier)
1642    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcw','','')
1643
1644    ALLOCATE (tmc_litter(kjpindex,nstm),stat=ier)
1645    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter','','')
1646
1647    ALLOCATE (tmc_litt_mea(kjpindex),stat=ier)
1648    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_mea','','')
1649
1650    ALLOCATE (tmc_litter_res(kjpindex,nstm),stat=ier)
1651    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_res','','')
1652
1653    ALLOCATE (tmc_litter_wilt(kjpindex,nstm),stat=ier)
1654    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_wilt','','')
1655
1656    ALLOCATE (tmc_litter_field(kjpindex,nstm),stat=ier)
1657    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_field','','')
1658
1659    ALLOCATE (tmc_litter_sat(kjpindex,nstm),stat=ier)
1660    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_sat','','')
1661
1662    ALLOCATE (tmc_litter_awet(kjpindex,nstm),stat=ier)
1663    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_awet','','')
1664
1665    ALLOCATE (tmc_litter_adry(kjpindex,nstm),stat=ier)
1666    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_adry','','')
1667
1668    ALLOCATE (tmc_litt_wet_mea(kjpindex),stat=ier)
1669    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_wet_mea','','')
1670
1671    ALLOCATE (tmc_litt_dry_mea(kjpindex),stat=ier)
1672    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_dry_mea','','')
1673
1674    ALLOCATE (v1(kjpindex,nstm),stat=ier)
1675    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable v1','','')
1676
1677    ALLOCATE (ru_ns(kjpindex,nstm),stat=ier)
1678    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ru_ns','','')
1679    ru_ns(:,:) = zero
1680
1681    ALLOCATE (dr_ns(kjpindex,nstm),stat=ier)
1682    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dr_ns','','')
1683    dr_ns(:,:) = zero
1684
1685    ALLOCATE (tr_ns(kjpindex,nstm),stat=ier)
1686    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tr_ns','','')
1687
1688    ALLOCATE (vegetmax_soil(kjpindex,nvm,nstm),stat=ier)
1689    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegetmax_soil','','')
1690
1691    ALLOCATE (mc(kjpindex,nslm,nstm),stat=ier)
1692    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc','','')
1693
1694
1695    ! Variables for nudging of soil moisture
1696    IF (ok_nudge_mc) THEN
1697       ALLOCATE (mc_read_prev(kjpindex,nslm,nstm),stat=ier)
1698       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_read_prev','','')
1699       ALLOCATE (mc_read_next(kjpindex,nslm,nstm),stat=ier)
1700       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_read_next','','')
1701       ALLOCATE (mc_read_current(kjpindex,nslm,nstm),stat=ier)
1702       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_read_current','','')
1703       ALLOCATE (mask_mc_interp(kjpindex,nslm,nstm),stat=ier)
1704       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_mc_interp','','')
1705       ALLOCATE (tmc_aux(kjpindex,nstm),stat=ier)
1706       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_aux','','')
1707    END IF
1708
1709    ! Variables for nudging of snow variables
1710    IF (ok_nudge_snow) THEN
1711       ALLOCATE (snowdz_read_prev(kjpindex,nsnow),stat=ier)
1712       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowdz_read_prev','','')
1713       ALLOCATE (snowdz_read_next(kjpindex,nsnow),stat=ier)
1714       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowdz_read_next','','')
1715       
1716       ALLOCATE (snowrho_read_prev(kjpindex,nsnow),stat=ier)
1717       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowrho_read_prev','','')
1718       ALLOCATE (snowrho_read_next(kjpindex,nsnow),stat=ier)
1719       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowrho_read_next','','')
1720       
1721       ALLOCATE (snowtemp_read_prev(kjpindex,nsnow),stat=ier)
1722       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowtemp_read_prev','','')
1723       ALLOCATE (snowtemp_read_next(kjpindex,nsnow),stat=ier)
1724       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snowtemp_read_next','','')
1725       
1726       ALLOCATE (mask_snow_interp(kjpindex,nsnow),stat=ier)
1727       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_snow_interp','','')
1728    END IF
1729
1730    ALLOCATE (mcl(kjpindex, nslm, nstm),stat=ier)
1731    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcl','','')
1732
1733    IF (ok_freeze_cwrr) THEN
1734       ALLOCATE (profil_froz_hydro(kjpindex, nslm),stat=ier)
1735       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydrol','','')
1736       profil_froz_hydro(:,:) = zero
1737    ENDIF
1738   
1739    ALLOCATE (profil_froz_hydro_ns(kjpindex, nslm, nstm),stat=ier)
1740    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydro_ns','','')
1741    profil_froz_hydro_ns(:,:,:) = zero
1742   
1743    ALLOCATE (soilmoist(kjpindex,nslm),stat=ier)
1744    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soilmoist','','')
1745
1746    ALLOCATE (soilmoist_liquid(kjpindex,nslm),stat=ier)
1747    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soilmoist_liquid','','')
1748
1749    ALLOCATE (soil_wet_ns(kjpindex,nslm,nstm),stat=ier)
1750    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soil_wet_ns','','')
1751
1752    ALLOCATE (soil_wet_litter(kjpindex,nstm),stat=ier)
1753    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soil_wet_litter','','')
1754
1755    ALLOCATE (qflux_ns(kjpindex,nslm,nstm),stat=ier) 
1756    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable qflux_ns','','')
1757
1758    ALLOCATE (check_top_ns(kjpindex,nstm),stat=ier) 
1759    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable check_top_ns','','')
1760
1761    ALLOCATE (tmat(kjpindex,nslm,3),stat=ier)
1762    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmat','','')
1763
1764    ALLOCATE (stmat(kjpindex,nslm,3),stat=ier)
1765    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable stmat','','')
1766
1767    ALLOCATE (nroot(kjpindex,nvm, nslm),stat=ier)
1768    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nroot','','')
1769
1770    ALLOCATE (kfact_root(kjpindex, nslm, nstm), stat=ier)
1771    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kfact_root','','')
1772
1773    ALLOCATE (kfact(nslm, kjpindex),stat=ier)
1774    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kfact','','')
1775
1776    ALLOCATE (zz(nslm),stat=ier)
1777    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zz','','')
1778
1779    ALLOCATE (dz(nslm),stat=ier)
1780    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dz','','')
1781   
1782    ALLOCATE (dh(nslm),stat=ier)
1783    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dh','','')
1784
1785    ALLOCATE (mc_lin(imin:imax, kjpindex),stat=ier)
1786    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_lin','','')
1787
1788    ALLOCATE (k_lin(imin:imax, nslm, kjpindex),stat=ier)
1789    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable k_lin','','')
1790
1791    ALLOCATE (d_lin(imin:imax, nslm, kjpindex),stat=ier)
1792    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable d_lin','','')
1793
1794    ALLOCATE (a_lin(imin:imax, nslm, kjpindex),stat=ier)
1795    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable a_lin','','')
1796
1797    ALLOCATE (b_lin(imin:imax, nslm, kjpindex),stat=ier)
1798    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable b_lin','','')
1799
1800    ALLOCATE (undermcr(kjpindex),stat=ier)
1801    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable undermcr','','')
1802
1803    ALLOCATE (tot_watveg_beg(kjpindex),stat=ier)
1804    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watveg_beg','','')
1805   
1806    ALLOCATE (tot_watveg_end(kjpindex),stat=ier)
1807    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watvag_end','','')
1808   
1809    ALLOCATE (tot_watsoil_beg(kjpindex),stat=ier)
1810    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watsoil_beg','','')
1811   
1812    ALLOCATE (tot_watsoil_end(kjpindex),stat=ier)
1813    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watsoil_end','','')
1814   
1815    ALLOCATE (delsoilmoist(kjpindex),stat=ier)
1816    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delsoilmoist','','')
1817   
1818    ALLOCATE (delintercept(kjpindex),stat=ier)
1819    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delintercept','','')
1820   
1821    ALLOCATE (delswe(kjpindex),stat=ier)
1822    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delswe','','')
1823   
1824    ALLOCATE (snow_beg(kjpindex),stat=ier)
1825    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snow_beg','','')
1826   
1827    ALLOCATE (snow_end(kjpindex),stat=ier)
1828    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snow_end','','')
1829   
1830    !! 4 Open restart input file and read data for HYDROLOGIC process
1831       IF (printlev>=3) WRITE (numout,*) ' we have to read a restart file for HYDROLOGIC variables'
1832
1833       IF (is_root_prc) CALL ioconf_setatt_p('UNITS', '-')
1834       !
1835       DO jst=1,nstm
1836          ! var_name= "mc_1" ... "mc_3"
1837           WRITE (var_name,"('moistc_',I1)") jst
1838           IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME',var_name)
1839           CALL restget_p (rest_id, var_name, nbp_glo, nslm , 1, kjit, .TRUE., mc(:,:,jst), "gather", nbp_glo, index_g)
1840       END DO
1841
1842       IF (ok_nudge_mc) THEN
1843          DO jst=1,nstm
1844             WRITE (var_name,"('mc_read_next_',I1)") jst
1845             IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME','Soil moisture read from nudging file')
1846             CALL restget_p (rest_id, var_name, nbp_glo, nslm , 1, kjit, .TRUE., mc_read_next(:,:,jst), &
1847                  "gather", nbp_glo, index_g)
1848          END DO
1849       END IF
1850
1851       IF (ok_nudge_snow) THEN
1852          IF (is_root_prc) THEN
1853             CALL ioconf_setatt_p('UNITS', 'm')
1854             CALL ioconf_setatt_p('LONG_NAME','Snow layer thickness read from nudging file')
1855          ENDIF
1856          CALL restget_p (rest_id, 'snowdz_read_next', nbp_glo, nsnow, 1, kjit, .TRUE., snowdz_read_next, &
1857               "gather", nbp_glo, index_g)
1858
1859          IF (is_root_prc) THEN
1860             CALL ioconf_setatt_p('UNITS', 'kg/m^3')
1861             CALL ioconf_setatt_p('LONG_NAME','Snow density profile read from nudging file')
1862          ENDIF
1863          CALL restget_p (rest_id, 'snowrho_read_next', nbp_glo, nsnow, 1, kjit, .TRUE., snowrho_read_next, &
1864               "gather", nbp_glo, index_g)
1865
1866          IF (is_root_prc) THEN
1867             CALL ioconf_setatt_p('UNITS', 'K')
1868             CALL ioconf_setatt_p('LONG_NAME','Snow temperature read from nudging file')
1869          ENDIF
1870          CALL restget_p (rest_id, 'snowtemp_read_next', nbp_glo, nsnow, 1, kjit, .TRUE., snowtemp_read_next, &
1871               "gather", nbp_glo, index_g)
1872       END IF
1873     
1874       DO jst=1,nstm
1875          ! var_name= "mcl_1" ... "mcl_3"
1876           WRITE (var_name,"('moistcl_',I1)") jst
1877           IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME',var_name)
1878           CALL restget_p (rest_id, var_name, nbp_glo, nslm , 1, kjit, .TRUE., mcl(:,:,jst), "gather", nbp_glo, index_g)
1879       END DO
1880
1881       IF (is_root_prc) CALL ioconf_setatt_p('UNITS', '-')
1882       DO jst=1,nstm
1883          DO jsl=1,nslm
1884             ! var_name= "us_1_01" ... "us_3_11"
1885             WRITE (var_name,"('us_',i1,'_',i2.2)") jst,jsl
1886             IF (is_root_prc) CALL ioconf_setatt_p('LONG_NAME',var_name)
1887             CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., us(:,:,jst,jsl), "gather", nbp_glo, index_g)
1888          END DO
1889       END DO
1890       !
1891       var_name= 'free_drain_coef'
1892       IF (is_root_prc) THEN
1893          CALL ioconf_setatt_p('UNITS', '-')
1894          CALL ioconf_setatt_p('LONG_NAME','Coefficient for free drainage at bottom of soil')
1895       ENDIF
1896       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., free_drain_coef, "gather", nbp_glo, index_g)
1897       !
1898       var_name= 'zwt_force'
1899       IF (is_root_prc) THEN
1900          CALL ioconf_setatt_p('UNITS', 'm')
1901          CALL ioconf_setatt_p('LONG_NAME','Prescribed water table depth')
1902       ENDIF
1903       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., zwt_force, "gather", nbp_glo, index_g)
1904       !
1905       var_name= 'water2infilt'
1906       IF (is_root_prc) THEN
1907          CALL ioconf_setatt_p('UNITS', '-')
1908          CALL ioconf_setatt_p('LONG_NAME','Remaining water to be infiltrated on top of the soil')
1909       ENDIF
1910       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., water2infilt, "gather", nbp_glo, index_g)
1911       !
1912       var_name= 'ae_ns'
1913       IF (is_root_prc) THEN
1914          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
1915          CALL ioconf_setatt_p('LONG_NAME','Bare soil evap on each soil type')
1916       ENDIF
1917       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., ae_ns, "gather", nbp_glo, index_g)
1918       !
1919       var_name= 'snow'       
1920       IF (is_root_prc) THEN
1921          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
1922          CALL ioconf_setatt_p('LONG_NAME','Snow mass')
1923       ENDIF
1924       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., snow, "gather", nbp_glo, index_g)
1925       !
1926       var_name= 'snow_age'
1927       IF (is_root_prc) THEN
1928          CALL ioconf_setatt_p('UNITS', 'd')
1929          CALL ioconf_setatt_p('LONG_NAME','Snow age')
1930       ENDIF
1931       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., snow_age, "gather", nbp_glo, index_g)
1932       !
1933       var_name= 'snow_nobio'
1934       IF (is_root_prc) THEN
1935          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
1936          CALL ioconf_setatt_p('LONG_NAME','Snow on other surface types')
1937       ENDIF
1938       CALL restget_p (rest_id, var_name, nbp_glo, nnobio  , 1, kjit, .TRUE., snow_nobio, "gather", nbp_glo, index_g)
1939       !
1940       var_name= 'snow_nobio_age'
1941       IF (is_root_prc) THEN
1942          CALL ioconf_setatt_p('UNITS', 'd')
1943          CALL ioconf_setatt_p('LONG_NAME','Snow age on other surface types')
1944       ENDIF
1945       CALL restget_p (rest_id, var_name, nbp_glo, nnobio  , 1, kjit, .TRUE., snow_nobio_age, "gather", nbp_glo, index_g)
1946       !
1947       var_name= 'qsintveg'
1948       IF (is_root_prc) THEN
1949          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
1950          CALL ioconf_setatt_p('LONG_NAME','Intercepted moisture')
1951       ENDIF
1952       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., qsintveg, "gather", nbp_glo, index_g)
1953
1954       var_name= 'evap_bare_lim_ns'
1955       IF (is_root_prc) THEN
1956          CALL ioconf_setatt_p('UNITS', '?')
1957          CALL ioconf_setatt_p('LONG_NAME','?')
1958       ENDIF
1959       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., evap_bare_lim_ns, "gather", nbp_glo, index_g)
1960       CALL setvar_p (evap_bare_lim_ns, val_exp, 'NO_KEYWORD', 0.0)
1961
1962       var_name= 'resdist'
1963       IF (is_root_prc) THEN
1964          CALL ioconf_setatt_p('UNITS', '-')
1965          CALL ioconf_setatt_p('LONG_NAME','soiltile values from previous time-step')
1966       ENDIF
1967       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., resdist, "gather", nbp_glo, index_g)
1968
1969       var_name= 'vegtot_old'
1970       IF (is_root_prc) THEN
1971          CALL ioconf_setatt_p('UNITS', '-')
1972          CALL ioconf_setatt_p('LONG_NAME','vegtot from previous time-step')
1973       ENDIF
1974       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., vegtot_old, "gather", nbp_glo, index_g)       
1975       
1976       ! Read drysoil_frac. It will be initalized later in hydrol_var_init if the varaible is not find in restart file.
1977       IF (is_root_prc) THEN
1978          CALL ioconf_setatt_p('UNITS', '')
1979          CALL ioconf_setatt_p('LONG_NAME','Function of litter wetness')
1980       ENDIF
1981       CALL restget_p (rest_id, 'drysoil_frac', nbp_glo, 1  , 1, kjit, .TRUE., drysoil_frac, "gather", nbp_glo, index_g)
1982
1983
1984    !! 5 get restart values if none were found in the restart file
1985       !
1986       !Config Key   = HYDROL_MOISTURE_CONTENT
1987       !Config Desc  = Soil moisture on each soil tile and levels
1988       !Config If    =
1989       !Config Def   = 0.3
1990       !Config Help  = The initial value of mc if its value is not found
1991       !Config         in the restart file. This should only be used if the model is
1992       !Config         started without a restart file.
1993       !Config Units = [m3/m3]
1994       !
1995       CALL setvar_p (mc, val_exp, 'HYDROL_MOISTURE_CONTENT', 0.3_r_std)
1996
1997       ! Initialize mcl as mc if it is not found in the restart file
1998       IF ( ALL(mcl(:,:,:)==val_exp) ) THEN
1999          mcl(:,:,:) = mc(:,:,:)
2000       END IF
2001
2002
2003       
2004       !Config Key   = US_INIT
2005       !Config Desc  = US_NVM_NSTM_NSLM
2006       !Config If    =
2007       !Config Def   = 0.0
2008       !Config Help  = The initial value of us (relative moisture) if its value is not found
2009       !Config         in the restart file. This should only be used if the model is
2010       !Config         started without a restart file.
2011       !Config Units = [-]
2012       !
2013       DO jsl=1,nslm
2014          CALL setvar_p (us(:,:,:,jsl), val_exp, 'US_INIT', zero)
2015       ENDDO
2016       !
2017       !Config Key   = ZWT_FORCE
2018       !Config Desc  = Prescribed water depth, dimension nstm
2019       !Config If    =
2020       !Config Def   = undef undef undef
2021       !Config Help  = The initial value of zwt_force if its value is not found
2022       !Config         in the restart file. undef corresponds to a case whith no forced WT.
2023       !Config         This should only be used if the model is started without a restart file.
2024       !Config Units = [m]
2025       
2026       ALLOCATE (zwt_default(nstm),stat=ier)
2027       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zwt_default','','')
2028       zwt_default(:) = undef_sechiba
2029       CALL setvar_p (zwt_force, val_exp, 'ZWT_FORCE', zwt_default )
2030
2031       zforce = .FALSE.
2032       DO jst=1,nstm
2033          IF (zwt_force(1,jst) <= zmaxh) zforce = .TRUE. ! AD16*** check if OK with vertical_soil
2034       ENDDO
2035       !
2036       !Config Key   = FREE_DRAIN_COEF
2037       !Config Desc  = Coefficient for free drainage at bottom, dimension nstm
2038       !Config If    =
2039       !Config Def   = 1.0 1.0 1.0
2040       !Config Help  = The initial value of free drainage coefficient if its value is not found
2041       !Config         in the restart file. This should only be used if the model is
2042       !Config         started without a restart file.
2043       !Config Units = [-]
2044             
2045       ALLOCATE (free_drain_max(nstm),stat=ier)
2046       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable free_drain_max','','')
2047       free_drain_max(:)=1.0
2048
2049       CALL setvar_p (free_drain_coef, val_exp, 'FREE_DRAIN_COEF', free_drain_max)
2050       IF (printlev>=2) WRITE (numout,*) ' hydrol_init => free_drain_coef = ',free_drain_coef(1,:)
2051       DEALLOCATE(free_drain_max)
2052
2053       !
2054       !Config Key   = WATER_TO_INFILT
2055       !Config Desc  = Water to be infiltrated on top of the soil
2056       !Config If    =
2057       !Config Def   = 0.0
2058       !Config Help  = The initial value of free drainage if its value is not found
2059       !Config         in the restart file. This should only be used if the model is
2060       !Config         started without a restart file.
2061       !Config Units = [mm]
2062       !
2063       CALL setvar_p (water2infilt, val_exp, 'WATER_TO_INFILT', zero)
2064       !
2065       !Config Key   = EVAPNU_SOIL
2066       !Config Desc  = Bare soil evap on each soil if not found in restart
2067       !Config If    =
2068       !Config Def   = 0.0
2069       !Config Help  = The initial value of bare soils evap if its value is not found
2070       !Config         in the restart file. This should only be used if the model is
2071       !Config         started without a restart file.
2072       !Config Units = [mm]
2073       !
2074       CALL setvar_p (ae_ns, val_exp, 'EVAPNU_SOIL', zero)
2075       !
2076       !Config Key  = HYDROL_SNOW
2077       !Config Desc  = Initial snow mass if not found in restart
2078       !Config If    = OK_SECHIBA
2079       !Config Def   = 0.0
2080       !Config Help  = The initial value of snow mass if its value is not found
2081       !Config         in the restart file. This should only be used if the model is
2082       !Config         started without a restart file.
2083       !Config Units =
2084       !
2085       CALL setvar_p (snow, val_exp, 'HYDROL_SNOW', zero)
2086       !
2087       !Config Key   = HYDROL_SNOWAGE
2088       !Config Desc  = Initial snow age if not found in restart
2089       !Config If    = OK_SECHIBA
2090       !Config Def   = 0.0
2091       !Config Help  = The initial value of snow age if its value is not found
2092       !Config         in the restart file. This should only be used if the model is
2093       !Config         started without a restart file.
2094       !Config Units = ***
2095       !
2096       CALL setvar_p (snow_age, val_exp, 'HYDROL_SNOWAGE', zero)
2097       !
2098       !Config Key   = HYDROL_SNOW_NOBIO
2099       !Config Desc  = Initial snow amount on ice, lakes, etc. if not found in restart
2100       !Config If    = OK_SECHIBA
2101       !Config Def   = 0.0
2102       !Config Help  = The initial value of snow if its value is not found
2103       !Config         in the restart file. This should only be used if the model is
2104       !Config         started without a restart file.
2105       !Config Units = [mm]
2106       !
2107       CALL setvar_p (snow_nobio, val_exp, 'HYDROL_SNOW_NOBIO', zero)
2108       !
2109       !Config Key   = HYDROL_SNOW_NOBIO_AGE
2110       !Config Desc  = Initial snow age on ice, lakes, etc. if not found in restart
2111       !Config If    = OK_SECHIBA
2112       !Config Def   = 0.0
2113       !Config Help  = The initial value of snow age if its value is not found
2114       !Config         in the restart file. This should only be used if the model is
2115       !Config         started without a restart file.
2116       !Config Units = ***
2117       !
2118       CALL setvar_p (snow_nobio_age, val_exp, 'HYDROL_SNOW_NOBIO_AGE', zero)
2119       !
2120       !Config Key   = HYDROL_QSV
2121       !Config Desc  = Initial water on canopy if not found in restart
2122       !Config If    = OK_SECHIBA
2123       !Config Def   = 0.0
2124       !Config Help  = The initial value of moisture on canopy if its value
2125       !Config         is not found in the restart file. This should only be used if
2126       !Config         the model is started without a restart file.
2127       !Config Units = [mm]
2128       !
2129       CALL setvar_p (qsintveg, val_exp, 'HYDROL_QSV', zero)
2130
2131    !! 6 Vegetation array     
2132       !
2133       ! If resdist is not in restart file, initialize with soiltile
2134       IF ( MINVAL(resdist) .EQ.  MAXVAL(resdist) .AND. MINVAL(resdist) .EQ. val_exp) THEN
2135          resdist(:,:) = soiltile(:,:)
2136       ENDIF
2137       
2138       !
2139       !  Remember that it is only frac_nobio + SUM(veget_max(,:)) that is equal to 1. Thus we need vegtot
2140       !
2141       IF ( ALL(vegtot_old(:) == val_exp) ) THEN
2142          ! vegtot_old was not found in restart file
2143          DO ji = 1, kjpindex
2144             vegtot_old(ji) = SUM(veget_max(ji,:))
2145          ENDDO
2146       ENDIF
2147       
2148       ! In the initialization phase, vegtot must take the value from previous time-step.
2149       ! This is because hydrol_main is done before veget_max is updated in the end of the time step.
2150       vegtot(:) = vegtot_old(:)
2151       
2152       !
2153       !
2154       ! compute the masks for veget
2155
2156       mask_veget(:,:) = 0
2157       mask_soiltile(:,:) = 0
2158
2159       DO jst=1,nstm
2160          DO ji = 1, kjpindex
2161             IF(soiltile(ji,jst) .GT. min_sechiba) THEN
2162                mask_soiltile(ji,jst) = 1
2163             ENDIF
2164          END DO
2165       ENDDO
2166         
2167       DO jv = 1, nvm
2168          DO ji = 1, kjpindex
2169             IF(veget_max(ji,jv) .GT. min_sechiba) THEN
2170                mask_veget(ji,jv) = 1
2171             ENDIF
2172          END DO
2173       END DO
2174
2175       humrelv(:,:,:) = SUM(us,dim=4)
2176
2177         
2178       !! 7a. Set vegstress
2179     
2180       var_name= 'vegstress'
2181       IF (is_root_prc) THEN
2182          CALL ioconf_setatt_p('UNITS', '-')
2183          CALL ioconf_setatt_p('LONG_NAME','Vegetation growth moisture stress')
2184       ENDIF
2185       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., vegstress, "gather", nbp_glo, index_g)
2186
2187       vegstressv(:,:,:) = humrelv(:,:,:)
2188       ! Calculate vegstress if it is not found in restart file
2189       IF (ALL(vegstress(:,:)==val_exp)) THEN
2190          DO jv=1,nvm
2191             DO ji=1,kjpindex
2192                vegstress(ji,jv)=vegstress(ji,jv) + vegstressv(ji,jv,pref_soil_veg(jv))
2193             END DO
2194          END DO
2195       END IF
2196       !! 7b. Set humrel   
2197       ! Read humrel from restart file
2198       var_name= 'humrel'
2199       IF (is_root_prc) THEN
2200          CALL ioconf_setatt_p('UNITS', '')
2201          CALL ioconf_setatt_p('LONG_NAME','Relative humidity')
2202       ENDIF
2203       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., humrel, "gather", nbp_glo, index_g)
2204
2205       ! Calculate humrel if it is not found in restart file
2206       IF (ALL(humrel(:,:)==val_exp)) THEN
2207          ! set humrel from humrelv, assuming equi-repartition for the first time step
2208          humrel(:,:) = zero
2209          DO jv=1,nvm
2210             DO ji=1,kjpindex
2211                humrel(ji,jv)=humrel(ji,jv) + humrelv(ji,jv,pref_soil_veg(jv))     
2212             END DO
2213          END DO
2214       END IF
2215
2216       ! Read evap_bare_lim from restart file
2217       var_name= 'evap_bare_lim'
2218       IF (is_root_prc) THEN
2219          CALL ioconf_setatt_p('UNITS', '')
2220          CALL ioconf_setatt_p('LONG_NAME','Limitation factor for bare soil evaporation')
2221       ENDIF
2222       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., evap_bare_lim, "gather", nbp_glo, index_g)
2223
2224       ! Calculate evap_bare_lim if it was not found in the restart file.
2225       IF ( ALL(evap_bare_lim(:) == val_exp) ) THEN
2226          DO ji = 1, kjpindex
2227             evap_bare_lim(ji) =  SUM(evap_bare_lim_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
2228          ENDDO
2229       END IF
2230
2231
2232    ! Read from restart file       
2233    ! The variables tot_watsoil_beg, tot_watsoil_beg and snwo_beg will be initialized in the end of
2234    ! hydrol_initialize if they were not found in the restart file.
2235       
2236    var_name= 'tot_watveg_beg'
2237    IF (is_root_prc) THEN
2238       CALL ioconf_setatt_p('UNITS', '?')
2239       CALL ioconf_setatt_p('LONG_NAME','?')
2240    ENDIF
2241    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., tot_watveg_beg, "gather", nbp_glo, index_g)
2242   
2243    var_name= 'tot_watsoil_beg'
2244    IF (is_root_prc) THEN
2245       CALL ioconf_setatt_p('UNITS', '?')
2246       CALL ioconf_setatt_p('LONG_NAME','?')
2247    ENDIF
2248    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., tot_watsoil_beg, "gather", nbp_glo, index_g)
2249   
2250    var_name= 'snow_beg'
2251    IF (is_root_prc) THEN
2252       CALL ioconf_setatt_p('UNITS', '?')
2253       CALL ioconf_setatt_p('LONG_NAME','?')
2254    ENDIF
2255    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., snow_beg, "gather", nbp_glo, index_g)
2256       
2257 
2258    ! Initialize variables for explictsnow module by reading restart file
2259    CALL explicitsnow_initialize( kjit,     kjpindex, rest_id,    snowrho,   &
2260         snowtemp, snowdz,   snowheat,   snowgrain)
2261
2262
2263    ! Initialize soil moisture for nudging if not found in restart file
2264    IF (ok_nudge_mc) THEN
2265       IF ( ALL(mc_read_next(:,:,:)==val_exp) ) mc_read_next(:,:,:) = mc(:,:,:)
2266    END IF
2267   
2268    ! Initialize snow variables for nudging if not found in restart file
2269    IF (ok_nudge_snow) THEN
2270       IF ( ALL(snowdz_read_next(:,:)==val_exp) ) snowdz_read_next(:,:) = snowdz(:,:)
2271       IF ( ALL(snowrho_read_next(:,:)==val_exp) ) snowrho_read_next(:,:) = snowrho(:,:)
2272       IF ( ALL(snowtemp_read_next(:,:)==val_exp) ) snowtemp_read_next(:,:) = snowtemp(:,:)
2273    END IF
2274   
2275   
2276    IF (printlev>=3) WRITE (numout,*) ' hydrol_init done '
2277   
2278  END SUBROUTINE hydrol_init
2279
2280
2281!! ================================================================================================================================
2282!! SUBROUTINE   : hydrol_clear
2283!!
2284!>\BRIEF        Deallocate arrays
2285!!
2286!_ ================================================================================================================================
2287!_ hydrol_clear
2288
2289  SUBROUTINE hydrol_clear()
2290
2291    ! Allocation for soiltile related parameters
2292   
2293    IF ( ALLOCATED (pcent)) DEALLOCATE (pcent)
2294    IF ( ALLOCATED (mc_awet)) DEALLOCATE (mc_awet)
2295    IF ( ALLOCATED (mc_adry)) DEALLOCATE (mc_adry)
2296    ! Other arrays
2297    IF (ALLOCATED (mask_veget)) DEALLOCATE (mask_veget)
2298    IF (ALLOCATED (mask_soiltile)) DEALLOCATE (mask_soiltile)
2299    IF (ALLOCATED (humrelv)) DEALLOCATE (humrelv)
2300    IF (ALLOCATED (vegstressv)) DEALLOCATE (vegstressv)
2301    IF (ALLOCATED (us)) DEALLOCATE (us)
2302    IF (ALLOCATED  (precisol)) DEALLOCATE (precisol)
2303    IF (ALLOCATED  (throughfall)) DEALLOCATE (throughfall)
2304    IF (ALLOCATED  (precisol_ns)) DEALLOCATE (precisol_ns)
2305    IF (ALLOCATED  (free_drain_coef)) DEALLOCATE (free_drain_coef)
2306    IF (ALLOCATED  (frac_bare_ns)) DEALLOCATE (frac_bare_ns)
2307    IF (ALLOCATED  (water2infilt)) DEALLOCATE (water2infilt)
2308    IF (ALLOCATED  (ae_ns)) DEALLOCATE (ae_ns)
2309    IF (ALLOCATED  (rootsink)) DEALLOCATE (rootsink)
2310    IF (ALLOCATED  (subsnowveg)) DEALLOCATE (subsnowveg)
2311    IF (ALLOCATED  (subsnownobio)) DEALLOCATE (subsnownobio)
2312    IF (ALLOCATED  (icemelt)) DEALLOCATE (icemelt)
2313    IF (ALLOCATED  (subsinksoil)) DEALLOCATE (subsinksoil)
2314    IF (ALLOCATED  (mx_eau_var)) DEALLOCATE (mx_eau_var)
2315    IF (ALLOCATED  (vegtot)) DEALLOCATE (vegtot)
2316    IF (ALLOCATED  (vegtot_old)) DEALLOCATE (vegtot_old)
2317    IF (ALLOCATED  (resdist)) DEALLOCATE (resdist)
2318    IF (ALLOCATED  (tot_watveg_beg)) DEALLOCATE (tot_watveg_beg)
2319    IF (ALLOCATED  (tot_watveg_end)) DEALLOCATE (tot_watveg_end)
2320    IF (ALLOCATED  (tot_watsoil_beg)) DEALLOCATE (tot_watsoil_beg)
2321    IF (ALLOCATED  (tot_watsoil_end)) DEALLOCATE (tot_watsoil_end)
2322    IF (ALLOCATED  (delsoilmoist)) DEALLOCATE (delsoilmoist)
2323    IF (ALLOCATED  (delintercept)) DEALLOCATE (delintercept)
2324    IF (ALLOCATED  (snow_beg)) DEALLOCATE (snow_beg)
2325    IF (ALLOCATED  (snow_end)) DEALLOCATE (snow_end)
2326    IF (ALLOCATED  (delswe)) DEALLOCATE (delswe)
2327    IF (ALLOCATED  (undermcr)) DEALLOCATE (undermcr)
2328    IF (ALLOCATED  (v1)) DEALLOCATE (v1)
2329    IF (ALLOCATED  (humtot)) DEALLOCATE (humtot)
2330    IF (ALLOCATED  (resolv)) DEALLOCATE (resolv)
2331    IF (ALLOCATED  (k)) DEALLOCATE (k)
2332    IF (ALLOCATED  (kk)) DEALLOCATE (kk)
2333    IF (ALLOCATED  (kk_moy)) DEALLOCATE (kk_moy)
2334    IF (ALLOCATED  (avan_mod_tab)) DEALLOCATE (avan_mod_tab)
2335    IF (ALLOCATED  (nvan_mod_tab)) DEALLOCATE (nvan_mod_tab)
2336    IF (ALLOCATED  (a)) DEALLOCATE (a)
2337    IF (ALLOCATED  (b)) DEALLOCATE (b)
2338    IF (ALLOCATED  (d)) DEALLOCATE (d)
2339    IF (ALLOCATED  (e)) DEALLOCATE (e)
2340    IF (ALLOCATED  (f)) DEALLOCATE (f)
2341    IF (ALLOCATED  (g1)) DEALLOCATE (g1)
2342    IF (ALLOCATED  (ep)) DEALLOCATE (ep)
2343    IF (ALLOCATED  (fp)) DEALLOCATE (fp)
2344    IF (ALLOCATED  (gp)) DEALLOCATE (gp)
2345    IF (ALLOCATED  (rhs)) DEALLOCATE (rhs)
2346    IF (ALLOCATED  (srhs)) DEALLOCATE (srhs)
2347    IF (ALLOCATED  (tmc)) DEALLOCATE (tmc)
2348    IF (ALLOCATED  (tmcs)) DEALLOCATE (tmcs)
2349    IF (ALLOCATED  (tmcr)) DEALLOCATE (tmcr)
2350    IF (ALLOCATED  (tmcfc)) DEALLOCATE (tmcfc)
2351    IF (ALLOCATED  (tmcw)) DEALLOCATE (tmcw)
2352    IF (ALLOCATED  (tmc_litter)) DEALLOCATE (tmc_litter)
2353    IF (ALLOCATED  (tmc_litt_mea)) DEALLOCATE (tmc_litt_mea)
2354    IF (ALLOCATED  (tmc_litter_res)) DEALLOCATE (tmc_litter_res)
2355    IF (ALLOCATED  (tmc_litter_wilt)) DEALLOCATE (tmc_litter_wilt)
2356    IF (ALLOCATED  (tmc_litter_field)) DEALLOCATE (tmc_litter_field)
2357    IF (ALLOCATED  (tmc_litter_sat)) DEALLOCATE (tmc_litter_sat)
2358    IF (ALLOCATED  (tmc_litter_awet)) DEALLOCATE (tmc_litter_awet)
2359    IF (ALLOCATED  (tmc_litter_adry)) DEALLOCATE (tmc_litter_adry)
2360    IF (ALLOCATED  (tmc_litt_wet_mea)) DEALLOCATE (tmc_litt_wet_mea)
2361    IF (ALLOCATED  (tmc_litt_dry_mea)) DEALLOCATE (tmc_litt_dry_mea)
2362    IF (ALLOCATED  (ru_ns)) DEALLOCATE (ru_ns)
2363    IF (ALLOCATED  (dr_ns)) DEALLOCATE (dr_ns)
2364    IF (ALLOCATED  (tr_ns)) DEALLOCATE (tr_ns)
2365    IF (ALLOCATED  (vegetmax_soil)) DEALLOCATE (vegetmax_soil)
2366    IF (ALLOCATED  (mc)) DEALLOCATE (mc)
2367    IF (ALLOCATED  (soilmoist)) DEALLOCATE (soilmoist)
2368    IF (ALLOCATED  (soilmoist_liquid)) DEALLOCATE (soilmoist_liquid)
2369    IF (ALLOCATED  (soil_wet_ns)) DEALLOCATE (soil_wet_ns)
2370    IF (ALLOCATED  (soil_wet_litter)) DEALLOCATE (soil_wet_litter)
2371    IF (ALLOCATED  (qflux_ns)) DEALLOCATE (qflux_ns)
2372    IF (ALLOCATED  (tmat)) DEALLOCATE (tmat)
2373    IF (ALLOCATED  (stmat)) DEALLOCATE (stmat)
2374    IF (ALLOCATED  (nroot)) DEALLOCATE (nroot)
2375    IF (ALLOCATED  (kfact_root)) DEALLOCATE (kfact_root)
2376    IF (ALLOCATED  (kfact)) DEALLOCATE (kfact)
2377    IF (ALLOCATED  (zz)) DEALLOCATE (zz)
2378    IF (ALLOCATED  (dz)) DEALLOCATE (dz)
2379    IF (ALLOCATED  (dh)) DEALLOCATE (dh)
2380    IF (ALLOCATED  (mc_lin)) DEALLOCATE (mc_lin)
2381    IF (ALLOCATED  (k_lin)) DEALLOCATE (k_lin)
2382    IF (ALLOCATED  (d_lin)) DEALLOCATE (d_lin)
2383    IF (ALLOCATED  (a_lin)) DEALLOCATE (a_lin)
2384    IF (ALLOCATED  (b_lin)) DEALLOCATE (b_lin)
2385
2386  END SUBROUTINE hydrol_clear
2387
2388!! ================================================================================================================================
2389!! SUBROUTINE   : hydrol_tmc_update
2390!!
2391!>\BRIEF        This routine updates the soil moisture profiles when the vegetation fraction have changed.
2392!!
2393!! DESCRIPTION  :
2394!!
2395!!    This routine update tmc and mc with variation of veget_max (LAND_USE or DGVM activated)
2396!!
2397!!
2398!!
2399!!
2400!! RECENT CHANGE(S) : Adaptation to excluding nobio from soiltile(1)
2401!!
2402!! MAIN OUTPUT VARIABLE(S) :
2403!!
2404!! REFERENCE(S) :
2405!!
2406!! FLOWCHART    : None
2407!! \n
2408!_ ================================================================================================================================
2409!_ hydrol_tmc_update
2410  SUBROUTINE hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg, drain_upd, runoff_upd)
2411
2412    !! 0.1 Input variables
2413    INTEGER(i_std), INTENT(in)                            :: kjpindex      !! domain size
2414    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)     :: veget_max     !! max fraction of vegetation type
2415    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)   :: soiltile      !! Fraction of each soil tile (0-1, unitless)
2416
2417    !! 0.2 Output variables
2418    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: drain_upd        !! Change in drainage due to decrease in vegtot
2419                                                                              !! on mc [kg/m2/dt]
2420    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: runoff_upd       !! Change in runoff due to decrease in vegtot
2421                                                                              !! on water2infilt[kg/m2/dt]
2422   
2423    !! 0.3 Modified variables
2424    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg   !! Amount of water in the canopy interception
2425
2426    !! 0.4 Local variables
2427    INTEGER(i_std)                           :: ji, jv, jst,jsl
2428    LOGICAL                                  :: soil_upd        !! True if soiltile changed since last time step
2429    LOGICAL                                  :: vegtot_upd      !! True if vegtot changed since last time step
2430    REAL(r_std), DIMENSION(kjpindex,nstm)    :: vmr             !! Change in soiltile (within vegtot)
2431    REAL(r_std), DIMENSION(kjpindex)         :: vmr_sum
2432    REAL(r_std), DIMENSION(kjpindex)         :: delvegtot   
2433    REAL(r_std), DIMENSION(kjpindex,nslm)    :: mc_dilu         !! Total loss of moisture content
2434    REAL(r_std), DIMENSION(kjpindex)         :: infil_dilu      !! Total loss for water2infilt
2435    REAL(r_std), DIMENSION(kjpindex,nstm)    :: tmc_old         !! tmc before calculations
2436    REAL(r_std), DIMENSION(kjpindex,nstm)    :: water2infilt_old!! water2infilt before calculations
2437    REAL(r_std), DIMENSION (kjpindex,nvm)    :: qsintveg_old    !! qsintveg before calculations
2438    REAL(r_std), DIMENSION(kjpindex)         :: test
2439    REAL(r_std), DIMENSION(kjpindex,nslm,nstm) :: mcaux        !! serves to hold the chnage in mc when vegtot decreases
2440
2441   
2442    !! 1. If a PFT has disapperead as result from a veget_max change,
2443    !!    then add canopy water to surface water.
2444    !     Other adaptations of qsintveg are delt by the normal functioning of hydrol_canop
2445
2446    DO ji=1,kjpindex
2447       IF (vegtot_old(ji) .GT.min_sechiba) THEN
2448          DO jv=1,nvm
2449             IF ((veget_max(ji,jv).LT.min_sechiba).AND.(qsintveg(ji,jv).GT.0.)) THEN
2450                jst=pref_soil_veg(jv) ! soil tile index
2451                water2infilt(ji,jst) = water2infilt(ji,jst) + qsintveg(ji,jv)/(resdist(ji,jst)*vegtot_old(ji))
2452                qsintveg(ji,jv) = zero
2453             ENDIF
2454          ENDDO
2455       ENDIF
2456    ENDDO
2457   
2458    !! 2. We now deal with the changes of soiltile and corresponding soil moistures
2459    !!    Because sum(soiltile)=1 whatever vegtot, we need to distinguish two cases:
2460    !!    - when vegtot changes (meaning that the nobio fraction changes too),
2461    !!    - and when vegtot does not changes (a priori the most frequent case)
2462
2463    vegtot_upd = SUM(ABS((vegtot(:)-vegtot_old(:)))) .GT. zero ! True if at least one land point with a vegtot change
2464    runoff_upd(:) = zero
2465    drain_upd(:) = zero
2466    IF (vegtot_upd) THEN
2467       ! We find here the processing specific to the chnages of nobio fraction and vegtot
2468
2469       delvegtot(:) = vegtot(:) - vegtot_old(:)
2470
2471       DO jst=1,nstm
2472          DO ji=1,kjpindex
2473
2474             IF (delvegtot(ji) .GT. min_sechiba) THEN
2475
2476                !! 2.1. If vegtot increases (nobio decreases), then the mc in each soiltile is decreased
2477                !!      assuming the same proportions for each soiltile, and each soil layer
2478               
2479                mc(ji,:,jst) = mc(ji,:,jst) * vegtot_old(ji)/vegtot(ji) ! vegtot cannot be zero as > vegtot_old
2480                water2infilt(ji,jst) = water2infilt(ji,jst) * vegtot_old(ji)/vegtot(ji)
2481
2482             ELSE
2483
2484                !! 2.2 If vegtot decreases (nobio increases), then the mc in each soiltile should increase,
2485                !!     but should not exceed mcs
2486                !!     For simplicity, we choose to send the corresponding water volume to drainage
2487                !!     We do the same for water2infilt but send the excess to surface runoff
2488
2489                IF (vegtot(ji) .GT.min_sechiba) THEN
2490                   mcaux(ji,:,jst) =  mc(ji,:,jst) * (vegtot_old(ji)-vegtot(ji))/vegtot(ji) ! mcaux is the delta mc
2491                ELSE ! we just have nobio in the grid-cell
2492                   mcaux(ji,:,jst) =  mc(ji,:,jst)
2493                ENDIF
2494               
2495                drain_upd(ji) = drain_upd(ji) + dz(2) * ( trois*mcaux(ji,1,jst) + mcaux(ji,2,jst) )/huit
2496                DO jsl = 2,nslm-1
2497                   drain_upd(ji) = drain_upd(ji) + dz(jsl) * (trois*mcaux(ji,jsl,jst)+mcaux(ji,jsl-1,jst))/huit &
2498                        + dz(jsl+1) * (trois*mcaux(ji,jsl,jst)+mcaux(ji,jsl+1,jst))/huit
2499                ENDDO
2500                drain_upd(ji) = drain_upd(ji) + dz(nslm) * (trois*mcaux(ji,nslm,jst) + mcaux(ji,nslm-1,jst))/huit
2501
2502                IF (vegtot(ji) .GT.min_sechiba) THEN
2503                   runoff_upd(ji) = runoff_upd(ji) + water2infilt(ji,jst) * (vegtot_old(ji)-vegtot(ji))/vegtot(ji)
2504                ELSE ! we just have nobio in the grid-cell
2505                   runoff_upd(ji) = runoff_upd(ji) + water2infilt(ji,jst)
2506                ENDIF
2507
2508             ENDIF
2509             
2510          ENDDO
2511       ENDDO
2512       
2513    ENDIF
2514   
2515    !! 3. At the end of step 2, we are back to a case where vegtot changes are treated, so we can use soiltile
2516    !!    as a fraction of vegtot to process the mc transfers between soil tiles due to the changes of vegetation map
2517   
2518    !! 3.1 Check if soiltiles changed since last time step
2519    soil_upd=SUM(ABS(soiltile(:,:)-resdist(:,:))) .GT. zero
2520    IF (printlev>=3) WRITE (numout,*) 'soil_upd ', soil_upd
2521       
2522    IF (soil_upd) THEN
2523     
2524       !! 3.2 Define the change in soiltile
2525       vmr(:,:) = soiltile(:,:) - resdist(:,:)  ! resdist is the previous values of soiltiles, previous timestep, so before new map
2526
2527       ! Total area loss by the three soil tiles
2528       DO ji=1,kjpindex
2529          vmr_sum(ji)=SUM(vmr(ji,:),MASK=vmr(ji,:).LT.zero)
2530       ENDDO
2531
2532       !! 3.3 Shrinking soil tiles
2533       !! 3.3.1 Total loss of moisture content from the shrinking soil tiles, expressed by soil layer
2534       mc_dilu(:,:)=zero
2535       DO jst=1,nstm
2536          DO jsl = 1, nslm
2537             DO ji=1,kjpindex
2538                IF ( vmr(ji,jst) < -min_sechiba ) THEN
2539                   mc_dilu(ji,jsl) = mc_dilu(ji,jsl) + mc(ji,jsl,jst) * vmr(ji,jst) / vmr_sum(ji)
2540                ENDIF
2541             ENDDO
2542          ENDDO
2543       ENDDO
2544
2545       !! 3.3.2 Total loss of water2inft from the shrinking soil tiles
2546       infil_dilu(:)=zero
2547       DO jst=1,nstm
2548          DO ji=1,kjpindex
2549             IF ( vmr(ji,jst) < -min_sechiba ) THEN
2550                infil_dilu(ji) = infil_dilu(ji) + water2infilt(ji,jst) * vmr(ji,jst) / vmr_sum(ji)
2551             ENDIF
2552          ENDDO
2553       ENDDO
2554
2555       !! 3.4 Each gaining soil tile gets moisture proportionally to both the total loss and its areal increase
2556
2557       ! As the original mc from each soil tile are in [mcr,mcs] and we do weighted avrage, the new mc are in [mcr,mcs]
2558       ! The case where the soiltile is created (soiltile_old=0) works as the other cases
2559
2560       ! 3.4.1 Update mc(kjpindex,nslm,nstm) !m3/m3
2561       DO jst=1,nstm
2562          DO jsl = 1, nslm
2563             DO ji=1,kjpindex
2564                IF ( vmr(ji,jst) > min_sechiba ) THEN
2565                   mc(ji,jsl,jst) = ( mc(ji,jsl,jst) * resdist(ji,jst) + mc_dilu(ji,jsl) * vmr(ji,jst) ) / soiltile(ji,jst)
2566                   ! NB : soiltile can not be zero for case vmr > zero, see slowproc_veget
2567                ENDIF
2568             ENDDO
2569          ENDDO
2570       ENDDO
2571       
2572       ! 3.4.2 Update water2inft
2573       DO jst=1,nstm
2574          DO ji=1,kjpindex
2575             IF ( vmr(ji,jst) > min_sechiba ) THEN !donc soiltile>0     
2576                water2infilt(ji,jst) = ( water2infilt(ji,jst) * resdist(ji,jst) + infil_dilu(ji) * vmr(ji,jst) ) / soiltile(ji,jst)
2577             ENDIF !donc resdist>0
2578          ENDDO
2579       ENDDO
2580
2581       ! 3.4.3 Case where soiltile < min_sechiba
2582       DO jst=1,nstm
2583          DO ji=1,kjpindex
2584             IF ( soiltile(ji,jst) .LT. min_sechiba ) THEN
2585                water2infilt(ji,jst) = zero
2586                mc(ji,:,jst) = zero
2587             ENDIF
2588          ENDDO
2589       ENDDO
2590
2591    ENDIF ! soil_upd
2592
2593    !! 4. Update tmc and humtot
2594   
2595    DO jst=1,nstm
2596       DO ji=1,kjpindex
2597             tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
2598             DO jsl = 2,nslm-1
2599                tmc(ji,jst) = tmc(ji,jst) + dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
2600                     + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
2601             ENDDO
2602             tmc(ji,jst) = tmc(ji,jst) + dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
2603             tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
2604             ! WARNING tmc is increased by includes water2infilt(ji,jst)
2605       ENDDO
2606    ENDDO
2607
2608    humtot(:) = zero
2609    DO jst=1,nstm
2610       DO ji=1,kjpindex
2611          humtot(ji) = humtot(ji) + vegtot(ji) * soiltile(ji,jst) * tmc(ji,jst) ! average over grid-cell (i.e. total land)
2612       ENDDO
2613    ENDDO
2614
2615
2616    !! Now that the work is done, update resdist
2617    resdist(:,:) = soiltile(:,:)
2618
2619    IF (printlev>=3) WRITE (numout,*) ' hydrol_tmc_update done '
2620
2621  END SUBROUTINE hydrol_tmc_update
2622
2623!! ================================================================================================================================
2624!! SUBROUTINE   : hydrol_var_init
2625!!
2626!>\BRIEF        This routine initializes hydrologic parameters to define K and D, and diagnostic hydrologic variables. 
2627!!
2628!! DESCRIPTION  :
2629!! - 1 compute the depths
2630!! - 2 compute the profile for roots
2631!! - 3 compute the profile for a and n Van Genuchten parameter
2632!! - 4 compute the linearized values of k, a, b and d for the resolution of Fokker Planck equation
2633!! - 5 water reservoirs initialisation
2634!!
2635!! RECENT CHANGE(S) : None
2636!!
2637!! MAIN OUTPUT VARIABLE(S) :
2638!!
2639!! REFERENCE(S) :
2640!!
2641!! FLOWCHART    : None
2642!! \n
2643!_ ================================================================================================================================
2644!_ hydrol_var_init
2645
2646  SUBROUTINE hydrol_var_init (ks, nvan, avan, mcr, mcs, mcfc, mcw, &
2647       kjpindex, veget, veget_max, soiltile, njsc, &
2648       mx_eau_var, shumdiag_perma, &
2649       drysoil_frac, qsintveg, mc_layh, mcl_layh) 
2650
2651    ! interface description
2652
2653    !! 0. Variable and parameter declaration
2654
2655    !! 0.1 Input variables
2656    ! input scalar
2657    INTEGER(i_std), INTENT(in)                          :: kjpindex      !! Domain size (number of grid cells) (1)
2658    ! input fields
2659    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max     !! PFT fractions within grid-cells (1; 1)
2660    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget         !! Effective fraction of vegetation by PFT (1; 1)
2661    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: njsc          !! Index of the dominant soil textural class
2662                                                                         !! in the grid cell (1-nscm, unitless)
2663    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile      !! Fraction of each soil tile within vegtot (0-1, unitless)
2664   
2665    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: ks               !! Hydraulic conductivity at saturation (mm {-1})
2666    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: nvan             !! Van Genuchten coeficients n (unitless)
2667    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: avan             !! Van Genuchten coeficients a (mm-1})
2668    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
2669    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
2670    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
2671    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
2672 
2673    !! 0.2 Output variables
2674
2675    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: mx_eau_var    !! Maximum water content of the soil
2676                                                                         !! @tex $(kg m^{-2})$ @endtex
2677    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out) :: shumdiag_perma!! Percent of porosity filled with water (mc/mcs)
2678                                                                         !! used for the thermal computations
2679    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)    :: drysoil_frac  !! function of litter humidity
2680    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: mc_layh       !! Volumetric soil moisture content for each layer in hydrol(liquid+ice) [m3/m3]
2681    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: mcl_layh      !! Volumetric soil moisture content for each layer in hydrol(liquid) [m3/m3]
2682
2683    !! 0.3 Modified variables
2684    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg    !! Water on vegetation due to interception
2685                                                                         !! @tex $(kg m^{-2})$ @endtex 
2686
2687    !! 0.4 Local variables
2688
2689    INTEGER(i_std)                                      :: ji, jv        !! Grid-cell and PFT indices (1)
2690    INTEGER(i_std)                                      :: jst, jsc, jsl !! Soiltile, Soil Texture, and Soil layer indices (1)
2691    INTEGER(i_std)                                      :: i             !! Index (1)
2692    REAL(r_std)                                         :: m             !! m=1-1/n (unitless)
2693    REAL(r_std)                                         :: frac          !! Relative linearized VWC (unitless)
2694    REAL(r_std)                                         :: avan_mod      !! VG parameter a modified from  exponantial profile
2695                                                                         !! @tex $(mm^{-1})$ @endtex
2696    REAL(r_std)                                         :: nvan_mod      !! VG parameter n  modified from  exponantial profile
2697                                                                         !! (unitless)
2698    REAL(r_std), DIMENSION(nslm,kjpindex)               :: afact, nfact  !! Multiplicative factor for decay of a and n with depth
2699                                                                         !! (unitless)
2700    ! parameters for "soil densification" with depth
2701    REAL(r_std)                                         :: dp_comp       !! Depth at which the 'compacted' value of ksat
2702                                                                         !! is reached (m)
2703    REAL(r_std)                                         :: f_ks          !! Exponential factor for decay of ksat with depth
2704                                                                         !! @tex $(m^{-1})$ @endtex
2705    ! Fixed parameters from fitted relationships
2706    REAL(r_std)                                         :: n0            !! fitted value for relation log((n-n0)/(n_ref-n0)) =
2707                                                                         !! nk_rel * log(k/k_ref)
2708                                                                         !! (unitless)
2709    REAL(r_std)                                         :: nk_rel        !! fitted value for relation log((n-n0)/(n_ref-n0)) =
2710                                                                         !! nk_rel * log(k/k_ref)
2711                                                                         !! (unitless)
2712    REAL(r_std)                                         :: a0            !! fitted value for relation log((a-a0)/(a_ref-a0)) =
2713                                                                         !! ak_rel * log(k/k_ref)
2714                                                                         !! @tex $(mm^{-1})$ @endtex
2715    REAL(r_std)                                         :: ak_rel        !! fitted value for relation log((a-a0)/(a_ref-a0)) =
2716                                                                         !! ak_rel * log(k/k_ref)
2717                                                                         !! (unitless)
2718    REAL(r_std)                                         :: kfact_max     !! Maximum factor for Ks decay with depth (unitless)
2719    REAL(r_std)                                         :: k_tmp, tmc_litter_ratio
2720    INTEGER(i_std), PARAMETER                           :: error_level = 3 !! Error level for consistency check
2721                                                                           !! Switch to 2 tu turn fatal errors into warnings
2722    REAL(r_std), DIMENSION (kjpindex,nslm)              :: alphavg         !! VG param a modified with depth at each node
2723                                                                           !! @tex $(mm^{-1})$ @endtexe
2724    REAL(r_std), DIMENSION (kjpindex,nslm)              :: nvg             !! VG param n modified with depth at each node
2725                                                                           !! (unitless)
2726                                                                           !! need special treatment
2727    INTEGER(i_std)                                      :: ii
2728    INTEGER(i_std)                                      :: iiref           !! To identify the mc_lins where k_lin and d_lin
2729                                                                           !! need special treatment
2730
2731!_ ================================================================================================================================
2732
2733    !Config Key   = CWRR_NKS_N0
2734    !Config Desc  = fitted value for relation log((n-n0)/(n_ref-n0)) = nk_rel * log(k/k_ref)
2735    !Config Def   = 0.0
2736    !Config If    =
2737    !Config Help  =
2738    !Config Units = [-]
2739    n0 = 0.0
2740    CALL getin_p("CWRR_NKS_N0",n0)
2741
2742    !! Check parameter value (correct range)
2743    IF ( n0 < zero ) THEN
2744       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2745            &     "Wrong parameter value for CWRR_NKS_N0.", &
2746            &     "This parameter should be non-negative. ", &
2747            &     "Please, check parameter value in run.def. ")
2748    END IF
2749
2750
2751    !Config Key   = CWRR_NKS_POWER
2752    !Config Desc  = fitted value for relation log((n-n0)/(n_ref-n0)) = nk_rel * log(k/k_ref)
2753    !Config Def   = 0.0
2754    !Config If    =
2755    !Config Help  =
2756    !Config Units = [-]
2757    nk_rel = 0.0
2758    CALL getin_p("CWRR_NKS_POWER",nk_rel)
2759
2760    !! Check parameter value (correct range)
2761    IF ( nk_rel < zero ) THEN
2762       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2763            &     "Wrong parameter value for CWRR_NKS_POWER.", &
2764            &     "This parameter should be non-negative. ", &
2765            &     "Please, check parameter value in run.def. ")
2766    END IF
2767
2768
2769    !Config Key   = CWRR_AKS_A0
2770    !Config Desc  = fitted value for relation log((a-a0)/(a_ref-a0)) = ak_rel * log(k/k_ref)
2771    !Config Def   = 0.0
2772    !Config If    =
2773    !Config Help  =
2774    !Config Units = [1/mm]
2775    a0 = 0.0
2776    CALL getin_p("CWRR_AKS_A0",a0)
2777
2778    !! Check parameter value (correct range)
2779    IF ( a0 < zero ) THEN
2780       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2781            &     "Wrong parameter value for CWRR_AKS_A0.", &
2782            &     "This parameter should be non-negative. ", &
2783            &     "Please, check parameter value in run.def. ")
2784    END IF
2785
2786
2787    !Config Key   = CWRR_AKS_POWER
2788    !Config Desc  = fitted value for relation log((a-a0)/(a_ref-a0)) = ak_rel * log(k/k_ref)
2789    !Config Def   = 0.0
2790    !Config If    =
2791    !Config Help  =
2792    !Config Units = [-]
2793    ak_rel = 0.0
2794    CALL getin_p("CWRR_AKS_POWER",ak_rel)
2795
2796    !! Check parameter value (correct range)
2797    IF ( nk_rel < zero ) THEN
2798       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2799            &     "Wrong parameter value for CWRR_AKS_POWER.", &
2800            &     "This parameter should be non-negative. ", &
2801            &     "Please, check parameter value in run.def. ")
2802    END IF
2803
2804
2805    !Config Key   = KFACT_DECAY_RATE
2806    !Config Desc  = Factor for Ks decay with depth
2807    !Config Def   = 2.0
2808    !Config If    =
2809    !Config Help  = 
2810    !Config Units = [1/m]
2811    f_ks = 2.0
2812    CALL getin_p ("KFACT_DECAY_RATE", f_ks)
2813
2814    !! Check parameter value (correct range)
2815    IF ( f_ks < zero ) THEN
2816       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2817            &     "Wrong parameter value for KFACT_DECAY_RATE.", &
2818            &     "This parameter should be positive. ", &
2819            &     "Please, check parameter value in run.def. ")
2820    END IF
2821
2822
2823    !Config Key   = KFACT_STARTING_DEPTH
2824    !Config Desc  = Depth for compacted value of Ks
2825    !Config Def   = 0.3
2826    !Config If    =
2827    !Config Help  = 
2828    !Config Units = [m]
2829    dp_comp = 0.3
2830    CALL getin_p ("KFACT_STARTING_DEPTH", dp_comp)
2831
2832    !! Check parameter value (correct range)
2833    IF ( dp_comp <= zero ) THEN
2834       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2835            &     "Wrong parameter value for KFACT_STARTING_DEPTH.", &
2836            &     "This parameter should be positive. ", &
2837            &     "Please, check parameter value in run.def. ")
2838    END IF
2839
2840
2841    !Config Key   = KFACT_MAX
2842    !Config Desc  = Maximum Factor for Ks increase due to vegetation
2843    !Config Def   = 10.0
2844    !Config If    =
2845    !Config Help  =
2846    !Config Units = [-]
2847    kfact_max = 10.0
2848    CALL getin_p ("KFACT_MAX", kfact_max)
2849
2850    !! Check parameter value (correct range)
2851    IF ( kfact_max < 10. ) THEN
2852       CALL ipslerr_p(error_level, "hydrol_var_init.", &
2853            &     "Wrong parameter value for KFACT_MAX.", &
2854            &     "This parameter should be greater than 10. ", &
2855            &     "Please, check parameter value in run.def. ")
2856    END IF
2857
2858
2859
2860    !Config Key   = KFACT_ROOT_CONST
2861    !Config Desc  = Set constant kfact_root in every soil layer. Otherwise kfact_root increase over soil depth in the rootzone.
2862    !Config If    =
2863    !Config Def   = n
2864    !Config Help  = Use KFACT_ROOT_CONST=true to impose kfact_root=1 in every soil layer. Otherwise kfact_root increase over soil depth in the rootzone.
2865    !Config Units = [y/n]
2866    kfact_root_const = .FALSE.
2867    CALL getin_p("KFACT_ROOT_CONST",kfact_root_const)
2868
2869   
2870    !-
2871    !! 1 Create local variables in mm for the vertical depths
2872    !!   Vertical depth variables (znh, dnh, dlh) are stored in module vertical_soil_var in m.
2873    DO jsl=1,nslm
2874       zz(jsl) = znh(jsl)*mille
2875       dz(jsl) = dnh(jsl)*mille
2876       dh(jsl) = dlh(jsl)*mille
2877    ENDDO
2878
2879    !-
2880    !! 2 Compute the root density profile if not ok_dynroot
2881    !!   For the case with ok_dynroot, the calculations are done at each time step in hydrol_soil
2882    IF (.NOT. ok_dynroot) THEN
2883       DO ji=1, kjpindex
2884          !-
2885          !! The three following equations concerning nroot computation are derived from the integrals
2886          !! of equations C9 to C11 of De Rosnay's (1999) PhD thesis (page 158).
2887          !! The occasional absence of minus sign before humcste parameter is correct.
2888          DO jv = 1,nvm
2889             DO jsl = 2, nslm-1
2890                nroot(ji,jv,jsl) = (EXP(-humcste(jv)*zz(jsl)/mille)) * &
2891                     & (EXP(humcste(jv)*dz(jsl)/mille/deux) - &
2892                     & EXP(-humcste(jv)*dz(jsl+1)/mille/deux))/ &
2893                     & (EXP(-humcste(jv)*dz(2)/mille/deux) &
2894                     & -EXP(-humcste(jv)*zz(nslm)/mille))
2895             ENDDO
2896             nroot(ji,jv,1) = zero
2897
2898             nroot(ji,jv,nslm) = (EXP(humcste(jv)*dz(nslm)/mille/deux) -un) * &
2899                  & EXP(-humcste(jv)*zz(nslm)/mille) / &
2900                  & (EXP(-humcste(jv)*dz(2)/mille/deux) &
2901                  & -EXP(-humcste(jv)*zz(nslm)/mille))
2902          ENDDO
2903       ENDDO
2904    END IF
2905
2906 
2907
2908    !-
2909    !! 3 Compute the profile for a and n
2910    !-
2911    DO ji = 1, kjpindex
2912       DO jsl=1,nslm
2913          ! PhD thesis of d'Orgeval, 2006, p81, Eq. 4.38; d'Orgeval et al. 2008, Eq. 2
2914          ! Calibrated against Hapex-Sahel measurements
2915          kfact(jsl,ji) = MIN(MAX(EXP(- f_ks * (zz(jsl)/mille - dp_comp)), un/kfact_max),un)
2916          ! PhD thesis of d'Orgeval, 2006, p81, Eqs. 4.39; 4.42, and Fig 4.14
2917
2918          nfact(jsl,ji) = ( kfact(jsl,ji) )**nk_rel
2919          afact(jsl,ji) = ( kfact(jsl,ji) )**ak_rel
2920       ENDDO
2921    ENDDO
2922   
2923    ! For every grid cell
2924     DO ji = 1, kjpindex
2925       !-
2926       !! 4 Compute the linearized values of k, a, b and d
2927       !!   The effect of kfact_root on ks thus on k, a, n and d, is taken into account further in the code,
2928       !!   in hydrol_soil_coef.
2929       !-
2930       ! Calculate the matrix coef for Dublin model (de Rosnay, 1999; p149)
2931       ! piece-wise linearised hydraulic conductivity k_lin=alin * mc_lin + b_lin
2932       ! and diffusivity d_lin in each interval of mc, called mc_lin,
2933       ! between imin, for residual mcr, and imax for saturation mcs.
2934
2935       ! We define 51 bounds for 50 bins of mc between mcr and mcs
2936       mc_lin(imin,ji)=mcr(ji)
2937       mc_lin(imax,ji)=mcs(ji)
2938       DO ii= imin+1, imax-1 ! ii=2,50
2939          mc_lin(ii,ji) = mcr(ji) + (ii-imin)*(mcs(ji)-mcr(ji))/(imax-imin)
2940       ENDDO
2941
2942       DO jsl = 1, nslm
2943          ! From PhD thesis of d'Orgeval, 2006, p81, Eq. 4.42
2944          nvan_mod = n0 + (nvan(ji)-n0) * nfact(jsl,ji)
2945          avan_mod = a0 + (avan(ji)-a0) * afact(jsl,ji)
2946          m = un - un / nvan_mod
2947          ! Creation of arrays for SP-MIP output by landpoint
2948          nvan_mod_tab(jsl,ji) = nvan_mod
2949          avan_mod_tab(jsl,ji) = avan_mod
2950          ! We apply Van Genuchten equation for K(theta) based on Ks(z)=ks(ji) * kfact(jsl,ji)
2951          DO ii = imax,imin,-1
2952             frac=MIN(un,(mc_lin(ii,ji)-mcr(ji))/(mcs(ji)-mcr(ji)))
2953             k_lin(ii,jsl,ji) = ks(ji) * kfact(jsl,ji) * (frac**0.5) * ( un - ( un - frac ** (un/m)) ** m )**2
2954          ENDDO
2955
2956          ! k_lin should not be zero, nor too small
2957          ! We track iiref, the bin under which mc is too small and we may get zero k_lin
2958          !salma: ji replaced with ii and jiref replaced with iiref and jsc with ji
2959          ii=imax-1
2960          DO WHILE ((k_lin(ii,jsl,ji) > 1.e-32) .and. (ii>0))
2961             iiref=ii
2962             ii=ii-1
2963          ENDDO
2964          DO ii=iiref-1,imin,-1
2965             k_lin(ii,jsl,ji)=k_lin(ii+1,jsl,ji)/10.
2966          ENDDO
2967
2968          DO ii = imin,imax-1 ! ii=1,50
2969             ! We deduce a_lin and b_lin based on continuity between segments k_lin = a_lin*mc-lin+b_lin
2970             a_lin(ii,jsl,ji) = (k_lin(ii+1,jsl,ji)-k_lin(ii,jsl,ji)) / (mc_lin(ii+1,ji)-mc_lin(ii,ji))
2971             b_lin(ii,jsl,ji)  = k_lin(ii,jsl,ji) - a_lin(ii,jsl,ji)*mc_lin(ii,ji)
2972
2973             ! We calculate the d_lin for each mc bin, from Van Genuchten equation for D(theta)
2974             ! d_lin is constant and taken as the arithmetic mean between the values at the bounds of each bin
2975             IF (ii.NE.imin .AND. ii.NE.imax-1) THEN
2976                frac=MIN(un,(mc_lin(ii,ji)-mcr(ji))/(mcs(ji)-mcr(ji)))
2977                d_lin(ii,jsl,ji) =(k_lin(ii,jsl,ji) / (avan_mod*m*nvan_mod)) *  &
2978                     ( (frac**(-un/m))/(mc_lin(ii,ji)-mcr(ji)) ) * &
2979                     (  frac**(-un/m) -un ) ** (-m)
2980                frac=MIN(un,(mc_lin(ii+1,ji)-mcr(ji))/(mcs(ji)-mcr(ji)))
2981                d_lin(ii+1,jsl,ji) =(k_lin(ii+1,jsl,ji) / (avan_mod*m*nvan_mod))*&
2982                     ( (frac**(-un/m))/(mc_lin(ii+1,ji)-mcr(ji)) ) * &
2983                     (  frac**(-un/m) -un ) ** (-m)
2984                d_lin(ii,jsl,ji) = undemi * (d_lin(ii,jsl,ji)+d_lin(ii+1,jsl,ji))
2985             ELSE IF(ii.EQ.imax-1) THEN
2986                d_lin(ii,jsl,ji) =(k_lin(ii,jsl,ji) / (avan_mod*m*nvan_mod)) * &
2987                     ( (frac**(-un/m))/(mc_lin(ii,ji)-mcr(ji)) ) *  &
2988                     (  frac**(-un/m) -un ) ** (-m)
2989             ENDIF
2990          ENDDO
2991
2992          ! Special case for ii=imin
2993          d_lin(imin,jsl,ji) = d_lin(imin+1,jsl,ji)/1000.
2994
2995          ! We adjust d_lin where k_lin was previously adjusted otherwise we might get non-monotonous variations
2996          ! We don't want d_lin = zero
2997          DO ii=iiref-1,imin,-1
2998             d_lin(ii,jsl,ji)=d_lin(ii+1,jsl,ji)/10.
2999          ENDDO
3000
3001       ENDDO
3002    ENDDO
3003
3004
3005    ! Output of alphavg and nvg at each node for SP-MIP
3006    DO jsl = 1, nslm
3007       alphavg(:,jsl) = avan_mod_tab(jsl,:)*1000. ! from mm-1 to m-1
3008       nvg(:,jsl) = nvan_mod_tab(jsl,:)
3009    ENDDO
3010    CALL xios_orchidee_send_field("alphavg",alphavg) ! in m-1
3011    CALL xios_orchidee_send_field("nvg",nvg) ! unitless
3012
3013    !! 5 Water reservoir initialisation
3014    !
3015!!$    DO jst = 1,nstm
3016!!$       DO ji = 1, kjpindex
3017!!$          mx_eau_var(ji) = mx_eau_var(ji) + soiltile(ji,jst)*&
3018!!$               &   zmaxh*mille*mcs(njsc(ji))
3019!!$       END DO
3020!!$    END DO
3021
3022    mx_eau_var(:) = zero
3023    mx_eau_var(:) = zmaxh*mille*mcs(:)
3024
3025    DO ji = 1,kjpindex
3026       IF (vegtot(ji) .LE. zero) THEN
3027          mx_eau_var(ji) = mx_eau_nobio*zmaxh
3028          ! Aurelien: what does vegtot=0 mean? is it like frac_nobio=1? But if 0<frac_nobio<1 ???
3029       ENDIF
3030
3031    END DO
3032
3033    ! Compute the litter humidity, shumdiag and fry
3034    shumdiag_perma(:,:) = zero
3035    humtot(:) = zero
3036    tmc(:,:) = zero
3037
3038    ! Loop on soiltiles to compute the variables (ji,jst)
3039    DO jst=1,nstm
3040       DO ji = 1, kjpindex
3041          tmcs(ji,jst)=zmaxh* mille*mcs(ji)
3042          tmcr(ji,jst)=zmaxh* mille*mcr(ji)
3043          tmcfc(ji,jst)=zmaxh* mille*mcfc(ji)
3044          tmcw(ji,jst)=zmaxh* mille*mcw(ji)
3045       ENDDO
3046    ENDDO
3047
3048    ! The total soil moisture for each soiltile:
3049    DO jst=1,nstm
3050       DO ji=1,kjpindex
3051          tmc(ji,jst)= dz(2) * ( trois*mc(ji,1,jst)+ mc(ji,2,jst))/huit
3052       END DO
3053    ENDDO
3054
3055    DO jst=1,nstm
3056       DO jsl=2,nslm-1
3057          DO ji=1,kjpindex
3058             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) * ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
3059                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
3060          END DO
3061       END DO
3062    ENDDO
3063
3064    DO jst=1,nstm
3065       DO ji=1,kjpindex
3066          tmc(ji,jst) = tmc(ji,jst) +  dz(nslm) * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
3067          tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
3068       ENDDO
3069    END DO
3070
3071!JG: hydrol_tmc_update should not be called in the initialization phase. Call of hydrol_tmc_update makes the model restart differenlty.
3072!    ! If veget has been updated before restart (with LAND USE or DGVM),
3073!    ! tmc and mc must be modified with respect to humtot conservation.
3074!   CALL hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg)
3075
3076    ! The litter variables:
3077    ! level 1
3078    DO jst=1,nstm
3079       DO ji=1,kjpindex
3080          tmc_litter(ji,jst) = dz(2) * (trois*mcl(ji,1,jst)+mcl(ji,2,jst))/huit
3081          tmc_litter_wilt(ji,jst) = dz(2) * mcw(ji) / deux
3082          tmc_litter_res(ji,jst) = dz(2) * mcr(ji) / deux
3083          tmc_litter_field(ji,jst) = dz(2) * mcfc(ji) / deux
3084          tmc_litter_sat(ji,jst) = dz(2) * mcs(ji) / deux
3085          tmc_litter_awet(ji,jst) = dz(2) * mc_awet(njsc(ji)) / deux
3086          tmc_litter_adry(ji,jst) = dz(2) * mc_adry(njsc(ji)) / deux
3087       ENDDO
3088    END DO
3089    ! sum from level 2 to 4
3090    DO jst=1,nstm
3091       DO jsl=2,4
3092          DO ji=1,kjpindex
3093             tmc_litter(ji,jst) = tmc_litter(ji,jst) + dz(jsl) * &
3094                  & ( trois*mcl(ji,jsl,jst) + mcl(ji,jsl-1,jst))/huit &
3095                  & + dz(jsl+1)*(trois*mcl(ji,jsl,jst) + mcl(ji,jsl+1,jst))/huit
3096             tmc_litter_wilt(ji,jst) = tmc_litter_wilt(ji,jst) + &
3097                  &(dz(jsl)+ dz(jsl+1))*&
3098                  & mcw(ji)/deux
3099             tmc_litter_res(ji,jst) = tmc_litter_res(ji,jst) + &
3100                  &(dz(jsl)+ dz(jsl+1))*&
3101                  & mcr(ji)/deux
3102             tmc_litter_sat(ji,jst) = tmc_litter_sat(ji,jst) + &
3103                  &(dz(jsl)+ dz(jsl+1))* &
3104                  & mcs(ji)/deux
3105             tmc_litter_field(ji,jst) = tmc_litter_field(ji,jst) + &
3106                  & (dz(jsl)+ dz(jsl+1))* &
3107                  & mcfc(ji)/deux
3108             tmc_litter_awet(ji,jst) = tmc_litter_awet(ji,jst) + &
3109                  &(dz(jsl)+ dz(jsl+1))* &
3110                  & mc_awet(njsc(ji))/deux
3111             tmc_litter_adry(ji,jst) = tmc_litter_adry(ji,jst) + &
3112                  & (dz(jsl)+ dz(jsl+1))* &
3113                  & mc_adry(njsc(ji))/deux
3114          END DO
3115       END DO
3116    END DO
3117
3118
3119    DO jst=1,nstm
3120       DO ji=1,kjpindex
3121          ! here we set that humrelv=0 in PFT1
3122         humrelv(ji,1,jst) = zero
3123       ENDDO
3124    END DO
3125
3126
3127    ! Calculate shumdiag_perma for thermosoil
3128    ! Use resdist instead of soiltile because we here need to have
3129    ! shumdiag_perma at the value from previous time step.
3130    ! Here, soilmoist is only used as a temporary variable to calculate shumdiag_perma
3131    ! (based on resdist=soiltile from previous timestep, but normally equal to soiltile)
3132    ! For consistency with hydrol_soil, we want to calculate a grid-cell average
3133    soilmoist(:,:) = zero
3134    DO jst=1,nstm
3135       DO ji=1,kjpindex
3136          soilmoist(ji,1) = soilmoist(ji,1) + resdist(ji,jst) * &
3137               dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
3138          DO jsl = 2,nslm-1
3139             soilmoist(ji,jsl) = soilmoist(ji,jsl) + resdist(ji,jst) * &
3140                  ( dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
3141                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit )
3142          END DO
3143          soilmoist(ji,nslm) = soilmoist(ji,nslm) + resdist(ji,jst) * &
3144               dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
3145       ENDDO
3146    ENDDO
3147    DO ji=1,kjpindex
3148        soilmoist(ji,:) = soilmoist(ji,:) * vegtot_old(ji) ! grid cell average
3149    ENDDO
3150
3151    ! -- shumdiag_perma for restart
3152   !  For consistency with hydrol_soil, we want to calculate a grid-cell average
3153    DO jsl = 1, nslm
3154       DO ji=1,kjpindex
3155          shumdiag_perma(ji,jsl) = soilmoist(ji,jsl) / (dh(jsl)*mcs(ji))
3156          shumdiag_perma(ji,jsl) = MAX(MIN(shumdiag_perma(ji,jsl), un), zero)
3157       ENDDO
3158    ENDDO
3159
3160    ! Calculate drysoil_frac if it was not found in the restart file
3161    ! For simplicity, we set drysoil_frac to 0.5 in this case
3162    IF (ALL(drysoil_frac(:) == val_exp)) THEN
3163       DO ji=1,kjpindex
3164          drysoil_frac(ji) = 0.5
3165       END DO
3166    END IF
3167
3168    !! Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in
3169    !! thermosoil for the thermal conductivity.
3170    ! These values are only used in thermosoil_init in absence of a restart file
3171
3172    mc_layh(:,:) = zero
3173    mcl_layh(:,:) = zero
3174     
3175    DO jst=1,nstm
3176       DO jsl=1,nslm
3177          DO ji=1,kjpindex
3178            mc_layh(ji,jsl) = mc_layh(ji,jsl) + mc(ji,jsl,jst) * resdist(ji,jst)  * vegtot_old(ji)
3179            mcl_layh(ji,jsl) = mcl_layh(ji,jsl) + mcl(ji,jsl,jst) * resdist(ji,jst) * vegtot_old(ji)
3180         ENDDO
3181      END DO
3182    END DO
3183
3184    IF (printlev>=3) WRITE (numout,*) ' hydrol_var_init done '
3185
3186  END SUBROUTINE hydrol_var_init
3187
3188
3189
3190   
3191!! ================================================================================================================================
3192!! SUBROUTINE   : hydrol_canop
3193!!
3194!>\BRIEF        This routine computes canopy processes.
3195!!
3196!! DESCRIPTION  :
3197!! - 1 evaporation off the continents
3198!! - 1.1 The interception loss is take off the canopy.
3199!! - 1.2 precip_rain is shared for each vegetation type
3200!! - 1.3 Limits the effect and sum what receives soil
3201!! - 1.4 swap qsintveg to the new value
3202!!
3203!! RECENT CHANGE(S) : None
3204!!
3205!! MAIN OUTPUT VARIABLE(S) :
3206!!
3207!! REFERENCE(S) :
3208!!
3209!! FLOWCHART    : None
3210!! \n
3211!_ ================================================================================================================================
3212!_ hydrol_canop
3213
3214  SUBROUTINE hydrol_canop (kjpindex, precip_rain, vevapwet, veget_max, veget, qsintmax, &
3215       & qsintveg,precisol,tot_melt)
3216
3217    !
3218    ! interface description
3219    !
3220
3221    !! 0. Variable and parameter declaration
3222
3223    !! 0.1 Input variables
3224
3225    INTEGER(i_std), INTENT(in)                               :: kjpindex    !! Domain size
3226    ! input fields
3227    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_rain !! Rain precipitation
3228    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: vevapwet    !! Interception loss
3229    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: veget_max   !! max fraction of vegetation type
3230    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: veget       !! Fraction of vegetation type
3231    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: qsintmax    !! Maximum water on vegetation for interception
3232    REAL(r_std), DIMENSION  (kjpindex), INTENT (in)          :: tot_melt    !! Total melt
3233
3234    !! 0.2 Output variables
3235
3236    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: precisol    !! Water fallen onto the ground (throughfall+Totmelt)
3237
3238    !! 0.3 Modified variables
3239
3240    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(inout)     :: qsintveg    !! Water on vegetation due to interception
3241
3242    !! 0.4 Local variables
3243
3244    INTEGER(i_std)                                           :: ji, jv
3245    REAL(r_std), DIMENSION (kjpindex,nvm)                    :: zqsintvegnew
3246
3247!_ ================================================================================================================================
3248
3249    ! boucle sur les points continentaux
3250    ! calcul de qsintveg au pas de temps suivant
3251    ! par ajout du flux interception loss
3252    ! calcule par enerbil en fonction
3253    ! des calculs faits dans diffuco
3254    ! calcul de ce qui tombe sur le sol
3255    ! avec accumulation dans precisol
3256    ! essayer d'harmoniser le traitement du sol nu
3257    ! avec celui des differents types de vegetation
3258    ! fait si on impose qsintmax ( ,1) = 0.0
3259    !
3260    ! loop for continental subdomain
3261    !
3262    !
3263    !! 1 evaporation off the continents
3264    !
3265    !! 1.1 The interception loss is take off the canopy.
3266    DO jv=2,nvm
3267       qsintveg(:,jv) = qsintveg(:,jv) - vevapwet(:,jv)
3268    END DO
3269
3270    !     It is raining :
3271    !! 1.2 precip_rain is shared for each vegetation type
3272    !
3273    qsintveg(:,1) = zero
3274    DO jv=2,nvm
3275       qsintveg(:,jv) = qsintveg(:,jv) + veget(:,jv) * ((1-throughfall_by_pft(jv))*precip_rain(:))
3276    END DO
3277
3278    !
3279    !! 1.3 Limits the effect and sum what receives soil
3280    !
3281    precisol(:,1)=veget_max(:,1)*precip_rain(:)
3282    DO jv=2,nvm
3283       DO ji = 1, kjpindex
3284          zqsintvegnew(ji,jv) = MIN (qsintveg(ji,jv),qsintmax(ji,jv)) 
3285          precisol(ji,jv) = (veget(ji,jv)*throughfall_by_pft(jv)*precip_rain(ji)) + &
3286               qsintveg(ji,jv) - zqsintvegnew (ji,jv) + &
3287               (veget_max(ji,jv) - veget(ji,jv))*precip_rain(ji)
3288       ENDDO
3289    END DO
3290       
3291    ! Precisol is currently the same as throughfall, save it for diagnostics
3292    throughfall(:,:) = precisol(:,:)
3293
3294    DO jv=1,nvm
3295       DO ji = 1, kjpindex
3296          IF (vegtot(ji).GT.min_sechiba) THEN
3297             precisol(ji,jv) = precisol(ji,jv)+tot_melt(ji)*veget_max(ji,jv)/vegtot(ji)
3298          ENDIF
3299       ENDDO
3300    END DO
3301    !   
3302    !
3303    !! 1.4 swap qsintveg to the new value
3304    !
3305    DO jv=2,nvm
3306       qsintveg(:,jv) = zqsintvegnew (:,jv)
3307    END DO
3308
3309    IF (printlev>=3) WRITE (numout,*) ' hydrol_canop done '
3310
3311  END SUBROUTINE hydrol_canop
3312
3313
3314!! ================================================================================================================================
3315!! SUBROUTINE   : hydrol_vegupd
3316!!
3317!>\BRIEF        Vegetation update   
3318!!
3319!! DESCRIPTION  :
3320!!   The vegetation cover has changed and we need to adapt the reservoir distribution
3321!!   and the distribution of plants on different soil types.
3322!!   You may note that this occurs after evaporation and so on have been computed. It is
3323!!   not a problem as a new vegetation fraction will start with humrel=0 and thus will have no
3324!!   evaporation. If this is not the case it should have been caught above.
3325!!
3326!! - 1 Update of vegetation is it needed?
3327!! - 2 calculate water mass that we have to redistribute
3328!! - 3 put it into reservoir of plant whose surface area has grown
3329!! - 4 Soil tile gestion
3330!! - 5 update the corresponding masks
3331!!
3332!! RECENT CHANGE(S) : None
3333!!
3334!! MAIN OUTPUT VARIABLE(S) :
3335!!
3336!! REFERENCE(S) :
3337!!
3338!! FLOWCHART    : None
3339!! \n
3340!_ ================================================================================================================================
3341!_ hydrol_vegupd
3342
3343  SUBROUTINE hydrol_vegupd(kjpindex, veget, veget_max, soiltile, qsintveg, frac_bare, drain_upd, runoff_upd)
3344
3345
3346    !! 0. Variable and parameter declaration
3347
3348    !! 0.1 Input variables
3349
3350    ! input scalar
3351    INTEGER(i_std), INTENT(in)                            :: kjpindex 
3352    ! input fields
3353    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(in)    :: veget            !! New vegetation map
3354    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)     :: veget_max        !! Max. fraction of vegetation type
3355    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)   :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
3356
3357    !! 0.2 Output variables
3358    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)    :: frac_bare        !! Fraction(of veget_max) of bare soil
3359                                                                              !! in each vegetation type
3360    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: drain_upd        !! Change in drainage due to decrease in vegtot
3361                                                                              !! on mc [kg/m2/dt]
3362    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: runoff_upd       !! Change in runoff due to decrease in vegtot
3363                                                                              !! on water2infilt[kg/m2/dt]
3364   
3365
3366    !! 0.3 Modified variables
3367
3368    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg         !! Water on old vegetation
3369
3370    !! 0.4 Local variables
3371
3372    INTEGER(i_std)                                 :: ji,jv,jst
3373
3374!_ ================================================================================================================================
3375
3376    !! 1 If veget has been updated at last time step (with LAND USE or DGVM),
3377    !! tmc and mc must be modified with respect to humtot conservation.
3378    CALL hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg, drain_upd, runoff_upd)
3379
3380
3381    ! Compute the masks for veget
3382   
3383    mask_veget(:,:) = 0
3384    mask_soiltile(:,:) = 0
3385   
3386    DO jst=1,nstm
3387       DO ji = 1, kjpindex
3388          IF(soiltile(ji,jst) .GT. min_sechiba) THEN
3389             mask_soiltile(ji,jst) = 1
3390          ENDIF
3391       END DO
3392    ENDDO
3393         
3394    DO jv = 1, nvm
3395       DO ji = 1, kjpindex
3396          IF(veget_max(ji,jv) .GT. min_sechiba) THEN
3397             mask_veget(ji,jv) = 1
3398          ENDIF
3399       END DO
3400    END DO
3401
3402    ! Compute vegetmax_soil
3403    vegetmax_soil(:,:,:) = zero
3404    DO jv = 1, nvm
3405       jst = pref_soil_veg(jv)
3406       DO ji=1,kjpindex
3407          ! for veget distribution used in sechiba via humrel
3408          IF (mask_soiltile(ji,jst).GT.0 .AND. vegtot(ji) > min_sechiba) THEN
3409             vegetmax_soil(ji,jv,jst)=veget_max(ji,jv)/soiltile(ji,jst)
3410          ENDIF
3411       ENDDO
3412    ENDDO
3413
3414    ! Calculate frac_bare (previosly done in slowproc_veget)
3415    DO ji =1, kjpindex
3416       IF( veget_max(ji,1) .GT. min_sechiba ) THEN
3417          frac_bare(ji,1) = un
3418       ELSE
3419          frac_bare(ji,1) = zero
3420       ENDIF
3421    ENDDO
3422    DO jv = 2, nvm
3423       DO ji =1, kjpindex
3424          IF( veget_max(ji,jv) .GT. min_sechiba ) THEN
3425             frac_bare(ji,jv) = un - veget(ji,jv)/veget_max(ji,jv)
3426          ELSE
3427             frac_bare(ji,jv) = zero
3428          ENDIF
3429       ENDDO
3430    ENDDO
3431
3432    ! Tout dans cette routine est maintenant certainement obsolete (veget_max etant constant) en dehors des lignes
3433    ! suivantes et le calcul de frac_bare:
3434    frac_bare_ns(:,:) = zero
3435    DO jst = 1, nstm
3436       DO jv = 1, nvm
3437          DO ji =1, kjpindex
3438             IF(vegtot(ji) .GT. min_sechiba) THEN
3439                frac_bare_ns(ji,jst) = frac_bare_ns(ji,jst) + vegetmax_soil(ji,jv,jst) * frac_bare(ji,jv) / vegtot(ji)
3440             ENDIF
3441          END DO
3442       ENDDO
3443    END DO
3444   
3445    IF (printlev>=3) WRITE (numout,*) ' hydrol_vegupd done '
3446
3447  END SUBROUTINE hydrol_vegupd
3448
3449
3450!! ================================================================================================================================
3451!! SUBROUTINE   : hydrol_flood
3452!!
3453!>\BRIEF        This routine computes the evolution of the surface reservoir (floodplain). 
3454!!
3455!! DESCRIPTION  :
3456!! - 1 Take out vevapflo from the reservoir and transfer the remaining to subsinksoil
3457!! - 2 Compute the total flux from floodplain floodout (transfered to routing)
3458!! - 3 Discriminate between precip over land and over floodplain
3459!!
3460!! RECENT CHANGE(S) : None
3461!!
3462!! MAIN OUTPUT VARIABLE(S) :
3463!!
3464!! REFERENCE(S) :
3465!!
3466!! FLOWCHART    : None
3467!! \n
3468!_ ================================================================================================================================
3469!_ hydrol_flood
3470
3471  SUBROUTINE hydrol_flood (kjpindex, vevapflo, flood_frac, flood_res, floodout)
3472
3473    !! 0. Variable and parameter declaration
3474
3475    !! 0.1 Input variables
3476
3477    ! input scalar
3478    INTEGER(i_std), INTENT(in)                               :: kjpindex         !!
3479    ! input fields
3480    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: flood_frac       !! Fraction of floodplains in grid box
3481
3482    !! 0.2 Output variables
3483
3484    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: floodout         !! Flux to take out from floodplains
3485
3486    !! 0.3 Modified variables
3487
3488    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: flood_res        !! Floodplains reservoir estimate
3489    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapflo         !! Evaporation over floodplains
3490
3491    !! 0.4 Local variables
3492
3493    INTEGER(i_std)                                           :: ji, jv           !! Indices
3494    REAL(r_std), DIMENSION (kjpindex)                        :: temp             !!
3495
3496!_ ================================================================================================================================
3497    !-
3498    !! 1 Take out vevapflo from the reservoir and transfer the remaining to subsinksoil
3499    !-
3500    DO ji = 1,kjpindex
3501       temp(ji) = MIN(flood_res(ji), vevapflo(ji))
3502    ENDDO
3503    DO ji = 1,kjpindex
3504       flood_res(ji) = flood_res(ji) - temp(ji)
3505       subsinksoil(ji) = subsinksoil(ji) + vevapflo(ji) - temp(ji)
3506       vevapflo(ji) = temp(ji)
3507    ENDDO
3508
3509    !-
3510    !! 2 Compute the total flux from floodplain floodout (transfered to routing)
3511    !-
3512    DO ji = 1,kjpindex
3513       floodout(ji) = vevapflo(ji) - flood_frac(ji) * SUM(precisol(ji,:))
3514    ENDDO
3515
3516    !-
3517    !! 3 Discriminate between precip over land and over floodplain
3518    !-
3519    DO jv=1, nvm
3520       DO ji = 1,kjpindex
3521          precisol(ji,jv) = precisol(ji,jv) * (1 - flood_frac(ji))
3522       ENDDO
3523    ENDDO 
3524
3525    IF (printlev>=3) WRITE (numout,*) ' hydrol_flood done'
3526
3527  END SUBROUTINE hydrol_flood
3528
3529!! ================================================================================================================================
3530!! SUBROUTINE   : hydrol_soil
3531!!
3532!>\BRIEF        This routine computes soil processes with CWRR scheme (Richards equation solved by finite differences).
3533!! Note that the water fluxes are in kg/m2/dt_sechiba.
3534!!
3535!! DESCRIPTION  :
3536!! 0. Initialisation, and split 2d variables to 3d variables, per soil tile
3537!! -- START MAIN LOOP (prognostic loop to update mc and mcl) OVER SOILTILES
3538!! 1. FIRSTLY, WE CHANGE MC BASED ON EXTERNAL FLUXES, ALL APPLIED AT THE SOIL SURFACE
3539!! 1.1 Reduces water2infilt and water2extract to their difference
3540!! 1.2 To remove water2extract (including bare soilevaporation) from top layer
3541!! 1.3 Infiltration
3542!! 1.4 Reinfiltration of surface runoff : compute temporary surface water and extract from runoff
3543!! 2. SECONDLY, WE UPDATE MC FROM DIFFUSION, INCLUDING DRAINAGE AND ROOTSINK
3544!!    This will act on mcl (liquid water content) only
3545!! 2.1 K and D are recomputed after infiltration
3546!! 2.2 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
3547!! 2.3 We define mcl (liquid water content) based on mc and profil_froz_hydro_ns
3548!! 2.4 We calculate the total SM at the beginning of the routine tridiag for water conservation check
3549!! 2.5 Defining where diffusion is solved : everywhere
3550!! 2.6 We define the system of linear equations for mcl redistribution
3551!! 2.7 Solves diffusion equations
3552!! 2.8 Computes drainage = bottom boundary condition, consistent with rhs(ji,jsl=nslm)
3553!! 2.9 For water conservation check during redistribution, we calculate the total liquid SM
3554!!     at the end of the routine tridiag, and we compare the difference with the flux...
3555!! 3. AFTER DIFFUSION/REDISTRIBUTION
3556!! 3.1 Updating mc, as all the following checks against saturation will compare mc to mcs
3557!! 3.2 Correct here the possible over-saturation values (subroutine hydrol_soil_smooth_over_mcs2 acts on mc)
3558!!     Here hydrol_soil_smooth_over_mcs2 discard all excess as ru_corr_ns, oriented to either ru_ns or dr_ns
3559!! 3.3 Negative runoff is reported to drainage
3560!! 3.4 Optional block to force saturation below zwt_force
3561!! 3.5 Diagnosing the effective water table depth
3562!! 3.6 Diagnose under_mcr to adapt water stress calculation below
3563!! 4. At the end of the prognostic calculations, we recompute important moisture variables
3564!! 4.1 Total soil moisture content (water2infilt added below)
3565!! 4.2 mcl is a module variable; we update it here for calculating bare soil evaporation,
3566!! 5. Optional check of the water balance of soil column (if check_cwrr)
3567!! 5.1 Computation of the vertical water fluxes
3568!! 6. SM DIAGNOSTICS FOR OTHER ROUTINES, MODULES, OR NEXT STEP
3569!! 6.1 Total soil moisture, soil moisture at litter levels, soil wetness, us, humrelv, vesgtressv
3570!! 6.2 We need to turn off evaporation when is_under_mcr
3571!! 6.3 Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in thermosoil
3572!! 6.4 The hydraulic conductivities exported here are the ones used in the diffusion/redistribution
3573!! -- ENDING THE MAIN LOOP ON SOILTILES
3574!! 7. Summing 3d variables into 2d variables
3575!! 8. XIOS export of local variables, including water conservation checks
3576!! 9. COMPUTING EVAP_BARE_LIM_NS FOR NEXT TIME STEP, WITH A LOOP ON SOILTILES
3577!!    The principle is to run a dummy integration of the water redistribution scheme
3578!!    to check if the SM profile can sustain a potential evaporation.
3579!!    If not, the dummy integration is redone from the SM profile of the end of the normal integration,
3580!!    with a boundary condition leading to a very severe water limitation: mc(1)=mcr
3581!! 10. evap_bar_lim is the grid-cell scale beta
3582!!
3583!! RECENT CHANGE(S) : 2016 by A. Ducharne
3584!!
3585!! MAIN OUTPUT VARIABLE(S) :
3586!!
3587!! REFERENCE(S) :
3588!!
3589!! FLOWCHART    : None
3590!! \n
3591!_ ================================================================================================================================
3592!_ hydrol_soil
3593  SUBROUTINE hydrol_soil (ks, nvan, avan, mcr, mcs, mcfc, mcw, &
3594       kjpindex, veget_max, soiltile, njsc, reinf_slope, &
3595       & transpir, vevapnu, evapot, evapot_penm, runoff, drainage, &
3596       & returnflow, reinfiltration, irrigation, &
3597       & tot_melt, evap_bare_lim, evap_bare_lim_ns, shumdiag, shumdiag_perma,&
3598       & k_litt, litterhumdiag, humrel,vegstress, drysoil_frac, &
3599       & stempdiag,snow, &
3600       & snowdz, tot_bare_soil, u, v, tq_cdrag, mc_layh, mcl_layh)
3601    !
3602    ! interface description
3603
3604    !! 0. Variable and parameter declaration
3605
3606    !! 0.1 Input variables
3607   
3608    INTEGER(i_std), INTENT(in)                               :: kjpindex 
3609    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: veget_max        !! Map of max vegetation types [-]
3610    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc             !! Index of the dominant soil textural class
3611                                                                                 !!   in the grid cell (1-nscm, unitless)
3612   
3613    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: ks               !! Hydraulic conductivity at saturation (mm {-1})
3614    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: nvan             !! Van Genuchten coeficients n (unitless)
3615    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: avan             !! Van Genuchten coeficients a (mm-1})
3616    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
3617    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
3618    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
3619    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
3620   
3621    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
3622    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: transpir         !! Transpiration 
3623                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3624    REAL(r_std), DIMENSION (kjpindex), INTENT (in)           :: reinf_slope      !! Fraction of surface runoff that reinfiltrates
3625                                                                                 !!  (unitless, [0-1])
3626    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow       !! Water returning to the soil from the bottom
3627                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3628    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: reinfiltration   !! Water returning to the top of the soil
3629                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3630    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: irrigation       !! Irrigation
3631                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3632    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot           !! Potential evaporation
3633                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3634    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot_penm      !! Potential evaporation "Penman" (Milly's correction)
3635                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3636    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_melt         !! Total melt from snow and ice
3637                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3638    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in)       :: stempdiag        !! Diagnostic temp profile from thermosoil
3639    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: snow             !! Snow mass
3640                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3641    REAL(r_std), DIMENSION (kjpindex,nsnow),INTENT(in)       :: snowdz           !! Snow depth (m)
3642    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_bare_soil    !! Total evaporating bare soil fraction
3643                                                                                 !!  (unitless, [0-1])
3644    REAL(r_std),DIMENSION (kjpindex), INTENT(in)             :: u,v              !! Horizontal wind speed
3645    REAL(r_std),DIMENSION (kjpindex), INTENT(in)             :: tq_cdrag         !! Surface drag coefficient
3646
3647    !! 0.2 Output variables
3648
3649    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: runoff           !! Surface runoff
3650                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3651    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drainage         !! Drainage
3652                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3653    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: evap_bare_lim    !! Limitation factor (beta) for bare soil evaporation 
3654                                                                                 !! on each soil column (unitless, [0-1])
3655    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(out)      :: evap_bare_lim_ns !! Limitation factor (beta) for bare soil evaporation 
3656                                                                                 !! on each soil column (unitless, [0-1])
3657    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: shumdiag         !! Relative soil moisture in each diag soil layer
3658                                                                                 !! with respect to (mcfc-mcw) (unitless, [0-1])
3659    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: shumdiag_perma   !! Percent of porosity filled with water (mc/mcs)
3660                                                                                 !! in each diag soil layer (for the thermal computations)
3661                                                                                 !! (unitless, [0-1])
3662    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: k_litt           !! Litter approximated hydraulic conductivity
3663                                                                                 !!  @tex $(mm d^{-1})$ @endtex
3664    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: litterhumdiag    !! Mean of soil_wet_litter across soil tiles
3665                                                                                 !! (unitless, [0-1])
3666    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(out)      :: vegstress        !! Veg. moisture stress (only for vegetation
3667                                                                                 !! growth) (unitless, [0-1])
3668    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: drysoil_frac     !! Function of the litter humidity
3669    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: mc_layh          !! Volumetric water content (liquid + ice) for each soil layer
3670                                                                                 !! averaged over the mesh (for thermosoil)
3671                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
3672    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: mcl_layh         !! Volumetric liquid water content for each soil layer
3673                                                                                 !! averaged over the mesh (for thermosoil)
3674                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
3675    !! 0.3 Modified variables
3676
3677    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapnu          !! Bare soil evaporation
3678                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3679    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (inout)    :: humrel           !! Relative humidity (0-1, dimensionless)
3680
3681    !! 0.4 Local variables
3682
3683    INTEGER(i_std)                                 :: ji, jv, jsl, jst           !! Indices
3684    REAL(r_std), PARAMETER                         :: frac_mcs = 0.66            !! Temporary depth
3685    REAL(r_std), DIMENSION(kjpindex)               :: temp                       !! Temporary value for fluxes
3686    REAL(r_std), DIMENSION(kjpindex)               :: tmcold                     !! Total SM at beginning of hydrol_soil (kg/m2)
3687    REAL(r_std), DIMENSION(kjpindex)               :: tmcint                     !! Ancillary total SM (kg/m2)
3688    REAL(r_std), DIMENSION(kjpindex,nslm)          :: mcint                      !! To save mc values for future use
3689    REAL(r_std), DIMENSION(kjpindex,nslm)          :: mclint                     !! To save mcl values for future use
3690    LOGICAL, DIMENSION(kjpindex,nstm)              :: is_under_mcr               !! Identifies under residual soil moisture points
3691    LOGICAL, DIMENSION(kjpindex)                   :: is_over_mcs                !! Identifies over saturated soil moisture points
3692    REAL(r_std), DIMENSION(kjpindex)               :: deltahum,diff              !!
3693    LOGICAL(r_std), DIMENSION(kjpindex)            :: test                       !!
3694    REAL(r_std), DIMENSION(kjpindex)               :: water2extract              !! Water flux to be extracted at the soil surface
3695                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3696    REAL(r_std), DIMENSION(kjpindex)               :: returnflow_soil            !! Water from the routing back to the bottom of
3697                                                                                 !! the soil @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3698    REAL(r_std), DIMENSION(kjpindex)               :: reinfiltration_soil        !! Water from the routing back to the top of the
3699                                                                                 !! soil @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3700    REAL(r_std), DIMENSION(kjpindex)               :: irrigation_soil            !! Water from irrigation returning to soil moisture
3701                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3702    REAL(r_std), DIMENSION(kjpindex)               :: flux_infilt                !! Water to infiltrate
3703                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3704    REAL(r_std), DIMENSION(kjpindex)               :: flux_bottom                !! Flux at bottom of the soil column
3705                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3706    REAL(r_std), DIMENSION(kjpindex)               :: flux_top                   !! Flux at top of the soil column (for bare soil evap)
3707                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3708    REAL(r_std), DIMENSION (kjpindex,nstm)         :: qinfilt_ns                 !! Effective infiltration flux per soil tile
3709                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
3710    REAL(r_std), DIMENSION (kjpindex)              :: qinfilt                    !! Effective infiltration flux 
3711                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3712    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_infilt_ns               !! Surface runoff from hydrol_soil_infilt per soil tile
3713                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
3714    REAL(r_std), DIMENSION (kjpindex)              :: ru_infilt                  !! Surface runoff from hydrol_soil_infilt
3715                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3716    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_corr_ns                 !! Surface runoff produced to correct excess per soil tile
3717                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3718    REAL(r_std), DIMENSION (kjpindex)              :: ru_corr                    !! Surface runoff produced to correct excess
3719                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex 
3720    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_corr2_ns                !! Correction of negative surface runoff per soil tile
3721                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3722    REAL(r_std), DIMENSION (kjpindex)              :: ru_corr2                   !! Correction of negative surface runoff
3723                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3724    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_corr_ns                 !! Drainage produced to correct excess
3725                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3726    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_corrnum_ns              !! Drainage produced to correct numerical errors in tridiag
3727                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
3728    REAL(r_std), DIMENSION (kjpindex)              :: dr_corr                    !! Drainage produced to correct excess
3729                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3730    REAL(r_std), DIMENSION (kjpindex)              :: dr_corrnum                 !! Drainage produced to correct numerical errors in tridiag
3731                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
3732    REAL(r_std), DIMENSION (kjpindex,nslm)         :: dmc                        !! Delta mc when forcing saturation (zwt_force)
3733                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
3734    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_force_ns                !! Delta drainage when forcing saturation (zwt_force)
3735                                                                                 !!  per soil tile  @tex $(kg m^{-2})$ @endtex
3736    REAL(r_std), DIMENSION (kjpindex)              :: dr_force                   !! Delta drainage when forcing saturation (zwt_force)
3737                                                                                 !!  @tex $(kg m^{-2})$ @endtex 
3738    REAL(r_std), DIMENSION (kjpindex,nstm)         :: wtd_ns                     !! Effective water table depth (m)
3739    REAL(r_std), DIMENSION (kjpindex)              :: wtd                        !! Mean water table depth in the grid-cell (m)
3740
3741    ! For the calculation of soil_wet_ns and us/humrel/vegstress
3742    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sm                         !! Soil moisture of each layer (liquid phase)
3743                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3744    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smt                        !! Soil moisture of each layer (liquid+solid phase)
3745                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3746    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smw                        !! Soil moisture of each layer at wilting point
3747                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3748    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smf                        !! Soil moisture of each layer at field capacity
3749                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
3750    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sms                        !! Soil moisture of each layer at saturation
3751                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3752    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sm_nostress                !! Soil moisture of each layer at which us reaches 1
3753                                                                                 !!  @tex $(kg m^{-2})$ @endtex
3754    ! For water conservation checks (in mm/dtstep unless otherwise mentioned)
3755    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_infilt_ns             !! Water conservation diagnostic at routine scale
3756    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check1_ns                   !! Water conservation diagnostic at routine scale
3757    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_tr_ns                 !! Water conservation diagnostic at routine scale
3758    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_over_ns               !! Water conservation diagnostic at routine scale
3759    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_under_ns              !! Water conservation diagnostic at routine scale
3760    REAL(r_std), DIMENSION(kjpindex)               :: tmci                        !! Total soil moisture at beginning of routine (kg/m2)
3761    REAL(r_std), DIMENSION(kjpindex)               :: tmcf                        !! Total soil moisture at end of routine (kg/m2)
3762    REAL(r_std), DIMENSION(kjpindex)               :: diag_tr                     !! Transpiration flux
3763    REAL(r_std), DIMENSION (kjpindex)              :: check_infilt                !! Water conservation diagnostic at routine scale
3764    REAL(r_std), DIMENSION (kjpindex)              :: check1                      !! Water conservation diagnostic at routine scale
3765    REAL(r_std), DIMENSION (kjpindex)              :: check_tr                    !! Water conservation diagnostic at routine scale
3766    REAL(r_std), DIMENSION (kjpindex)              :: check_over                  !! Water conservation diagnostic at routine scale
3767    REAL(r_std), DIMENSION (kjpindex)              :: check_under                 !! Water conservation diagnostic at routine scale
3768
3769    ! Diagnostic of the vertical soil water fluxes 
3770    REAL(r_std), DIMENSION (kjpindex,nslm)         :: qflux                       !! Local upward flux into soil layer
3771                                                                                  !! from lower interface
3772                                                                                  !!  @tex $(kg m^{-2})$ @endtex
3773    REAL(r_std), DIMENSION (kjpindex)              :: check_top                   !! Water budget residu in top soil layer
3774                                                                                  !!  @tex $(kg m^{-2})$ @endtex
3775
3776    ! Variables for calculation of a soil resistance, option do_rsoil (following the formulation of Sellers et al 1992, implemented in Oleson et al. 2008)
3777    REAL(r_std)                                    :: speed                      !! magnitude of wind speed required for Aerodynamic resistance
3778    REAL(r_std)                                    :: ra                         !! diagnosed aerodynamic resistance
3779    REAL(r_std), DIMENSION(kjpindex)               :: mc_rel                     !! first layer relative soil moisture, required for rsoil
3780    REAL(r_std), DIMENSION(kjpindex)               :: evap_soil                  !! soil evaporation from Oleson et al 2008
3781    REAL(r_std), DIMENSION(kjpindex,nstm)          :: r_soil_ns                  !! soil resistance from Oleson et al 2008
3782    REAL(r_std), DIMENSION(kjpindex)               :: r_soil                     !! soil resistance from Oleson et al 2008
3783    REAL(r_std), DIMENSION(kjpindex)               :: tmcs_litter                !! Saturated soil moisture in the 4 "litter" soil layers
3784    REAL(r_std), DIMENSION(nslm)                   :: nroot_tmp                  !! Temporary variable to calculate the nroot
3785
3786    ! For CMIP6 and SP-MIP : ksat and matric pressure head psi(theta)
3787    REAL(r_std)                                    :: mc_ratio, mvg, avg
3788    REAL(r_std)                                    :: psi                        !! Matric head (per soil layer and soil tile) [mm=kg/m2]
3789    REAL(r_std), DIMENSION (kjpindex,nslm)         :: psi_moy                    !! Mean matric head per soil layer [mm=kg/m2] 
3790    REAL(r_std), DIMENSION (kjpindex,nslm)         :: ksat                       !! Saturated hydraulic conductivity at each node (mm/d) 
3791
3792!_ ================================================================================================================================
3793
3794    !! 0.1 Arrays with DIMENSION(kjpindex)
3795   
3796    returnflow_soil(:) = zero
3797    reinfiltration_soil(:) = zero
3798    irrigation_soil(:) = zero
3799    qflux_ns(:,:,:) = zero
3800    mc_layh(:,:) = zero ! for thermosoil
3801    mcl_layh(:,:) = zero ! for thermosoil
3802    kk(:,:,:) = zero
3803    kk_moy(:,:) = zero
3804    undermcr(:) = zero ! needs to be initialized outside from jst loop
3805    ksat(:,:) = zero
3806    psi_moy(:,:) = zero
3807
3808    IF (ok_freeze_cwrr) THEN
3809       
3810       ! 0.1 Calculate the temperature and fozen fraction at the hydrological levels
3811       
3812       ! Calculates profil_froz_hydro_ns as a function of stempdiag and mc if ok_thermodynamical_freezing
3813       ! These values will be kept till the end of the prognostic loop
3814       DO jst=1,nstm
3815          CALL hydrol_soil_froz(nvan, avan, mcr, mcs, kjpindex,jst,njsc,stempdiag)
3816       ENDDO
3817
3818    ELSE
3819 
3820       profil_froz_hydro_ns(:,:,:) = zero
3821             
3822    ENDIF
3823   
3824    !! 0.2 Split 2d variables to 3d variables, per soil tile
3825    !  Here, the evaporative fluxes are distributed over the soiltiles as a function of the
3826    !    corresponding control factors; they are normalized to vegtot
3827    !  At step 7, the reverse transformation is used for the fluxes produced in hydrol_soil
3828    !    flux_cell(ji)=sum(flux_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji))
3829    CALL hydrol_split_soil (kjpindex, veget_max, soiltile, vevapnu, transpir, humrel, &
3830         evap_bare_lim, evap_bare_lim_ns, tot_bare_soil)
3831   
3832    !! 0.3 Common variables related to routing, with all return flow applied to the soil surface
3833    ! The fluxes coming from the routing are uniformly splitted into the soiltiles,
3834    !    but are normalized to vegtot like the above fluxes:
3835    !            flux_ns(ji,jst)=flux_cell(ji)/vegtot(ji)
3836    ! It is the case for : irrigation_soil(ji) and reinfiltration_soil(ji) cf below
3837    ! It is also the case for subsinksoil(ji), which is divided by (1-tot_frac_nobio) at creation in hydrol_snow
3838    ! AD16*** The transformation in 0.2 and 0.3 is likely to induce conservation problems
3839    !         when tot_frac_nobio NE 0, since sum(soiltile) NE vegtot in this case
3840   
3841    DO ji=1,kjpindex
3842       IF(vegtot(ji).GT.min_sechiba) THEN
3843          ! returnflow_soil is assumed to enter from the bottom, but it is not possible with CWRR
3844          returnflow_soil(ji) = zero
3845          reinfiltration_soil(ji) = (returnflow(ji) + reinfiltration(ji))/vegtot(ji)
3846          irrigation_soil(ji) = irrigation(ji)/vegtot(ji)
3847       ELSE
3848          returnflow_soil(ji) = zero
3849          reinfiltration_soil(ji) = zero
3850          irrigation_soil(ji) = zero
3851       ENDIF
3852    ENDDO       
3853   
3854    !! -- START MAIN LOOP (prognostic loop to update mc and mcl) OVER SOILTILES
3855    !!    The called subroutines work on arrays with DIMENSION(kjpindex),
3856    !!    recursively used for each soiltile jst
3857   
3858    DO jst = 1,nstm
3859
3860       is_under_mcr(:,jst) = .FALSE.
3861       is_over_mcs(:) = .FALSE.
3862       
3863       !! 0.4. Keep initial values for future check-up
3864       
3865       ! Total moisture content (including water2infilt) is saved for balance checks at the end
3866       ! In hydrol_tmc_update, tmc is increased by water2infilt(ji,jst), but mc is not modified !
3867       tmcold(:) = tmc(:,jst)
3868       
3869       ! The value of mc is kept in mcint (nstm dimension removed), in case needed for water balance checks
3870       DO jsl = 1, nslm
3871          DO ji = 1, kjpindex
3872             mcint(ji,jsl) = mask_soiltile(ji,jst) * mc(ji,jsl,jst)
3873          ENDDO
3874       ENDDO
3875       !
3876       ! Initial total moisture content : tmcint does not include water2infilt, contrarily to tmcold
3877       DO ji = 1, kjpindex
3878          tmcint(ji) = dz(2) * ( trois*mcint(ji,1) + mcint(ji,2) )/huit 
3879       ENDDO
3880       DO jsl = 2,nslm-1
3881          DO ji = 1, kjpindex
3882             tmcint(ji) = tmcint(ji) + dz(jsl) &
3883                  & * (trois*mcint(ji,jsl)+mcint(ji,jsl-1))/huit &
3884                  & + dz(jsl+1) * (trois*mcint(ji,jsl)+mcint(ji,jsl+1))/huit
3885          ENDDO
3886       ENDDO
3887       DO ji = 1, kjpindex
3888          tmcint(ji) = tmcint(ji) + dz(nslm) &
3889               & * (trois * mcint(ji,nslm) + mcint(ji,nslm-1))/huit
3890       ENDDO
3891
3892       !! 1. FIRSTLY, WE CHANGE MC BASED ON EXTERNAL FLUXES, ALL APPLIED AT THE SOIL SURFACE
3893       !!   Input = water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) + precisol_ns(ji,jst)
3894       !!      - negative evaporation fluxes (MIN(ae_ns(ji,jst),zero)+ MIN(subsinksoil(ji),zero))
3895       !!   Output = MAX(ae_ns(ji,jst),zero) + subsinksoil(ji) = positive evaporation flux = water2extract
3896       ! In practice, negative subsinksoil(ji) is not possible
3897
3898       !! 1.1 Reduces water2infilt and water2extract to their difference
3899
3900       ! Compares water2infilt and water2extract to keep only difference
3901       ! Here, temp is used as a temporary variable to store the min of water to infiltrate vs evaporate
3902       DO ji = 1, kjpindex
3903          temp(ji) = MIN(water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) &
3904                         - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst), &
3905                           MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) )
3906       ENDDO
3907
3908       ! The water to infiltrate at the soil surface is either 0, or the difference to what has to be evaporated
3909       !   - the initial water2infilt (right hand side) results from qsintveg changes with vegetation updates
3910       !   - irrigation_soil is the input flux to the soil surface from irrigation
3911       !   - reinfiltration_soil is the input flux to the soil surface from routing 'including returnflow)
3912       !   - eventually, water2infilt holds all fluxes to the soil surface except precisol (reduced by water2extract)
3913       DO ji = 1, kjpindex
3914          water2infilt(ji,jst) = water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) &
3915                - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst) &
3916                - temp(ji) 
3917       ENDDO       
3918             
3919       ! The water to evaporate from the sol surface is either the difference to what has to be infiltrated, or 0
3920       !   - subsinksoil is the residual from sublimation is the snowpack is not sufficient
3921       !   - how are the negative values of ae_ns taken into account ???
3922       DO ji = 1, kjpindex
3923          water2extract(ji) =  MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) - temp(ji) 
3924       ENDDO
3925
3926       ! Here we acknowledge that subsinksoil is part of ae_ns, but ae_ns is not used further
3927       ae_ns(:,jst) = ae_ns(:,jst) + subsinksoil(:) 
3928
3929       !! 1.2 To remove water2extract (including bare soil) from top layer
3930       flux_top(:) = water2extract(:)
3931
3932       !! 1.3 Infiltration
3933
3934       !! Definition of flux_infilt
3935       DO ji = 1, kjpindex
3936          ! Initialise the flux to be infiltrated 
3937          flux_infilt(ji) = water2infilt(ji,jst) 
3938       ENDDO
3939       
3940       !! K and D are computed for the profile of mc before infiltration
3941       !! They depend on the fraction of soil ice, given by profil_froz_hydro_ns
3942       CALL hydrol_soil_coef(mcr, mcs, kjpindex,jst,njsc)
3943
3944       !! Infiltration and surface runoff are computed
3945       !! Infiltration stems from comparing liquid water2infilt to initial total mc (liquid+ice)
3946       !! The conductivity comes from hydrol_soil_coef and relates to the liquid phase only
3947       !  This seems consistent with ok_freeze
3948       CALL hydrol_soil_infilt(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, jst, njsc, flux_infilt,  stempdiag, &
3949                               qinfilt_ns, ru_infilt_ns, check_infilt_ns)
3950       ru_ns(:,jst) = ru_infilt_ns(:,jst) 
3951
3952       !! 1.4 Reinfiltration of surface runoff : compute temporary surface water and extract from runoff
3953       ! Evrything here is liquid
3954       ! RK: water2infilt is both a volume for future reinfiltration (in mm) and a correction term for surface runoff (in mm/dt_sechiba)
3955       IF ( .NOT. doponds ) THEN ! this is the general case...
3956          DO ji = 1, kjpindex
3957             water2infilt(ji,jst) = reinf_slope(ji) * ru_ns(ji,jst)
3958          ENDDO
3959       ELSE
3960          DO ji = 1, kjpindex           
3961             water2infilt(ji,jst) = zero
3962          ENDDO
3963       ENDIF
3964       !
3965       DO ji = 1, kjpindex           
3966          ru_ns(ji,jst) = ru_ns(ji,jst) - water2infilt(ji,jst)
3967       END DO
3968
3969       !! 2. SECONDLY, WE UPDATE MC FROM DIFFUSION, INCLUDING DRAINAGE AND ROOTSINK
3970       !!    This will act on mcl only
3971       
3972       !! 2.1 K and D are recomputed after infiltration
3973       !! They depend on the fraction of soil ice, still given by profil_froz_hydro_ns
3974       CALL hydrol_soil_coef(mcr, mcs,kjpindex,jst,njsc)
3975 
3976       !! 2.2 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
3977       !! This process will further act on mcl only, based on a, b, d from hydrol_soil_coef
3978       CALL hydrol_soil_setup(kjpindex,jst)
3979
3980       !! 2.3 We define mcl (liquid water content) based on mc and profil_froz_hydro_ns
3981       DO jsl = 1, nslm
3982          DO ji =1, kjpindex
3983             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(ji) + &
3984                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(ji)) )
3985             ! we always have mcl<=mc
3986             ! if mc>mcr, then mcl>mcr; if mc=mcr,mcl=mcr; if mc<mcr, then mcl<mcr
3987             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
3988          ENDDO
3989       ENDDO
3990
3991       ! The value of mcl is kept in mclint (nstm dimension removed), used in the flux computation after diffusion
3992       DO jsl = 1, nslm
3993          DO ji = 1, kjpindex
3994             mclint(ji,jsl) = mask_soiltile(ji,jst) * mcl(ji,jsl,jst)
3995          ENDDO
3996       ENDDO
3997
3998       !! 2.3bis Diagnostic of the matric potential used for redistribution by Richards/tridiag (in m)
3999       !  We use VG relationship giving psi as a function of mc (mcl in our case)
4000       !  With patches against numerical pbs when (mc_ratio - un) becomes very slightly negative (gives NaN)
4001       !  or if psi become too strongly negative (pbs with xios output)
4002       DO jsl=1, nslm
4003          DO ji = 1, kjpindex
4004             IF (soiltile(ji,jst) .GT. zero) THEN
4005                mvg = un - un / nvan_mod_tab(jsl,ji)
4006                avg = avan_mod_tab(jsl,ji)*1000. ! to convert in m-1
4007                mc_ratio = MAX( 10.**(-14*mvg), (mcl(ji,jsl,jst) - mcr(ji))/(mcs(ji) - mcr(ji)) )**(-un/mvg)
4008                psi = - MAX(zero,(mc_ratio - un))**(un/nvan_mod_tab(jsl,ji)) / avg ! in m
4009                psi_moy(ji,jsl) = psi_moy(ji,jsl) + soiltile(ji,jst) * psi ! average across soil tiles
4010             ENDIF
4011          ENDDO
4012       ENDDO
4013
4014       !! 2.4 We calculate the total SM at the beginning of the routine tridiag for water conservation check
4015       !  (on mcl only, since the diffusion only modifies mcl)
4016       tmci(:) = dz(2) * ( trois*mcl(:,1,jst) + mcl(:,2,jst) )/huit
4017       DO jsl = 2,nslm-1
4018          tmci(:) = tmci(:) + dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
4019               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
4020       ENDDO
4021       tmci(:) = tmci(:) + dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit
4022
4023       !! 2.5 Defining where diffusion is solved : everywhere
4024       !! Since mc>mcs is not possible after infiltration, and we accept that mc<mcr
4025       !! (corrected later by shutting off all evaporative fluxes in this case)
4026       !  Nothing is done if resolv=F
4027       resolv(:) = (mask_soiltile(:,jst) .GT. 0)
4028
4029       !! 2.6 We define the system of linear equations for mcl redistribution,
4030       !! based on the matrix coefficients from hydrol_soil_setup
4031       !! following the PhD thesis of de Rosnay (1999), p155-157
4032       !! The bare soil evaporation (subtracted from infiltration) is used directly as flux_top
4033       ! rhs for right-hand side term; fp for f'; gp for g'; ep for e'; with flux=0 !
4034       
4035       !- First layer
4036       DO ji = 1, kjpindex
4037          tmat(ji,1,1) = zero
4038          tmat(ji,1,2) = f(ji,1)
4039          tmat(ji,1,3) = g1(ji,1)
4040          rhs(ji,1)    = fp(ji,1) * mcl(ji,1,jst) + gp(ji,1)*mcl(ji,2,jst) &
4041               &  - flux_top(ji) - (b(ji,1)+b(ji,2))/deux *(dt_sechiba/one_day) - rootsink(ji,1,jst)
4042       ENDDO
4043       !- soil body
4044       DO jsl=2, nslm-1
4045          DO ji = 1, kjpindex
4046             tmat(ji,jsl,1) = e(ji,jsl)
4047             tmat(ji,jsl,2) = f(ji,jsl)
4048             tmat(ji,jsl,3) = g1(ji,jsl)
4049             rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
4050                  & +  gp(ji,jsl) * mcl(ji,jsl+1,jst) & 
4051                  & + (b(ji,jsl-1) - b(ji,jsl+1)) * (dt_sechiba/one_day) / deux & 
4052                  & - rootsink(ji,jsl,jst) 
4053          ENDDO
4054       ENDDO       
4055       !- Last layer, including drainage
4056       DO ji = 1, kjpindex
4057          jsl=nslm
4058          tmat(ji,jsl,1) = e(ji,jsl)
4059          tmat(ji,jsl,2) = f(ji,jsl)
4060          tmat(ji,jsl,3) = zero
4061          rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
4062               & + (b(ji,jsl-1) + b(ji,jsl)*(un-deux*free_drain_coef(ji,jst))) * (dt_sechiba/one_day) / deux &
4063               & - rootsink(ji,jsl,jst)
4064       ENDDO
4065       !- Store the equations in case needed again
4066       DO jsl=1,nslm
4067          DO ji = 1, kjpindex
4068             srhs(ji,jsl) = rhs(ji,jsl)
4069             stmat(ji,jsl,1) = tmat(ji,jsl,1)
4070             stmat(ji,jsl,2) = tmat(ji,jsl,2)
4071             stmat(ji,jsl,3) = tmat(ji,jsl,3) 
4072          ENDDO
4073       ENDDO
4074       
4075       !! 2.7 Solves diffusion equations, but only in grid-cells where resolv is true, i.e. everywhere (cf 2.2)
4076       !!     The result is an updated mcl profile
4077
4078       CALL hydrol_soil_tridiag(kjpindex,jst)
4079
4080       !! 2.8 Computes drainage = bottom boundary condition, consistent with rhs(ji,jsl=nslm)
4081       ! dr_ns in mm/dt_sechiba, from k in mm/d
4082       ! This should be done where resolv=T, like tridiag (drainage is part of the linear system !)
4083       DO ji = 1, kjpindex
4084          IF (resolv(ji)) THEN
4085             dr_ns(ji,jst) = mask_soiltile(ji,jst)*k(ji,nslm)*free_drain_coef(ji,jst) * (dt_sechiba/one_day)
4086          ELSE
4087             dr_ns(ji,jst) = zero
4088          ENDIF
4089       ENDDO
4090
4091       !! 2.9 For water conservation check during redistribution AND CORRECTION,
4092       !!     we calculate the total liquid SM at the end of the routine tridiag
4093       tmcf(:) = dz(2) * ( trois*mcl(:,1,jst) + mcl(:,2,jst) )/huit
4094       DO jsl = 2,nslm-1
4095          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
4096               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
4097       ENDDO
4098       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit
4099         
4100       !! And we compare the difference with the flux...
4101       ! Normally, tcmf=tmci-flux_top(ji)-transpir-dr_ns
4102       DO ji=1,kjpindex
4103          diag_tr(ji)=SUM(rootsink(ji,:,jst))
4104       ENDDO
4105       ! Here, check_tr_ns holds the inaccuracy during the redistribution phase
4106       check_tr_ns(:,jst) = tmcf(:)-(tmci(:)-flux_top(:)-dr_ns(:,jst)-diag_tr(:))
4107
4108       !! We solve here the numerical errors that happen when the soil is close to saturation
4109       !! and drainage very high, and which lead to negative check_tr_ns: the soil dries more
4110       !! than what is demanded by the fluxes, so we need to increase the fluxes.
4111       !! This is done by increasing the drainage.
4112       !! There are also instances of positive check_tr_ns, larger when the drainage is high
4113       !! They are similarly corrected by a decrease of dr_ns, in the limit of keeping a positive drainage.
4114       DO ji=1,kjpindex
4115          IF ( check_tr_ns(ji,jst) .LT. zero ) THEN
4116              dr_corrnum_ns(ji,jst) = -check_tr_ns(ji,jst)
4117          ELSE
4118              dr_corrnum_ns(ji,jst) = -MIN(dr_ns(ji,jst),check_tr_ns(ji,jst))             
4119          ENDIF
4120          dr_ns(ji,jst) = dr_ns(ji,jst) + dr_corrnum_ns(ji,jst) ! dr_ns increases/decrease if check_tr negative/positive
4121       ENDDO
4122       !! For water conservation check during redistribution
4123       IF (check_cwrr) THEN         
4124          check_tr_ns(:,jst) = tmcf(:)-(tmci(:)-flux_top(:)-dr_ns(:,jst)-diag_tr(:)) 
4125       ENDIF
4126
4127       !! 3. AFTER DIFFUSION/REDISTRIBUTION
4128
4129       !! 3.1 Updating mc, as all the following checks against saturation will compare mc to mcs
4130       !      The frozen fraction is constant, so that any water flux to/from a layer changes
4131       !      both mcl and the ice amount. The assumption behind this is that water entering/leaving
4132       !      a soil layer immediately freezes/melts with the proportion profil_froz_hydro_ns/(1-profil_...)
4133       DO jsl = 1, nslm
4134          DO ji =1, kjpindex
4135             mc(ji,jsl,jst) = MAX( mcl(ji,jsl,jst), mcl(ji,jsl,jst) + &
4136                  profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(ji)) )
4137             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we get mc=mcl
4138          ENDDO
4139       ENDDO
4140
4141       !! 3.2 Correct here the possible over-saturation values (subroutine hydrol_soil_smooth_over_mcs2 acts on mc)
4142       !    Oversaturation results from numerical inaccuracies and can be frequent if free_drain_coef=0
4143       !    Here hydrol_soil_smooth_over_mcs2 discard all excess as ru_corr_ns, oriented to either ru_ns or dr_ns
4144       !    The former routine hydrol_soil_smooth_over_mcs, which keeps most of the excess in the soiltile
4145       !    after smoothing, first downward then upward, is kept in the module but not used here
4146       dr_corr_ns(:,jst) = zero
4147       ru_corr_ns(:,jst) = zero
4148       call hydrol_soil_smooth_over_mcs2(mcs, kjpindex, jst, njsc, is_over_mcs, ru_corr_ns, check_over_ns)
4149       
4150       ! In absence of freezing, if F is large enough, the correction of oversaturation is sent to drainage       
4151       DO ji = 1, kjpindex
4152          IF ((free_drain_coef(ji,jst) .GE. 0.5) .AND. (.NOT. ok_freeze_cwrr) ) THEN
4153             dr_corr_ns(ji,jst) = ru_corr_ns(ji,jst) 
4154             ru_corr_ns(ji,jst) = zero
4155          ENDIF
4156       ENDDO
4157       dr_ns(:,jst) = dr_ns(:,jst) + dr_corr_ns(:,jst)
4158       ru_ns(:,jst) = ru_ns(:,jst) + ru_corr_ns(:,jst)
4159
4160       !! 3.3 Negative runoff is reported to drainage
4161       !  Since we computed ru_ns directly from hydrol_soil_infilt, ru_ns should not be negative
4162             
4163       ru_corr2_ns(:,jst) = zero
4164       DO ji = 1, kjpindex
4165          IF (ru_ns(ji,jst) .LT. zero) THEN
4166             IF (printlev>=3)  WRITE (numout,*) 'NEGATIVE RU_NS: runoff and drainage before correction',&
4167                  ru_ns(ji,jst),dr_ns(ji,jst)
4168             dr_ns(ji,jst)=dr_ns(ji,jst)+ru_ns(ji,jst)
4169             ru_corr2_ns(ji,jst) = -ru_ns(ji,jst)
4170             ru_ns(ji,jst)= 0.
4171          END IF         
4172       ENDDO
4173
4174       !! 3.4.1 Optional nudging for soil moisture
4175       IF (ok_nudge_mc) THEN
4176          CALL hydrol_nudge_mc(kjpindex, jst, mc)
4177       END IF
4178
4179
4180       !! 3.4.2 Optional block to force saturation below zwt_force
4181       ! This block is not compatible with freezing; in this case, mcl must be corrected too
4182       ! We test if zwt_force(1,jst) <= zmaxh, to avoid steps 1 and 2 if unnecessary
4183       
4184       IF (zwt_force(1,jst) <= zmaxh) THEN
4185
4186          !! We force the nodes below zwt_force to be saturated
4187          !  As above, we compare mc to mcs
4188          DO jsl = 1,nslm
4189             DO ji = 1, kjpindex
4190                dmc(ji,jsl) = zero
4191                IF ( ( zz(jsl) >= zwt_force(ji,jst)*mille ) ) THEN
4192                   dmc(ji,jsl) = mcs(ji) - mc(ji,jsl,jst) ! addition to reach mcs (m3/m3) = positive value
4193                   mc(ji,jsl,jst) = mcs(ji)
4194                ENDIF
4195             ENDDO
4196          ENDDO
4197         
4198          !! To ensure conservation, this needs to be balanced by a negative change in drainage (in kg/m2/dt)
4199          DO ji = 1, kjpindex
4200             dr_force_ns(ji,jst) = dz(2) * ( trois*dmc(ji,1) + dmc(ji,2) )/huit ! top layer = initialization
4201          ENDDO
4202          DO jsl = 2,nslm-1 ! intermediate layers
4203             DO ji = 1, kjpindex
4204                dr_force_ns(ji,jst) = dr_force_ns(ji,jst) + dz(jsl) &
4205                     & * (trois*dmc(ji,jsl)+dmc(ji,jsl-1))/huit &
4206                     & + dz(jsl+1) * (trois*dmc(ji,jsl)+dmc(ji,jsl+1))/huit
4207             ENDDO
4208          ENDDO
4209          DO ji = 1, kjpindex
4210             dr_force_ns(ji,jst) = dr_force_ns(ji,jst) + dz(nslm) & ! bottom layer
4211                  & * (trois * dmc(ji,nslm) + dmc(ji,nslm-1))/huit
4212             dr_ns(ji,jst) = dr_ns(ji,jst) - dr_force_ns(ji,jst) ! dr_force_ns is positive and dr_ns must be reduced
4213          END DO
4214
4215       ELSE         
4216
4217          dr_force_ns(:,jst) = zero 
4218
4219       ENDIF
4220
4221       !! 3.5 Diagnosing the effective water table depth:
4222       !!     Defined as as the smallest jsl value when mc(jsl) is no more at saturation (mcs), starting from the bottom
4223       !      If there is a part of the soil which is saturated but underlain with unsaturated nodes,
4224       !      this is not considered as a water table
4225       DO ji = 1, kjpindex
4226          wtd_ns(ji,jst) = undef_sechiba ! in meters
4227          jsl=nslm
4228          DO WHILE ( (mc(ji,jsl,jst) .EQ. mcs(ji)) .AND. (jsl > 1) )
4229             wtd_ns(ji,jst) = zz(jsl)/mille ! in meters
4230             jsl=jsl-1
4231          ENDDO
4232       ENDDO
4233
4234       !! 3.6 Diagnose under_mcr to adapt water stress calculation below
4235       !      This routine does not change tmc but decides where we should turn off ET to prevent further mc decrease
4236       !      Like above, the tests are made on total mc, compared to mcr
4237       CALL hydrol_soil_smooth_under_mcr(mcr, kjpindex, jst, njsc, is_under_mcr, check_under_ns)
4238 
4239       !! 4. At the end of the prognostic calculations, we recompute important moisture variables
4240
4241       !! 4.1 Total soil moisture content (water2infilt added below)
4242       DO ji = 1, kjpindex
4243          tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
4244       ENDDO
4245       DO jsl = 2,nslm-1
4246          DO ji = 1, kjpindex
4247             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) &
4248                  & * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
4249                  & + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
4250          ENDDO
4251       ENDDO
4252       DO ji = 1, kjpindex
4253          tmc(ji,jst) = tmc(ji,jst) + dz(nslm) &
4254               & * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
4255       END DO
4256
4257       !! 4.2 mcl is a module variable; we update it here for calculating bare soil evaporation,
4258       !!     and in case we would like to export it (xios)
4259       DO jsl = 1, nslm
4260          DO ji =1, kjpindex
4261             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(ji) + &
4262                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(ji)) )
4263             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
4264          ENDDO
4265       ENDDO
4266       
4267       !! 5. Optional check of the water balance of soil column (if check_cwrr)
4268
4269       IF (check_cwrr) THEN
4270
4271          !! 5.1 Computation of the vertical water fluxes and water balance of the top layer
4272          CALL hydrol_diag_soil_flux(kjpindex,jst,mclint,flux_top)
4273
4274       ENDIF
4275
4276       !! 6. SM DIAGNOSTICS FOR OTHER ROUTINES, MODULES, OR NEXT STEP
4277       !    Starting here, mc and mcl should not change anymore
4278       
4279       !! 6.1 Total soil moisture, soil moisture at litter levels, soil wetness, us, humrelv, vesgtressv
4280       !!     (based on mc)
4281
4282       !! In output, tmc includes water2infilt(ji,jst)
4283       DO ji=1,kjpindex
4284          tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
4285       END DO
4286       
4287       ! The litter is the 4 top levels of the soil
4288       ! Compute various field of soil moisture for the litter (used for stomate and for albedo)
4289       ! We exclude the frozen water from the calculation
4290       DO ji=1,kjpindex
4291          tmc_litter(ji,jst) = dz(2) * ( trois*mcl(ji,1,jst)+ mcl(ji,2,jst))/huit
4292       END DO
4293       ! sum from level 1 to 4
4294       DO jsl=2,4
4295          DO ji=1,kjpindex
4296             tmc_litter(ji,jst) = tmc_litter(ji,jst) + dz(jsl) * & 
4297                  & ( trois*mcl(ji,jsl,jst) + mcl(ji,jsl-1,jst))/huit &
4298                  & + dz(jsl+1)*(trois*mcl(ji,jsl,jst) + mcl(ji,jsl+1,jst))/huit
4299          END DO
4300       END DO
4301
4302       ! Subsequent calculation of soil_wet_litter (tmc-tmcw)/(tmcfc-tmcw)
4303       ! Based on liquid water content
4304       DO ji=1,kjpindex
4305          soil_wet_litter(ji,jst) = MIN(un, MAX(zero,&
4306               & (tmc_litter(ji,jst)-tmc_litter_wilt(ji,jst)) / &
4307               & (tmc_litter_field(ji,jst)-tmc_litter_wilt(ji,jst)) ))
4308       END DO
4309
4310       ! Preliminary calculation of various soil moistures (for each layer, in kg/m2)
4311       sm(:,1)  = dz(2) * (trois*mcl(:,1,jst) + mcl(:,2,jst))/huit
4312       smt(:,1) = dz(2) * (trois*mc(:,1,jst) + mc(:,2,jst))/huit
4313       smw(:,1) = dz(2) * (quatre*mcw(:))/huit
4314       smf(:,1) = dz(2) * (quatre*mcfc(:))/huit
4315       sms(:,1) = dz(2) * (quatre*mcs(:))/huit
4316       DO jsl = 2,nslm-1
4317          sm(:,jsl)  = dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
4318               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
4319          smt(:,jsl) = dz(jsl) * (trois*mc(:,jsl,jst)+mc(:,jsl-1,jst))/huit &
4320               + dz(jsl+1) * (trois*mc(:,jsl,jst)+mc(:,jsl+1,jst))/huit
4321          smw(:,jsl) = dz(jsl) * ( quatre*mcw(:) )/huit &
4322               + dz(jsl+1) * ( quatre*mcw(:) )/huit
4323          smf(:,jsl) = dz(jsl) * ( quatre*mcfc(:) )/huit &
4324               + dz(jsl+1) * ( quatre*mcfc(:) )/huit
4325          sms(:,jsl) = dz(jsl) * ( quatre*mcs(:) )/huit &
4326               + dz(jsl+1) * ( quatre*mcs(:) )/huit
4327       ENDDO
4328       sm(:,nslm)  = dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit 
4329       smt(:,nslm) = dz(nslm) * (trois*mc(:,nslm,jst) + mc(:,nslm-1,jst))/huit     
4330       smw(:,nslm) = dz(nslm) * (quatre*mcw(:))/huit
4331       smf(:,nslm) = dz(nslm) * (quatre*mcfc(:))/huit
4332       sms(:,nslm) = dz(nslm) * (quatre*mcs(:))/huit
4333       ! sm_nostress = soil moisture of each layer at which us reaches 1, here at the middle of [smw,smf]
4334       DO jsl = 1,nslm
4335          sm_nostress(:,jsl) = smw(:,jsl) + pcent(njsc(:)) * (smf(:,jsl)-smw(:,jsl))
4336       END DO
4337
4338       ! Saturated litter soil moisture for rsoil
4339       tmcs_litter(:) = zero
4340       DO jsl = 1,4
4341          tmcs_litter(:) = tmcs_litter(:) + sms(:,jsl)
4342       END DO
4343             
4344       ! Soil wetness profiles (W-Ww)/(Ws-Ww)
4345       ! soil_wet_ns is the ratio of available soil moisture to max available soil moisture
4346       ! (ie soil moisture at saturation minus soil moisture at wilting point).
4347       ! soil wet is a water stress for stomate, to control C decomposition
4348       ! Based on liquid water content
4349       DO jsl=1,nslm
4350          DO ji=1,kjpindex
4351             soil_wet_ns(ji,jsl,jst) = MIN(un, MAX(zero, &
4352                  (sm(ji,jsl)-smw(ji,jsl))/(sms(ji,jsl)-smw(ji,jsl)) ))
4353          END DO
4354       END DO
4355
4356       ! Compute us and the new humrelv to use in sechiba (with loops on the vegetation types)
4357       ! This is the water stress for transpiration (diffuco) and photosynthesis (diffuco)
4358       ! humrel is never used in stomate
4359       ! Based on liquid water content
4360
4361       ! -- PFT1
4362       humrelv(:,1,jst) = zero       
4363       ! -- Top layer
4364       DO jv = 2,nvm
4365          DO ji=1,kjpindex
4366             !- Here we make the assumption that roots do not take water from the 1st layer.
4367             us(ji,jv,jst,1) = zero
4368             humrelv(ji,jv,jst) = zero ! initialisation of the sum
4369          END DO
4370       ENDDO
4371
4372       !! Dynamic nroot to optimize water use: the root profile used to weight the water stress function
4373       !! of each soil layer is updated at each time step in order to match the soil water profile
4374       !! (the soil water content of each layer available for transpiration)
4375       IF (ok_dynroot) THEN
4376          DO jv = 1, nvm
4377             IF ( is_tree(jv) ) THEN
4378                DO ji = 1, kjpindex
4379                   nroot_tmp(:) = zero
4380                   DO jsl = 2, nslm
4381                      nroot_tmp(jsl) = MAX(zero,sm(ji,jsl)-smw(ji,jsl) )
4382                   ENDDO
4383                   IF (SUM(nroot_tmp(:)) .GT. min_sechiba ) THEN
4384                      nroot(ji,jv,:) = nroot_tmp(:)/SUM(nroot_tmp(:))
4385                   ELSE
4386                      nroot(ji,jv,:) = zero
4387                   END IF
4388                ENDDO
4389             ELSE
4390                ! Specific case for grasses where we only consider the first 1m of soil.               
4391                DO ji = 1, kjpindex
4392                   nroot_tmp(:) = zero
4393                   DO jsl = 2, nslm
4394                      IF (znt(jsl) .LT. un) THEN
4395                         nroot_tmp(jsl) = MAX(zero,sm(ji,jsl)-smw(ji,jsl) )
4396                      END IF
4397                   ENDDO
4398                   
4399                   IF (SUM(nroot_tmp(:)) .GT. min_sechiba ) THEN
4400                      DO jsl = 2,nslm
4401                         IF (znt(jsl) .LT. un) THEN
4402                            nroot(ji,jv,jsl) = nroot_tmp(jsl)/SUM(nroot_tmp(:))
4403                         ELSE
4404                            nroot(ji,jv,jsl) = zero
4405                         END IF
4406                      ENDDO
4407                      nroot(ji,jv,1) = zero
4408                   END IF
4409                ENDDO
4410             END IF
4411          ENDDO
4412       ENDIF
4413
4414       ! -- Intermediate and bottom layers
4415       DO jsl = 2,nslm
4416          DO jv = 2, nvm
4417             DO ji=1,kjpindex
4418                ! AD16*** Although plants can only withdraw liquid water, we compute here the water stress
4419                ! based on mc and the corresponding thresholds mcs, pcent, or potentially mcw and mcfc
4420                ! This is consistent with assuming that ice is uniformly distributed within the poral space
4421                ! In such a case, freezing makes mcl and the "liquid" porosity smaller than the "total" values
4422                ! And it is the same for all the moisture thresholds, which are proportional to porosity.
4423                ! Since the stress is based on relative moisture, it could thus independent from the porosity
4424                ! at first order, thus independent from freezing.   
4425                ! 26-07-2017: us and humrel now based on liquid soil moisture, so the stress is stronger
4426                IF(new_watstress) THEN
4427                   IF((sm(ji,jsl)-smw(ji,jsl)) .GT. min_sechiba) THEN
4428                      us(ji,jv,jst,jsl) = MIN(un, MAX(zero, &
4429                           (EXP(- alpha_watstress * &
4430                           ( (smf(ji,jsl) - smw(ji,jsl)) / ( sm_nostress(ji,jsl) - smw(ji,jsl)) ) * &
4431                           ( (sm_nostress(ji,jsl) - sm(ji,jsl)) / ( sm(ji,jsl) - smw(ji,jsl)) ) ) ) ))&
4432                           * nroot(ji,jv,jsl)
4433                   ELSE
4434                      us(ji,jv,jst,jsl) = 0.
4435                   ENDIF
4436                ELSE
4437                   us(ji,jv,jst,jsl) = MIN(un, MAX(zero, &
4438                        (sm(ji,jsl)-smw(ji,jsl))/(sm_nostress(ji,jsl)-smw(ji,jsl)) )) * nroot(ji,jv,jsl)
4439                ENDIF
4440                humrelv(ji,jv,jst) = humrelv(ji,jv,jst) + us(ji,jv,jst,jsl)
4441             END DO
4442          END DO
4443       ENDDO
4444
4445       !! vegstressv is the water stress for phenology in stomate
4446       !! It varies linearly from zero at wilting point to 1 at field capacity
4447       vegstressv(:,:,jst) = zero
4448       DO jv = 2, nvm
4449          DO ji=1,kjpindex
4450             DO jsl=1,nslm
4451                vegstressv(ji,jv,jst) = vegstressv(ji,jv,jst) + &
4452                     MIN(un, MAX(zero, (sm(ji,jsl)-smw(ji,jsl))/(smf(ji,jsl)-smw(ji,jsl)) )) &
4453                     * nroot(ji,jv,jsl)
4454             END DO
4455          END DO
4456       END DO
4457
4458
4459       ! -- If the PFT is absent, the corresponding humrelv and vegstressv = 0
4460       DO jv = 2, nvm
4461          DO ji = 1, kjpindex
4462             IF (vegetmax_soil(ji,jv,jst) .LT. min_sechiba) THEN
4463                humrelv(ji,jv,jst) = zero
4464                vegstressv(ji,jv,jst) = zero
4465                us(ji,jv,jst,:) = zero
4466             ENDIF
4467          END DO
4468       END DO
4469
4470       !! 6.2 We need to turn off evaporation when is_under_mcr
4471       !!     We set us, humrelv and vegstressv to zero in this case
4472       !!     WARNING: It's different from having locally us=0 in the soil layers(s) where mc<mcr
4473       !!              This part is crucial to preserve water conservation
4474       DO jsl = 1,nslm
4475          DO jv = 2, nvm
4476             WHERE (is_under_mcr(:,jst))
4477                us(:,jv,jst,jsl) = zero
4478             ENDWHERE
4479          ENDDO
4480       ENDDO
4481       DO jv = 2, nvm
4482          WHERE (is_under_mcr(:,jst))
4483             humrelv(:,jv,jst) = zero
4484          ENDWHERE
4485       ENDDO
4486       
4487       ! For consistency in stomate, we also set moderwilt and soil_wet_ns to zero in this case.
4488       ! They are used later for shumdiag and shumdiag_perma
4489       DO jsl = 1,nslm
4490          WHERE (is_under_mcr(:,jst))
4491             soil_wet_ns(:,jsl,jst) = zero
4492          ENDWHERE
4493       ENDDO
4494
4495       ! Counting the nb of under_mcr occurences in each grid-cell
4496       WHERE (is_under_mcr(:,jst))
4497          undermcr = undermcr + un
4498       ENDWHERE
4499
4500       !! 6.3 Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in
4501       !!     thermosoil for the thermal conductivity.
4502       !! The multiplication by vegtot creates grid-cell average values
4503       ! *** To be checked for consistency with the use of nobio properties in thermosoil
4504           
4505       DO jsl=1,nslm
4506          DO ji=1,kjpindex
4507             mc_layh(ji,jsl) = mc_layh(ji,jsl) + mc(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji) 
4508             mcl_layh(ji,jsl) = mcl_layh(ji,jsl) + mcl(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji)
4509          ENDDO
4510       END DO
4511
4512       !! 6.4 The hydraulic conductivities exported here are the ones used in the diffusion/redistribution
4513       ! (no call of hydrol_soil_coef since 2.1)
4514       ! We average the values of each soiltile and keep the specific value (no multiplication by vegtot)
4515       DO ji = 1, kjpindex
4516          kk_moy(ji,:) = kk_moy(ji,:) + soiltile(ji,jst) * k(ji,:) 
4517          kk(ji,:,jst) = k(ji,:)
4518       ENDDO
4519       
4520       !! 6.5 We also want to export ksat at each node for CMIP6
4521       !  (In the output, done only once according to field_def_orchidee.xml; same averaging as for kk)
4522       DO jsl = 1, nslm
4523          ksat(:,jsl) = ksat(:,jsl) + soiltile(:,jst) * &
4524               ( ks(:) * kfact(jsl,:) * kfact_root(:,jsl,jst) ) 
4525       ENDDO
4526             
4527      IF (printlev>=3) WRITE (numout,*) ' prognostic/diagnostic part of hydrol_soil done for jst =', jst         
4528
4529    END DO  ! end of loop on soiltile
4530
4531    !! -- ENDING THE MAIN LOOP ON SOILTILES
4532
4533    !! 7. Summing 3d variables into 2d variables
4534    CALL hydrol_diag_soil (ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, veget_max, soiltile, njsc, runoff, drainage, &
4535         & evapot, vevapnu, returnflow, reinfiltration, irrigation, &
4536         & shumdiag,shumdiag_perma, k_litt, litterhumdiag, humrel, vegstress, drysoil_frac,tot_melt)
4537
4538    ! Means of wtd, runoff and drainage corrections, across soiltiles   
4539    wtd(:) = zero 
4540    ru_corr(:) = zero
4541    ru_corr2(:) = zero
4542    dr_corr(:) = zero
4543    dr_corrnum(:) = zero
4544    dr_force(:) = zero
4545    DO jst = 1, nstm
4546       DO ji = 1, kjpindex 
4547          wtd(ji) = wtd(ji) + soiltile(ji,jst) * wtd_ns(ji,jst) ! average over vegtot only
4548          IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
4549             ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
4550             ru_corr(ji) = ru_corr(ji) + vegtot(ji) * soiltile(ji,jst) * ru_corr_ns(ji,jst) 
4551             ru_corr2(ji) = ru_corr2(ji) + vegtot(ji) * soiltile(ji,jst) * ru_corr2_ns(ji,jst) 
4552             dr_corr(ji) = dr_corr(ji) + vegtot(ji) * soiltile(ji,jst) * dr_corr_ns(ji,jst) 
4553             dr_corrnum(ji) = dr_corrnum(ji) + vegtot(ji) * soiltile(ji,jst) * dr_corrnum_ns(ji,jst)
4554             dr_force(ji) = dr_force(ji) - vegtot(ji) * soiltile(ji,jst) * dr_force_ns(ji,jst)
4555                                       ! the sign is OK to get a negative drainage flux
4556          ENDIF
4557       ENDDO
4558    ENDDO
4559
4560    ! Means local variables, including water conservation checks
4561    ru_infilt(:)=0.
4562    qinfilt(:)=0.
4563    check_infilt(:)=0.
4564    check_tr(:)=0.
4565    check_over(:)=0.
4566    check_under(:)=0.
4567    qflux(:,:)=0.
4568    check_top(:)=0.
4569    DO jst = 1, nstm
4570       DO ji = 1, kjpindex 
4571          IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
4572             ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
4573             ru_infilt(ji) = ru_infilt(ji) + vegtot(ji) * soiltile(ji,jst) * ru_infilt_ns(ji,jst)
4574             qinfilt(ji) = qinfilt(ji) + vegtot(ji) * soiltile(ji,jst) * qinfilt_ns(ji,jst)
4575          ENDIF
4576       ENDDO
4577    ENDDO
4578 
4579    IF (check_cwrr) THEN
4580       DO jst = 1, nstm
4581          DO ji = 1, kjpindex 
4582             IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
4583                ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
4584                check_infilt(ji) = check_infilt(ji) + vegtot(ji) * soiltile(ji,jst) * check_infilt_ns(ji,jst)
4585                check_tr(ji) = check_tr(ji) + vegtot(ji) * soiltile(ji,jst) * check_tr_ns(ji,jst)
4586                check_over(ji) = check_over(ji) + vegtot(ji) * soiltile(ji,jst) * check_over_ns(ji,jst)
4587                check_under(ji) =  check_under(ji) + vegtot(ji) * soiltile(ji,jst) * check_under_ns(ji,jst)
4588                !
4589                qflux(ji,:) = qflux(ji,:) + vegtot(ji) * soiltile(ji,jst) * qflux_ns(ji,:,jst)
4590                check_top(ji) =  check_top(ji) + vegtot(ji) * soiltile(ji,jst) * check_top_ns(ji,jst)
4591             ENDIF
4592          ENDDO
4593       ENDDO
4594    END IF
4595
4596    !! 8. COMPUTING EVAP_BARE_LIM_NS FOR NEXT TIME STEP, WITH A LOOP ON SOILTILES
4597    !!    The principle is to run a dummy integration of the water redistribution scheme
4598    !!    to check if the SM profile can sustain a potential evaporation.
4599    !!    If not, the dummy integration is redone from the SM profile of the end of the normal integration,
4600    !!    with a boundary condition leading to a very severe water limitation: mc(1)=mcr
4601
4602    ! evap_bare_lim = beta factor for bare soil evaporation
4603    evap_bare_lim(:) = zero
4604    evap_bare_lim_ns(:,:) = zero
4605
4606    ! Loop on soil tiles 
4607    DO jst = 1,nstm
4608
4609       !! 8.1 Save actual mc, mcl, and tmc for restoring at the end of the time step
4610       !!      and calculate tmcint corresponding to mc without water2infilt
4611       DO jsl = 1, nslm
4612          DO ji = 1, kjpindex
4613             mcint(ji,jsl) = mask_soiltile(ji,jst) * mc(ji,jsl,jst)
4614             mclint(ji,jsl) = mask_soiltile(ji,jst) * mcl(ji,jsl,jst)
4615          ENDDO
4616       ENDDO
4617
4618       DO ji = 1, kjpindex
4619          temp(ji) = tmc(ji,jst)
4620          tmcint(ji) = temp(ji) - water2infilt(ji,jst) ! to estimate bare soil evap based on water budget
4621       ENDDO
4622
4623       !! 8.2 Since we estimate bare soile evap for the next time step, we update profil_froz_hydro and mcl
4624       !     (effect of mc only, the change in stempdiag is neglected)
4625       IF ( ok_freeze_cwrr ) CALL hydrol_soil_froz(nvan, avan, mcr, mcs,kjpindex,jst,njsc,stempdiag)
4626       DO jsl = 1, nslm
4627          DO ji =1, kjpindex
4628             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(ji) + &
4629                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(ji)) )
4630             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
4631          ENDDO
4632       ENDDO         
4633
4634       !! 8.3 K and D are recomputed for the updated profile of mc/mcl
4635       CALL hydrol_soil_coef(mcr, mcs, kjpindex,jst,njsc)
4636
4637       !! 8.4 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
4638       CALL hydrol_soil_setup(kjpindex,jst)
4639       resolv(:) = (mask_soiltile(:,jst) .GT. 0) 
4640
4641       !! 8.5 We define the system of linear equations, based on matrix coefficients,
4642
4643       !- Impose potential evaporation as flux_top in mm/step, assuming the water is available
4644       ! Note that this should lead to never have evapnu>evapot_penm(ji)
4645
4646       DO ji = 1, kjpindex
4647         
4648          IF (vegtot(ji).GT.min_sechiba) THEN
4649             
4650             ! We calculate a reduced demand, by means of a soil resistance (Sellers et al., 1992)
4651             ! It is based on the liquid SM only, like for us and humrel
4652             IF (do_rsoil) THEN
4653                mc_rel(ji) = tmc_litter(ji,jst)/tmcs_litter(ji) ! tmc_litter based on mcl
4654                ! based on SM in the top 4 soil layers (litter) to smooth variability
4655                r_soil_ns(ji,jst) = exp(8.206 - 4.255 * mc_rel(ji))
4656             ELSE
4657                r_soil_ns(ji,jst) = zero
4658             ENDIF
4659
4660             ! Aerodynamic resistance
4661             speed = MAX(min_wind, SQRT (u(ji)*u(ji) + v(ji)*v(ji)))
4662             IF (speed * tq_cdrag(ji) .GT. min_sechiba) THEN
4663                ra = un / (speed * tq_cdrag(ji))
4664                evap_soil(ji) = evapot_penm(ji) / (un + r_soil_ns(ji,jst)/ra)
4665             ELSE
4666                evap_soil(ji) = evapot_penm(ji)
4667             ENDIF
4668                         
4669             flux_top(ji) = evap_soil(ji) * &
4670                  AINT(frac_bare_ns(ji,jst)+un-min_sechiba)
4671          ELSE
4672             
4673             flux_top(ji) = zero
4674             r_soil_ns(ji,jst) = zero
4675             
4676          ENDIF
4677       ENDDO
4678
4679       ! We don't use rootsinks, because we assume there is no transpiration in the bare soil fraction (??)
4680       !- First layer
4681       DO ji = 1, kjpindex
4682          tmat(ji,1,1) = zero
4683          tmat(ji,1,2) = f(ji,1)
4684          tmat(ji,1,3) = g1(ji,1)
4685          rhs(ji,1)    = fp(ji,1) * mcl(ji,1,jst) + gp(ji,1)*mcl(ji,2,jst) &
4686               - flux_top(ji) - (b(ji,1)+b(ji,2))/deux *(dt_sechiba/one_day)
4687       ENDDO
4688       !- soil body
4689       DO jsl=2, nslm-1
4690          DO ji = 1, kjpindex
4691             tmat(ji,jsl,1) = e(ji,jsl)
4692             tmat(ji,jsl,2) = f(ji,jsl)
4693             tmat(ji,jsl,3) = g1(ji,jsl)
4694             rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
4695                  +  gp(ji,jsl) * mcl(ji,jsl+1,jst) &
4696                  + (b(ji,jsl-1) - b(ji,jsl+1)) * (dt_sechiba/one_day) / deux
4697          ENDDO
4698       ENDDO
4699       !- Last layer
4700       DO ji = 1, kjpindex
4701          jsl=nslm
4702          tmat(ji,jsl,1) = e(ji,jsl)
4703          tmat(ji,jsl,2) = f(ji,jsl)
4704          tmat(ji,jsl,3) = zero
4705          rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
4706               + (b(ji,jsl-1) + b(ji,jsl)*(un-deux*free_drain_coef(ji,jst))) * (dt_sechiba/one_day) / deux
4707       ENDDO
4708       !- Store the equations for later use (9.6)
4709       DO jsl=1,nslm
4710          DO ji = 1, kjpindex
4711             srhs(ji,jsl) = rhs(ji,jsl)
4712             stmat(ji,jsl,1) = tmat(ji,jsl,1)
4713             stmat(ji,jsl,2) = tmat(ji,jsl,2)
4714             stmat(ji,jsl,3) = tmat(ji,jsl,3)
4715          ENDDO
4716       ENDDO
4717
4718       !! 8.6 Solve the diffusion equation, assuming that flux_top=evapot_penm (updates mcl)
4719       CALL hydrol_soil_tridiag(kjpindex,jst)
4720
4721       !! 9.7 Alternative solution with mc(1)=mcr in points where the above solution leads to mcl<mcr
4722       ! hydrol_soil_tridiag calculates mc recursively from the top as a fonction of rhs and tmat
4723       ! We re-use these the above values, but for mc(1)=mcr and the related tmat
4724       
4725       DO ji = 1, kjpindex
4726          ! by construction, mc and mcl are always on the same side of mcr, so we can use mcl here
4727          resolv(ji) = (mcl(ji,1,jst).LT.(mcr(ji)).AND.flux_top(ji).GT.min_sechiba)
4728       ENDDO
4729       !! Reset the coefficient for diffusion (tridiag is only solved if resolv(ji) = .TRUE.)O
4730       DO jsl=1,nslm
4731          !- The new condition is to put the upper layer at residual soil moisture
4732          DO ji = 1, kjpindex
4733             rhs(ji,jsl) = srhs(ji,jsl)
4734             tmat(ji,jsl,1) = stmat(ji,jsl,1)
4735             tmat(ji,jsl,2) = stmat(ji,jsl,2)
4736             tmat(ji,jsl,3) = stmat(ji,jsl,3)
4737          END DO
4738       END DO
4739       
4740       DO ji = 1, kjpindex
4741          tmat(ji,1,2) = un
4742          tmat(ji,1,3) = zero
4743          rhs(ji,1) = mcr(ji)
4744       ENDDO
4745       
4746       ! Solves the diffusion equation with new surface bc where resolv=T
4747       CALL hydrol_soil_tridiag(kjpindex,jst)
4748
4749       !! 8.8 In both case, we have drainage to be consistent with rhs
4750       DO ji = 1, kjpindex
4751          flux_bottom(ji) = mask_soiltile(ji,jst)*k(ji,nslm)*free_drain_coef(ji,jst) * (dt_sechiba/one_day)
4752       ENDDO
4753       
4754       !! 8.9 Water budget to assess the top flux = soil evaporation
4755       !      Where resolv=F at the 2nd step (9.6), it should simply be the potential evaporation
4756
4757       ! Total soil moisture content for water budget
4758
4759       DO jsl = 1, nslm
4760          DO ji =1, kjpindex
4761             mc(ji,jsl,jst) = MAX( mcl(ji,jsl,jst), mcl(ji,jsl,jst) + &
4762                  profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(ji)) )
4763             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we get mc=mcl
4764          ENDDO
4765       ENDDO
4766       
4767       DO ji = 1, kjpindex
4768          tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
4769       ENDDO       
4770       DO jsl = 2,nslm-1
4771          DO ji = 1, kjpindex
4772             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) &
4773                  * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
4774                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
4775          ENDDO
4776       ENDDO
4777       DO ji = 1, kjpindex
4778          tmc(ji,jst) = tmc(ji,jst) + dz(nslm) &
4779               * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
4780       END DO
4781   
4782       ! Deduce upper flux from soil moisture variation and bottom flux
4783       ! TMCi-D-BSE=TMC (BSE=bare soil evap=TMCi-TMC-D)
4784       ! The numerical errors of tridiag close to saturation cannot be simply solved here,
4785       ! we can only hope they are not too large because we don't add water at this stage...
4786       DO ji = 1, kjpindex
4787          evap_bare_lim_ns(ji,jst) = mask_soiltile(ji,jst) * &
4788               (tmcint(ji)-tmc(ji,jst)-flux_bottom(ji))
4789       END DO
4790
4791       !! 8.10 evap_bare_lim_ns is turned from an evaporation rate to a beta
4792       DO ji = 1, kjpindex
4793          ! Here we weight evap_bare_lim_ns by the fraction of bare evaporating soil.
4794          ! This is given by frac_bare_ns, taking into account bare soil under vegetation
4795          IF(vegtot(ji) .GT. min_sechiba) THEN
4796             evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) * frac_bare_ns(ji,jst)
4797          ELSE
4798             evap_bare_lim_ns(ji,jst) = 0.
4799          ENDIF
4800       END DO
4801
4802       ! We divide by evapot, which is consistent with diffuco (evap_bare_lim_ns < evapot_penm/evapot)
4803       ! Further decrease if tmc_litter is below the wilting point
4804
4805       IF (do_rsoil) THEN
4806          DO ji=1,kjpindex
4807             IF (evapot(ji).GT.min_sechiba) THEN
4808                evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) / evapot(ji)
4809             ELSE
4810                evap_bare_lim_ns(ji,jst) = zero ! not redundant with the is_under_mcr case below
4811                                                ! but not necessarily useful
4812             END IF
4813             evap_bare_lim_ns(ji,jst)=MAX(MIN(evap_bare_lim_ns(ji,jst),1.),0.)
4814          END DO
4815       ELSE
4816          DO ji=1,kjpindex
4817             IF ((evapot(ji).GT.min_sechiba) .AND. &
4818                  (tmc_litter(ji,jst).GT.(tmc_litter_wilt(ji,jst)))) THEN
4819                evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) / evapot(ji)
4820             ELSEIF((evapot(ji).GT.min_sechiba).AND. &
4821                  (tmc_litter(ji,jst).GT.(tmc_litter_res(ji,jst)))) THEN
4822                evap_bare_lim_ns(ji,jst) =  (un/deux) * evap_bare_lim_ns(ji,jst) / evapot(ji)
4823                ! This is very arbitrary, with no justification from the literature
4824             ELSE
4825                evap_bare_lim_ns(ji,jst) = zero
4826             END IF
4827             evap_bare_lim_ns(ji,jst)=MAX(MIN(evap_bare_lim_ns(ji,jst),1.),0.)
4828          END DO
4829       ENDIF
4830
4831       !! 8.11 Set evap_bare_lim_ns to zero if is_under_mcr at the end of the prognostic loop
4832       !!      (cf us, humrelv, vegstressv in 5.2)
4833       WHERE (is_under_mcr(:,jst))
4834          evap_bare_lim_ns(:,jst) = zero
4835       ENDWHERE
4836
4837       !! 8.12 Restores mc, mcl, and tmc, to erase the effect of the dummy integrations
4838       !!      on these prognostic variables
4839       DO jsl = 1, nslm
4840          DO ji = 1, kjpindex
4841             mc(ji,jsl,jst) = mask_soiltile(ji,jst) * mcint(ji,jsl)
4842             mcl(ji,jsl,jst) = mask_soiltile(ji,jst) * mclint(ji,jsl)
4843          ENDDO
4844       ENDDO
4845       DO ji = 1, kjpindex
4846          tmc(ji,jst) = temp(ji)
4847       ENDDO
4848
4849    ENDDO !end loop on tiles for dummy integration
4850
4851    !! 9. evap_bar_lim is the grid-cell scale beta
4852    DO ji = 1, kjpindex
4853       evap_bare_lim(ji) =  SUM(evap_bare_lim_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
4854       r_soil(ji) =  SUM(r_soil_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
4855    ENDDO
4856    ! si vegtot LE min_sechiba, evap_bare_lim_ns et evap_bare_lim valent zero
4857
4858
4859    !! 10. XIOS export of local variables, including water conservation checks
4860   
4861    CALL xios_orchidee_send_field("ksat",ksat) ! mm/d (for CMIP6, once)
4862    CALL xios_orchidee_send_field("psi_moy",psi_moy) ! mm (for SP-MIP)
4863    CALL xios_orchidee_send_field("wtd",wtd) ! in m
4864    CALL xios_orchidee_send_field("ru_corr",ru_corr/dt_sechiba)   ! adjustment flux added to surface runoff (included in runoff)
4865    CALL xios_orchidee_send_field("ru_corr2",ru_corr2/dt_sechiba)
4866    CALL xios_orchidee_send_field("dr_corr",dr_corr/dt_sechiba)   ! adjustment flux added to drainage (included in drainage)
4867    CALL xios_orchidee_send_field("dr_corrnum",dr_corrnum/dt_sechiba) 
4868    CALL xios_orchidee_send_field("dr_force",dr_force/dt_sechiba) ! adjustement flux added to drainage to sustain a forced wtd
4869    CALL xios_orchidee_send_field("qinfilt",qinfilt/dt_sechiba)
4870    CALL xios_orchidee_send_field("ru_infilt",ru_infilt/dt_sechiba)
4871    CALL xios_orchidee_send_field("r_soil",r_soil) ! s/m
4872
4873    IF (check_cwrr) THEN
4874       CALL xios_orchidee_send_field("check_infilt",check_infilt/dt_sechiba)
4875       CALL xios_orchidee_send_field("check_tr",check_tr/dt_sechiba)
4876       CALL xios_orchidee_send_field("check_over",check_over/dt_sechiba)
4877       CALL xios_orchidee_send_field("check_under",check_under/dt_sechiba) 
4878       ! Variables calculated in hydrol_diag_soil_flux
4879       CALL xios_orchidee_send_field("qflux",qflux/dt_sechiba) ! upward water flux at the low interface of each layer
4880       CALL xios_orchidee_send_field("check_top",check_top/dt_sechiba) !water budget residu in top layer
4881    END IF
4882
4883
4884  END SUBROUTINE hydrol_soil
4885
4886
4887!! ================================================================================================================================
4888!! SUBROUTINE   : hydrol_soil_infilt
4889!!
4890!>\BRIEF        Infiltration
4891!!
4892!! DESCRIPTION  :
4893!! 1. We calculate the total SM at the beginning of the routine
4894!! 2. Infiltration process
4895!! 2.1 Initialization of time counter and infiltration rate
4896!! 2.2 Infiltration layer by layer, accounting for an exponential law for subgrid variability
4897!! 2.3 Resulting infiltration and surface runoff
4898!! 3. For water conservation check, we calculate the total SM at the beginning of the routine,
4899!!    and export the difference with the flux
4900!! 5. Local verification
4901!!
4902!! RECENT CHANGE(S) : 2016 by A. Ducharne
4903!! Adding checks and interactions variables with hydrol_soil, but the processes are unchanged
4904!!
4905!! MAIN OUTPUT VARIABLE(S) :
4906!!
4907!! REFERENCE(S) :
4908!!
4909!! FLOWCHART    : None
4910!! \n
4911!_ ================================================================================================================================
4912!_ hydrol_soil_infilt
4913
4914  SUBROUTINE hydrol_soil_infilt(ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, ins, njsc, flux_infilt, stempdiag, &
4915                                qinfilt_ns, ru_infilt, check)
4916
4917    !! 0. Variable and parameter declaration
4918
4919    !! 0.1 Input variables
4920
4921    ! GLOBAL (in or inout)
4922    INTEGER(i_std), INTENT(in)                        :: kjpindex        !! Domain size
4923    INTEGER(i_std), INTENT(in)                        :: ins
4924    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc            !! Index of the dominant soil textural class in the grid cell
4925                                                                         !!  (1-nscm, unitless)
4926    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: ks               !! Hydraulic conductivity at saturation (mm {-1})
4927    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: nvan             !! Van Genuchten coeficients n (unitless)
4928    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: avan             !! Van Genuchten coeficients a (mm-1})
4929    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
4930    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
4931    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
4932    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
4933    REAL(r_std), DIMENSION (kjpindex), INTENT (in)    :: flux_infilt     !! Water to infiltrate
4934                                                                         !!  @tex $(kg m^{-2})$ @endtex
4935    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in):: stempdiag       !! Diagnostic temp profile from thermosoil                                                                     
4936    !! 0.2 Output variables
4937    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check       !! delta SM - flux (mm/dt_sechiba)
4938    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: ru_infilt   !! Surface runoff from soil_infilt (mm/dt_sechiba)
4939    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: qinfilt_ns  !! Effective infiltration flux (mm/dt_sechiba)
4940
4941    !! 0.3 Modified variables
4942
4943    !! 0.4 Local variables
4944
4945    INTEGER(i_std)                                :: ji, jsl      !! Indices
4946    REAL(r_std), DIMENSION (kjpindex)             :: wat_inf_pot  !! infiltrable water in the layer
4947    REAL(r_std), DIMENSION (kjpindex)             :: wat_inf      !! infiltrated water in the layer
4948    REAL(r_std), DIMENSION (kjpindex)             :: dt_tmp       !! time remaining before the end of the time step
4949    REAL(r_std), DIMENSION (kjpindex)             :: dt_inf       !! the time it takes to complete the infiltration in the
4950                                                                  !! layer
4951    REAL(r_std)                                   :: k_m          !! the mean conductivity used for the saturated front
4952    REAL(r_std), DIMENSION (kjpindex)             :: infilt_tmp   !! infiltration rate for the considered layer
4953    REAL(r_std), DIMENSION (kjpindex)             :: infilt_tot   !! total infiltration
4954    REAL(r_std), DIMENSION (kjpindex)             :: flux_tmp     !! rate at which precip hits the ground
4955
4956    REAL(r_std), DIMENSION(kjpindex)              :: tmci         !! total SM at beginning of routine (kg/m2)
4957    REAL(r_std), DIMENSION(kjpindex)              :: tmcf         !! total SM at end of routine (kg/m2)
4958   
4959
4960!_ ================================================================================================================================
4961
4962    ! If data (or coupling with GCM) was available, a parameterization for subgrid rainfall could be performed
4963
4964    !! 1. We calculate the total SM at the beginning of the routine
4965    IF (check_cwrr) THEN
4966       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
4967       DO jsl = 2,nslm-1
4968          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
4969               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
4970       ENDDO
4971       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
4972    ENDIF
4973
4974    !! 2. Infiltration process
4975
4976    !! 2.1 Initialization
4977
4978    DO ji = 1, kjpindex
4979       !! First we fill up the first layer (about 1mm) without any resistance and quasi-immediately
4980       wat_inf_pot(ji) = MAX((mcs(ji)-mc(ji,1,ins)) * dz(2) / deux, zero)
4981       wat_inf(ji) = MIN(wat_inf_pot(ji), flux_infilt(ji))
4982       mc(ji,1,ins) = mc(ji,1,ins) + wat_inf(ji) * deux / dz(2)
4983       !
4984    ENDDO
4985
4986    !! Initialize a countdown for infiltration during the time-step and the value of potential runoff
4987    dt_tmp(:) = dt_sechiba / one_day
4988    infilt_tot(:) = wat_inf(:)
4989    !! Compute the rate at which water will try to infiltrate each layer
4990    ! flux_temp is converted here to the same unit as k_m
4991    flux_tmp(:) = (flux_infilt(:)-wat_inf(:)) / dt_tmp(:)
4992
4993    !! 2.2 Infiltration layer by layer
4994    DO jsl = 2, nslm-1
4995       DO ji = 1, kjpindex
4996          !! Infiltrability of each layer if under a saturated one
4997          ! This is computed by an simple arithmetic average because
4998          ! the time step (30min) is not appropriate for a geometric average (advised by Haverkamp and Vauclin)
4999          k_m = (k(ji,jsl) + ks(ji)*kfact(jsl-1,ji)*kfact_root(ji,jsl,ins)) / deux 
5000
5001          IF (ok_freeze_cwrr) THEN
5002             IF (stempdiag(ji, jsl) .LT. ZeroCelsius) THEN
5003                k_m = k(ji,jsl)
5004             ENDIF
5005          ENDIF
5006
5007          !! We compute the mean rate at which water actually infiltrate:
5008          ! Subgrid: Exponential distribution of k around k_m, but average p directly used
5009          ! See d'Orgeval 2006, p 78, but it's not fully clear to me (AD16***)
5010          infilt_tmp(ji) = k_m * (un - EXP(- flux_tmp(ji) / k_m)) 
5011
5012          !! From which we deduce the time it takes to fill up the layer or to end the time step...
5013          wat_inf_pot(ji) =  MAX((mcs(ji)-mc(ji,jsl,ins)) * (dz(jsl) + dz(jsl+1)) / deux, zero)
5014          IF ( infilt_tmp(ji) > min_sechiba) THEN
5015             dt_inf(ji) =  MIN(wat_inf_pot(ji)/infilt_tmp(ji), dt_tmp(ji))
5016             ! The water infiltration TIME has to limited by what is still available for infiltration.
5017             IF ( dt_inf(ji) * infilt_tmp(ji) > flux_infilt(ji)-infilt_tot(ji) ) THEN
5018                dt_inf(ji) = MAX(flux_infilt(ji)-infilt_tot(ji),zero)/infilt_tmp(ji)
5019             ENDIF
5020          ELSE
5021             dt_inf(ji) = dt_tmp(ji)
5022          ENDIF
5023
5024          !! The water enters in the layer
5025          wat_inf(ji) = dt_inf(ji) * infilt_tmp(ji)
5026          ! bviously the moisture content
5027          mc(ji,jsl,ins) = mc(ji,jsl,ins) + &
5028               & wat_inf(ji) * deux / (dz(jsl) + dz(jsl+1))
5029          ! the time remaining before the next time step
5030          dt_tmp(ji) = dt_tmp(ji) - dt_inf(ji)
5031          ! and finally the infilt_tot (which is just used to check if there is a problem, below)
5032          infilt_tot(ji) = infilt_tot(ji) + infilt_tmp(ji) * dt_inf(ji)
5033       ENDDO
5034    ENDDO
5035
5036    !! 2.3 Resulting infiltration and surface runoff
5037    ru_infilt(:,ins) = flux_infilt(:) - infilt_tot(:)
5038    qinfilt_ns(:,ins) = infilt_tot(:)
5039
5040    !! 3. For water conservation check: we calculate the total SM at the beginning of the routine
5041    !!    and export the difference with the flux
5042    IF (check_cwrr) THEN
5043       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5044       DO jsl = 2,nslm-1
5045          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5046               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5047       ENDDO
5048       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5049       ! Normally, tcmf=tmci+infilt_tot
5050       check(:,ins) = tmcf(:)-(tmci(:)+infilt_tot(:))
5051    ENDIF
5052   
5053    !! 5. Local verification
5054    DO ji = 1, kjpindex
5055       IF (infilt_tot(ji) .LT. -min_sechiba .OR. infilt_tot(ji) .GT. flux_infilt(ji) + min_sechiba) THEN
5056          WRITE (numout,*) 'Error in the calculation of infilt tot', infilt_tot(ji)
5057          WRITE (numout,*) 'k, ji, jst, mc', k(ji,1:2), ji, ins, mc(ji,1,ins)
5058          CALL ipslerr_p(3, 'hydrol_soil_infilt', 'We will STOP now.','Error in calculation of infilt tot','')
5059       ENDIF
5060    ENDDO
5061
5062  END SUBROUTINE hydrol_soil_infilt
5063
5064
5065!! ================================================================================================================================
5066!! SUBROUTINE   : hydrol_soil_smooth_under_mcr
5067!!
5068!>\BRIEF        : Modifies the soil moisture profile to avoid under-residual values,
5069!!                then diagnoses the points where such "excess" values remain.
5070!!
5071!! DESCRIPTION  :
5072!! The "excesses" under-residual are corrected from top to bottom, by transfer of excesses
5073!! to the lower layers. The reverse transfer is performed to smooth any remaining "excess" in the bottom layer.
5074!! If some "excess" remain afterwards, the entire soil profile is at the threshold value (mcs or mcr),
5075!! and the remaining "excess" is necessarily concentrated in the top layer.
5076!! This allowing diagnosing the flag is_under_mcr.
5077!! Eventually, the remaining "excess" is split over the entire profile
5078!! 1. We calculate the total SM at the beginning of the routine
5079!! 2. Smoothes the profile to avoid negative values of punctual soil moisture
5080!! Note that we check that mc > min_sechiba in hydrol_soil
5081!! 3. For water conservation check, We calculate the total SM at the beginning of the routine,
5082!!    and export the difference with the flux
5083!!
5084!! RECENT CHANGE(S) : 2016 by A. Ducharne
5085!!
5086!! MAIN OUTPUT VARIABLE(S) :
5087!!
5088!! REFERENCE(S) :
5089!!
5090!! FLOWCHART    : None
5091!! \n
5092!_ ================================================================================================================================
5093!_ hydrol_soil_smooth_under_mcr
5094
5095  SUBROUTINE hydrol_soil_smooth_under_mcr(mcr, kjpindex, ins, njsc, is_under_mcr, check)
5096
5097    !- arguments
5098
5099    !! 0. Variable and parameter declaration
5100
5101    !! 0.1 Input variables
5102
5103    INTEGER(i_std), INTENT(in)                         :: kjpindex     !! Domain size
5104    INTEGER(i_std), INTENT(in)                         :: ins          !! Soiltile index (1-nstm, unitless)
5105    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc         !! Index of the dominant soil textural class in grid cell
5106                                                                       !! (1-nscm, unitless) 
5107    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: mcr          !! Residual volumetric water content (m^{3} m^{-3}) 
5108   
5109    !! 0.2 Output variables
5110
5111    LOGICAL, DIMENSION(kjpindex,nstm), INTENT(out)     :: is_under_mcr !! Flag diagnosing under residual soil moisture
5112    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check        !! delta SM - flux
5113
5114    !! 0.3 Modified variables
5115
5116    !! 0.4 Local variables
5117
5118    INTEGER(i_std)                       :: ji,jsl
5119    REAL(r_std)                          :: excess
5120    REAL(r_std), DIMENSION(kjpindex)     :: excessji
5121    REAL(r_std), DIMENSION(kjpindex)     :: tmci      !! total SM at beginning of routine
5122    REAL(r_std), DIMENSION(kjpindex)     :: tmcf      !! total SM at end of routine
5123
5124!_ ================================================================================================================================       
5125
5126    !! 1. We calculate the total SM at the beginning of the routine
5127    IF (check_cwrr) THEN
5128       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5129       DO jsl = 2,nslm-1
5130          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5131               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5132       ENDDO
5133       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5134    ENDIF
5135
5136    !! 2. Smoothes the profile to avoid negative values of punctual soil moisture
5137
5138    ! 2.1 smoothing from top to bottom
5139    DO jsl = 1,nslm-2
5140       DO ji=1, kjpindex
5141          excess = MAX(mcr(ji)-mc(ji,jsl,ins),zero)
5142          mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5143          mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) - excess * &
5144               &  (dz(jsl)+dz(jsl+1))/(dz(jsl+1)+dz(jsl+2))
5145       ENDDO
5146    ENDDO
5147
5148    jsl = nslm-1
5149    DO ji=1, kjpindex
5150       excess = MAX(mcr(ji)-mc(ji,jsl,ins),zero)
5151       mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5152       mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) - excess * &
5153            &  (dz(jsl)+dz(jsl+1))/dz(jsl+1)
5154    ENDDO
5155
5156    jsl = nslm
5157    DO ji=1, kjpindex
5158       excess = MAX(mcr(ji)-mc(ji,jsl,ins),zero)
5159       mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5160       mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) - excess * &
5161            &  dz(jsl)/(dz(jsl-1)+dz(jsl))
5162    ENDDO
5163
5164    ! 2.2 smoothing from bottom to top
5165    DO jsl = nslm-1,2,-1
5166       DO ji=1, kjpindex
5167          excess = MAX(mcr(ji)-mc(ji,jsl,ins),zero)
5168          mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
5169          mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) - excess * &
5170               &  (dz(jsl)+dz(jsl+1))/(dz(jsl-1)+dz(jsl))
5171       ENDDO
5172    ENDDO
5173
5174    ! 2.3 diagnoses is_under_mcr(ji), and updates the entire profile
5175    ! excess > 0
5176    DO ji=1, kjpindex
5177       excessji(ji) = mask_soiltile(ji,ins) * MAX(mcr(ji)-mc(ji,1,ins),zero)
5178    ENDDO
5179    DO ji=1, kjpindex
5180       mc(ji,1,ins) = mc(ji,1,ins) + excessji(ji) ! then mc(1)=mcr
5181       is_under_mcr(ji,ins) = (excessji(ji) .GT. min_sechiba)
5182    ENDDO
5183
5184    ! 2.4 The amount of water corresponding to excess in the top soil layer is redistributed in all soil layers
5185      ! -excess(ji) * dz(2) / deux donne le deficit total, negatif, en mm
5186      ! diviser par la profondeur totale en mm donne des delta_mc identiques en chaque couche, en mm
5187      ! retransformes en delta_mm par couche selon les bonnes eqs (eqs_hydrol.pdf, Eqs 13-15), puis sommes
5188      ! retourne bien le deficit total en mm
5189    DO jsl = 1, nslm
5190       DO ji=1, kjpindex
5191          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excessji(ji) * dz(2) / (deux * zmaxh*mille)
5192       ENDDO
5193    ENDDO
5194    ! This can lead to mc(jsl) < mcr depending on the value of excess,
5195    ! but this is no major pb for the diffusion
5196    ! Yet, we need to prevent evaporation if is_under_mcr
5197   
5198    !! Note that we check that mc > min_sechiba in hydrol_soil
5199
5200    ! We just make sure that mc remains at 0 where soiltile=0
5201    DO jsl = 1, nslm
5202       DO ji=1, kjpindex
5203          mc(ji,jsl,ins) = mask_soiltile(ji,ins) * mc(ji,jsl,ins)
5204       ENDDO
5205    ENDDO
5206
5207    !! 3. For water conservation check, We calculate the total SM at the beginning of the routine,
5208    !!    and export the difference with the flux
5209    IF (check_cwrr) THEN
5210       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5211       DO jsl = 2,nslm-1
5212          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5213               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5214       ENDDO
5215       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5216       ! Normally, tcmf=tmci since we just redistribute the deficit
5217       check(:,ins) = tmcf(:)-tmci(:)
5218    ENDIF
5219       
5220  END SUBROUTINE hydrol_soil_smooth_under_mcr
5221
5222
5223!! ================================================================================================================================
5224!! SUBROUTINE   : hydrol_soil_smooth_over_mcs
5225!!
5226!>\BRIEF        : Modifies the soil moisture profile to avoid over-saturation values,
5227!!                by putting the excess in ru_ns
5228!!                Thus, no point remain where such "excess" values remain (is_over_mcs becomes useless)
5229!!
5230!! DESCRIPTION  :
5231!! The "excesses" over-saturation are corrected from top to bottom, by transfer of excesses
5232!! to the lower layers. The reverse transfer is performed to smooth any remaining "excess" in the bottom layer.
5233!! If some "excess" remain afterwards, the entire soil profile is at the threshold value (mcs or mcr),
5234!! and the remaining "excess" is necessarily concentrated in the top layer.
5235!! Eventually, the remaining "excess" creates rudr_corr, to be added to ru_ns or dr_ns
5236!! 1. We calculate the total SM at the beginning of the routine
5237!! 2. In case of over-saturation we put the water where it is possible by smoothing
5238!! 3. The excess is transformed into surface runoff, with conversion from m3/m3 to kg/m2
5239!! 4. For water conservation checks, we calculate the total SM at the beginning of the routine,
5240!!    and export the difference with the flux
5241!!
5242!! RECENT CHANGE(S) : 2016 by A. Ducharne
5243!!
5244!! MAIN OUTPUT VARIABLE(S) :
5245!!
5246!! REFERENCE(S) :
5247!!
5248!! FLOWCHART    : None
5249!! \n
5250!_ ================================================================================================================================
5251!_ hydrol_soil_smooth_over_mcs
5252
5253  SUBROUTINE hydrol_soil_smooth_over_mcs(mcs ,kjpindex, ins, njsc, is_over_mcs, rudr_corr, check)
5254
5255    !- arguments
5256
5257    !! 0. Variable and parameter declaration
5258
5259    !! 0.1 Input variables
5260    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size
5261    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless)
5262    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell
5263                                                                            !! (1-nscm, unitless)
5264    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: mcs             !! Saturated volumetric water content (m^{3} m^{-3})
5265   
5266    !! 0.2 Output variables
5267
5268    LOGICAL, DIMENSION(kjpindex), INTENT(out)            :: is_over_mcs     !! Flag diagnosing over saturated soil moisture 
5269    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out)   :: check           !! delta SM - flux
5270   
5271    !! 0.3 Modified variables   
5272    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(inout):: rudr_corr         !! Surface runoff produced to correct excess (mm/dtstep)
5273
5274    !! 0.4 Local variables
5275
5276    INTEGER(i_std)                        :: ji,jsl
5277    REAL(r_std)                           :: excess
5278    REAL(r_std), DIMENSION(kjpindex)      :: tmci    !! total SM at beginning of routine
5279    REAL(r_std), DIMENSION(kjpindex)      :: tmcf    !! total SM at end of routine
5280
5281    !_ ================================================================================================================================
5282
5283    !! 1. We calculate the total SM at the beginning of the routine
5284    IF (check_cwrr) THEN
5285       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5286       DO jsl = 2,nslm-1
5287          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5288               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5289       ENDDO
5290       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5291    ENDIF
5292
5293    !! 2. In case of over-saturation we put the water where it is possible by smoothing
5294
5295    ! 2.1 smoothing from top to bottom
5296    DO jsl = 1, nslm-2
5297       DO ji=1, kjpindex
5298          excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
5299          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5300          mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) + excess * &
5301               &  (dz(jsl)+dz(jsl+1))/(dz(jsl+1)+dz(jsl+2))
5302       ENDDO
5303    ENDDO
5304
5305    jsl = nslm-1
5306    DO ji=1, kjpindex
5307       excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
5308       mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5309       mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) + excess * &
5310            &  (dz(jsl)+dz(jsl+1))/dz(jsl+1)
5311    ENDDO
5312
5313    jsl = nslm
5314    DO ji=1, kjpindex
5315       excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
5316       mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5317       mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) + excess * &
5318            &  dz(jsl)/(dz(jsl-1)+dz(jsl))
5319    ENDDO
5320
5321    ! 2.2 smoothing from bottom to top, leading  to keep most of the excess in the soil column
5322    DO jsl = nslm-1,2,-1
5323       DO ji=1, kjpindex
5324          excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
5325          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
5326          mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) + excess * &
5327               &  (dz(jsl)+dz(jsl+1))/(dz(jsl-1)+dz(jsl))
5328       ENDDO
5329    ENDDO
5330
5331    !! 3. The excess is transformed into surface runoff, with conversion from m3/m3 to kg/m2
5332
5333    DO ji=1, kjpindex
5334       excess = mask_soiltile(ji,ins) * MAX(mc(ji,1,ins)-mcs(ji),zero)
5335       mc(ji,1,ins) = mc(ji,1,ins) - excess ! then mc(1)=mcs
5336       rudr_corr(ji,ins) = rudr_corr(ji,ins) + excess * dz(2) / deux 
5337       is_over_mcs(ji) = .FALSE.
5338    ENDDO
5339
5340    !! 4. For water conservation checks, we calculate the total SM at the beginning of the routine,
5341    !!    and export the difference with the flux
5342
5343    IF (check_cwrr) THEN
5344       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5345       DO jsl = 2,nslm-1
5346          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5347               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5348       ENDDO
5349       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5350       ! Normally, tcmf=tmci-rudr_corr
5351       check(:,ins) = tmcf(:)-(tmci(:)-rudr_corr(:,ins))
5352    ENDIF
5353   
5354  END SUBROUTINE hydrol_soil_smooth_over_mcs
5355
5356 !! ================================================================================================================================
5357!! SUBROUTINE   : hydrol_soil_smooth_over_mcs2
5358!!
5359!>\BRIEF        : Modifies the soil moisture profile to avoid over-saturation values,
5360!!                by putting the excess in ru_ns
5361!!                Thus, no point remain where such "excess" values remain (is_over_mcs becomes useless)
5362!!
5363!! DESCRIPTION  :
5364!! The "excesses" over-saturation are corrected, by directly discarding the excess as rudr_corr,
5365!! to be added to ru_ns or dr_nsrunoff (via rudr_corr).
5366!! Therefore, there is no more smoothing, and this helps preventing the saturation of too many layers,
5367!! which leads to numerical errors with tridiag.
5368!! 1. We calculate the total SM at the beginning of the routine
5369!! 2. In case of over-saturation, we directly eliminate the excess via rudr_corr
5370!!    The calculation of the adjustement flux needs to account for nodes n-1 and n+1.
5371!! 3. For water conservation checks, we calculate the total SM at the beginning of the routine,
5372!!    and export the difference with the flux   
5373!!
5374!! RECENT CHANGE(S) : 2016 by A. Ducharne
5375!!
5376!! MAIN OUTPUT VARIABLE(S) :
5377!!
5378!! REFERENCE(S) :
5379!!
5380!! FLOWCHART    : None
5381!! \n
5382!_ ================================================================================================================================
5383!_ hydrol_soil_smooth_over_mcs2
5384
5385  SUBROUTINE hydrol_soil_smooth_over_mcs2(mcs, kjpindex, ins, njsc, is_over_mcs, rudr_corr, check)
5386
5387    !- arguments
5388
5389    !! 0. Variable and parameter declaration
5390
5391    !! 0.1 Input variables
5392    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size
5393    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless)
5394    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell
5395                                                                            !! (1-nscm, unitless)
5396    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: mcs             !! Saturated volumetric water content (m^{3} m^{-3})
5397   
5398    !! 0.2 Output variables
5399
5400    LOGICAL, DIMENSION(kjpindex), INTENT(out)            :: is_over_mcs     !! Flag diagnosing over saturated soil moisture 
5401    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out)   :: check           !! delta SM - flux
5402   
5403    !! 0.3 Modified variables   
5404    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(inout):: rudr_corr         !! Surface runoff produced to correct excess (mm/dtstep)
5405
5406    !! 0.4 Local variables
5407
5408    INTEGER(i_std)                        :: ji,jsl
5409    REAL(r_std), DIMENSION(kjpindex,nslm) :: excess
5410    REAL(r_std), DIMENSION(kjpindex)      :: tmci    !! total SM at beginning of routine
5411    REAL(r_std), DIMENSION(kjpindex)      :: tmcf    !! total SM at end of routine
5412
5413!_ ================================================================================================================================       
5414    !-
5415
5416    !! 1. We calculate the total SM at the beginning of the routine
5417    IF (check_cwrr) THEN
5418       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5419       DO jsl = 2,nslm-1
5420          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5421               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5422       ENDDO
5423       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5424    ENDIF 
5425
5426    !! 2. In case of over-saturation, we don't do any smoothing,
5427    !! but directly eliminate the excess as runoff (via rudr_corr)
5428    !    we correct the calculation of the adjustement flux, which needs to account for nodes n-1 and n+1 
5429    !    for the calculation to remain simple and accurate, we directly drain all the oversaturated mc,
5430    !    without transfering to lower layers       
5431
5432    !! 2.1 thresholding from top to bottom, with excess defined along jsl
5433    DO jsl = 1, nslm
5434       DO ji=1, kjpindex
5435          excess(ji,jsl) = MAX(mc(ji,jsl,ins)-mcs(ji),zero) ! >=0
5436          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess(ji,jsl) ! here mc either does not change or decreases
5437       ENDDO
5438    ENDDO
5439
5440    !! 2.2 To ensure conservation, this needs to be balanced by additional drainage (in kg/m2/dt)                       
5441    DO ji = 1, kjpindex
5442       rudr_corr(ji,ins) = dz(2) * ( trois*excess(ji,1) + excess(ji,2) )/huit ! top layer = initialisation 
5443    ENDDO
5444    DO jsl = 2,nslm-1 ! intermediate layers     
5445       DO ji = 1, kjpindex
5446          rudr_corr(ji,ins) = rudr_corr(ji,ins) + dz(jsl) &
5447               & * (trois*excess(ji,jsl)+excess(ji,jsl-1))/huit &
5448               & + dz(jsl+1) * (trois*excess(ji,jsl)+excess(ji,jsl+1))/huit
5449       ENDDO
5450    ENDDO
5451    DO ji = 1, kjpindex
5452       rudr_corr(ji,ins) = rudr_corr(ji,ins) + dz(nslm) &    ! bottom layer
5453            & * (trois * excess(ji,nslm) + excess(ji,nslm-1))/huit
5454       is_over_mcs(ji) = .FALSE. 
5455    END DO
5456
5457    !! 3. For water conservation checks, we calculate the total SM at the beginning of the routine,
5458    !!    and export the difference with the flux
5459
5460    IF (check_cwrr) THEN
5461       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
5462       DO jsl = 2,nslm-1
5463          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
5464               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
5465       ENDDO
5466       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
5467       ! Normally, tcmf=tmci-rudr_corr
5468       check(:,ins) = tmcf(:)-(tmci(:)-rudr_corr(:,ins))
5469    ENDIF
5470   
5471  END SUBROUTINE hydrol_soil_smooth_over_mcs2
5472
5473
5474!! ================================================================================================================================
5475!! SUBROUTINE   : hydrol_diag_soil_flux
5476!!
5477!>\BRIEF        : This subroutine diagnoses the vertical liquid water fluxes between the
5478!!                different soil layers, based on each layer water budget. It also checks the
5479!!                corresponding water conservation (during redistribution).
5480!!
5481!! DESCRIPTION  :
5482!! 1. Initialize qflux_ns from the bottom, with dr_ns
5483!! 2. Between layer nslm and nslm-1, by means of water budget knowing mc changes and flux at the lowest interface
5484!! 3. We go up, and deduct qflux_ns(1:nslm-2), still by means of water budget
5485!! 4. Water balance verification: pursuing upward water budget, the flux at the surface should equal -flux_top 
5486!!
5487!! RECENT CHANGE(S) : 2016 by A. Ducharne to fit hydrol_soil
5488!!
5489!! MAIN OUTPUT VARIABLE(S) :
5490!!
5491!! REFERENCE(S) :
5492!!
5493!! FLOWCHART    : None
5494!! \n
5495!_ ================================================================================================================================
5496
5497  SUBROUTINE hydrol_diag_soil_flux(kjpindex,ins,mclint,flux_top)
5498    !
5499    !! 0. Variable and parameter declaration
5500
5501    !! 0.1 Input variables
5502
5503    INTEGER(i_std), INTENT(in)                         :: kjpindex        !! Domain size
5504    INTEGER(i_std), INTENT(in)                         :: ins             !! index of soil type
5505    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT(in) :: mclint          !! mc values at the beginning of the time step
5506    REAL(r_std), DIMENSION (kjpindex), INTENT(in)      :: flux_top        !! Exfiltration (bare soil evaporation minus infiltration)
5507   
5508    !! 0.2 Output variables
5509
5510    !! 0.3 Modified variables
5511
5512    !! 0.4 Local variables
5513    REAL(r_std), DIMENSION (kjpindex)                  :: check_temp      !! Diagnosed flux at soil surface, should equal -flux_top
5514    INTEGER(i_std)                                     :: jsl,ji
5515
5516    !_ ================================================================================================================================
5517
5518    !- Compute the diffusion flux at every level from bottom to top (using mcl,mclint, and sink values)
5519    DO ji = 1, kjpindex
5520
5521       !! 1. Initialize qflux_ns from the bottom, with dr_ns
5522       jsl = nslm
5523       qflux_ns(ji,jsl,ins) = dr_ns(ji,ins)
5524       !! 2. Between layer nslm and nslm-1, by means of water budget
5525       !!    knowing mc changes and flux at the lowest interface
5526       !     qflux_ns is downward
5527       jsl = nslm-1
5528       qflux_ns(ji,jsl,ins) = qflux_ns(ji,jsl+1,ins) & 
5529            &  + (mcl(ji,jsl,ins)-mclint(ji,jsl) &
5530            &  + trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1)) &
5531            &  * (dz(jsl+1)/huit) &
5532            &  + rootsink(ji,jsl+1,ins) 
5533    ENDDO
5534
5535    !! 3. We go up, and deduct qflux_ns(1:nslm-2), still by means of water budget
5536    ! Here, qflux_ns(ji,1,ins) is the downward flux between the top soil layer and the 2nd one
5537    DO jsl = nslm-2,1,-1
5538       DO ji = 1, kjpindex
5539          qflux_ns(ji,jsl,ins) = qflux_ns(ji,jsl+1,ins) & 
5540               &  + (mcl(ji,jsl,ins)-mclint(ji,jsl) &
5541               &  + trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1)) &
5542               &  * (dz(jsl+1)/huit) &
5543               &  + rootsink(ji,jsl+1,ins) &
5544               &  + (dz(jsl+2)/huit) &
5545               &  * (trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1) &
5546               &  + mcl(ji,jsl+2,ins)-mclint(ji,jsl+2)) 
5547       END DO
5548    ENDDO
5549   
5550    !! 4. Water balance verification: pursuing upward water budget, the flux at the surface (check_temp)
5551    !! should equal -flux_top
5552    DO ji = 1, kjpindex
5553
5554       check_temp(ji) =  qflux_ns(ji,1,ins) + (dz(2)/huit) &
5555            &  * (trois* (mcl(ji,1,ins)-mclint(ji,1)) + (mcl(ji,2,ins)-mclint(ji,2))) &
5556            &  + rootsink(ji,1,ins)   
5557       ! flux_top is positive when upward, while check_temp is positive when downward
5558       check_top_ns(ji,ins) = flux_top(ji)+check_temp(ji)
5559
5560       IF (ABS(check_top_ns(ji,ins))/dt_sechiba .GT. min_sechiba) THEN
5561          ! Diagnosed (check_temp) and imposed (flux_top) differ by more than 1.e-8 mm/s
5562          WRITE(numout,*) 'Problem in the water balance, qflux_ns computation, surface fluxes', flux_top(ji),check_temp(ji)
5563          WRITE(numout,*) 'Diagnosed and imposed fluxes differ by more than 1.e-8 mm/s: ', check_top_ns(ji,ins)
5564          WRITE(numout,*) 'ji', ji, 'jsl',jsl,'ins',ins
5565          WRITE(numout,*) 'mclint', mclint(ji,:)
5566          WRITE(numout,*) 'mcl', mcl(ji,:,ins)
5567          WRITE (numout,*) 'rootsink', rootsink(ji,1,ins)
5568          CALL ipslerr_p(1, 'hydrol_diag_soil_flux', 'NOTE:',&
5569               & 'Problem in the water balance, qflux_ns computation','')
5570       ENDIF
5571    ENDDO
5572
5573  END SUBROUTINE hydrol_diag_soil_flux
5574
5575
5576!! ================================================================================================================================
5577!! SUBROUTINE   : hydrol_soil_tridiag
5578!!
5579!>\BRIEF        This subroutine solves a set of linear equations which has a tridiagonal coefficient matrix.
5580!!
5581!! DESCRIPTION  : It is only applied in the grid-cells where resolv(ji)=TRUE
5582!!
5583!! RECENT CHANGE(S) : None
5584!!
5585!! MAIN OUTPUT VARIABLE(S) : mcl (global module variable)
5586!!
5587!! REFERENCE(S) :
5588!!
5589!! FLOWCHART    : None
5590!! \n
5591!_ ================================================================================================================================
5592!_ hydrol_soil_tridiag
5593
5594  SUBROUTINE hydrol_soil_tridiag(kjpindex,ins)
5595
5596    !- arguments
5597
5598    !! 0. Variable and parameter declaration
5599
5600    !! 0.1 Input variables
5601
5602    INTEGER(i_std), INTENT(in)                         :: kjpindex        !! Domain size
5603    INTEGER(i_std), INTENT(in)                         :: ins             !! number of soil type
5604
5605    !! 0.2 Output variables
5606
5607    !! 0.3 Modified variables
5608
5609    !! 0.4 Local variables
5610
5611    INTEGER(i_std)                                     :: ji,jsl
5612    REAL(r_std), DIMENSION(kjpindex)                   :: bet
5613    REAL(r_std), DIMENSION(kjpindex,nslm)              :: gam
5614
5615!_ ================================================================================================================================
5616    DO ji = 1, kjpindex
5617
5618       IF (resolv(ji)) THEN
5619          bet(ji) = tmat(ji,1,2)
5620          mcl(ji,1,ins) = rhs(ji,1)/bet(ji)
5621       ENDIF
5622    ENDDO
5623
5624    DO jsl = 2,nslm
5625       DO ji = 1, kjpindex
5626         
5627          IF (resolv(ji)) THEN
5628
5629             gam(ji,jsl) = tmat(ji,jsl-1,3)/bet(ji)
5630             bet(ji) = tmat(ji,jsl,2) - tmat(ji,jsl,1)*gam(ji,jsl)
5631             mcl(ji,jsl,ins) = (rhs(ji,jsl)-tmat(ji,jsl,1)*mcl(ji,jsl-1,ins))/bet(ji)
5632          ENDIF
5633
5634       ENDDO
5635    ENDDO
5636
5637    DO ji = 1, kjpindex
5638       IF (resolv(ji)) THEN
5639          DO jsl = nslm-1,1,-1
5640             mcl(ji,jsl,ins) = mcl(ji,jsl,ins) - gam(ji,jsl+1)*mcl(ji,jsl+1,ins)
5641          ENDDO
5642       ENDIF
5643    ENDDO
5644
5645  END SUBROUTINE hydrol_soil_tridiag
5646
5647
5648!! ================================================================================================================================
5649!! SUBROUTINE   : hydrol_soil_coef
5650!!
5651!>\BRIEF        Computes coef for the linearised hydraulic conductivity
5652!! k_lin=a_lin mc_lin+b_lin and the linearised diffusivity d_lin.
5653!!
5654!! DESCRIPTION  :
5655!! First, we identify the interval i in which the current value of mc is located.
5656!! Then, we give the values of the linearized parameters to compute
5657!! conductivity and diffusivity as K=a*mc+b and d.
5658!!
5659!! RECENT CHANGE(S) : Addition of the dependence to profil_froz_hydro_ns
5660!!
5661!! MAIN OUTPUT VARIABLE(S) :
5662!!
5663!! REFERENCE(S) :
5664!!
5665!! FLOWCHART    : None
5666!! \n
5667!_ ================================================================================================================================
5668!_ hydrol_soil_coef
5669
5670  SUBROUTINE hydrol_soil_coef(mcr, mcs, kjpindex,ins,njsc)
5671
5672    IMPLICIT NONE
5673    !
5674    !! 0. Variable and parameter declaration
5675
5676    !! 0.1 Input variables
5677    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size
5678    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type
5679    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class
5680                                                                          !! in the grid cell (1-nscm, unitless)
5681    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
5682    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
5683
5684    !! 0.2 Output variables
5685
5686    !! 0.3 Modified variables
5687
5688    !! 0.4 Local variables
5689
5690    INTEGER(i_std)                                    :: jsl,ji,i
5691    REAL(r_std)                                       :: mc_ratio
5692    REAL(r_std)                                       :: mc_used    !! Used liquid water content
5693    REAL(r_std)                                       :: x,m
5694   
5695!_ ================================================================================================================================
5696
5697    IF (ok_freeze_cwrr) THEN
5698   
5699       ! Calculation of liquid and frozen saturation degrees with respect to residual
5700       ! x=liquid saturation degree/residual=(mcl-mcr)/(mcs-mcr)
5701       ! 1-x=frozen saturation degree/residual=(mcfc-mcr)/(mcs-mcr) (=profil_froz_hydro)
5702       
5703       DO jsl=1,nslm
5704          DO ji=1,kjpindex
5705             
5706             x = 1._r_std - profil_froz_hydro_ns(ji, jsl,ins)
5707             
5708             ! mc_used is used in the calculation of hydrological properties
5709             ! It corresponds to a liquid mc, but the expression is different from mcl in hydrol_soil,
5710             ! to ensure that we get the a, b, d of the first bin when mcl<mcr
5711             mc_used = mcr(ji)+x*MAX((mc(ji,jsl, ins)-mcr(ji)),zero) 
5712             !
5713             ! calcul de k based on mc_liq
5714             !
5715             i= MAX(imin, MIN(imax-1, INT(imin +(imax-imin)*(mc_used-mcr(ji))/(mcs(ji)-mcr(ji)))))
5716             a(ji,jsl) = a_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
5717             b(ji,jsl) = b_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
5718             d(ji,jsl) = d_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm^2/d
5719             k(ji,jsl) = kfact_root(ji,jsl,ins) * MAX(k_lin(imin+1,jsl,ji), &
5720                  a_lin(i,jsl,ji) * mc_used + b_lin(i,jsl,ji)) ! in mm/d
5721          ENDDO ! loop on grid
5722       ENDDO
5723             
5724    ELSE
5725       ! .NOT. ok_freeze_cwrr
5726       DO jsl=1,nslm
5727          DO ji=1,kjpindex 
5728             
5729             ! it is impossible to consider a mc<mcr for the binning
5730             mc_ratio = MAX(mc(ji,jsl,ins)-mcr(ji), zero)/(mcs(ji)-mcr(ji))
5731             
5732             i= MAX(MIN(INT((imax-imin)*mc_ratio)+imin , imax-1), imin)
5733             a(ji,jsl) = a_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
5734             b(ji,jsl) = b_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
5735             d(ji,jsl) = d_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm^2/d
5736             k(ji,jsl) = kfact_root(ji,jsl,ins) * MAX(k_lin(imin+1,jsl,ji), &
5737                  a_lin(i,jsl,ji) * mc(ji,jsl,ins) + b_lin(i,jsl,ji))  ! in mm/d
5738          END DO
5739       END DO
5740    ENDIF
5741   
5742  END SUBROUTINE hydrol_soil_coef
5743
5744!! ================================================================================================================================
5745!! SUBROUTINE   : hydrol_soil_froz
5746!!
5747!>\BRIEF        Computes profil_froz_hydro_ns, the fraction of frozen water in the soil layers.
5748!!
5749!! DESCRIPTION  :
5750!!
5751!! RECENT CHANGE(S) : Created by A. Ducharne in 2016.
5752!!
5753!! MAIN OUTPUT VARIABLE(S) : profil_froz_hydro_ns
5754!!
5755!! REFERENCE(S) :
5756!!
5757!! FLOWCHART    : None
5758!! \n
5759!_ ================================================================================================================================
5760!_ hydrol_soil_froz
5761 
5762  SUBROUTINE hydrol_soil_froz(nvan, avan, mcr, mcs, kjpindex,ins,njsc,stempdiag)
5763
5764    IMPLICIT NONE
5765    !
5766    !! 0. Variable and parameter declaration
5767
5768    !! 0.1 Input variables
5769
5770    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size
5771    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type
5772    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class
5773                                                                          !! in the grid cell (1-nscm, unitless)
5774    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: nvan             !! Van Genuchten coeficients n (unitless)
5775    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: avan             !! Van Genuchten coeficients a (mm-1})
5776    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
5777    REAL(r_std),DIMENSION (kjpindex), INTENT (in)     :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
5778    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in):: stempdiag        !! Diagnostic temp profile from thermosoil
5779
5780    !! 0.2 Output variables
5781
5782    !! 0.3 Modified variables
5783
5784    !! 0.4 Local variables
5785
5786    INTEGER(i_std)                                    :: jsl,ji,i
5787    REAL(r_std)                                       :: x,m
5788    REAL(r_std)                                       :: denom
5789    REAL(r_std),DIMENSION (kjpindex)                  :: froz_frac_moy
5790    REAL(r_std),DIMENSION (kjpindex)                  :: smtot_moy
5791    REAL(r_std),DIMENSION (kjpindex,nslm)             :: mc_ns
5792   
5793!_ ================================================================================================================================
5794
5795!    ONLY FOR THE (ok_freeze_cwrr) CASE
5796   
5797       ! Calculation of liquid and frozen saturation degrees above residual moisture
5798       !   x=liquid saturation degree/residual=(mcl-mcr)/(mcs-mcr)
5799       !   1-x=frozen saturation degree/residual=(mcfc-mcr)/(mcs-mcr) (=profil_froz_hydro)
5800       ! It's important for the good work of the water diffusion scheme (tridiag) that the total
5801       ! liquid water also includes mcr, so mcl > 0 even when x=0
5802       
5803       DO jsl=1,nslm
5804          DO ji=1,kjpindex
5805             ! Van Genuchten parameter for thermodynamical calculation
5806             m = 1. -1./nvan(ji)
5807           
5808             IF ((.NOT. ok_thermodynamical_freezing).OR.(mc(ji,jsl, ins).LT.(mcr(ji)+min_sechiba))) THEN
5809                ! Linear soil freezing or soil moisture below residual
5810                IF (stempdiag(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN
5811                   x=1._r_std
5812                ELSE IF ( (stempdiag(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &
5813                     (stempdiag(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN
5814                   x=(stempdiag(ji, jsl)-(ZeroCelsius-fr_dT/2.))/fr_dT
5815                ELSE
5816                   x=0._r_std
5817                ENDIF
5818             ELSE IF (ok_thermodynamical_freezing) THEN
5819                ! Thermodynamical soil freezing
5820                IF (stempdiag(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN
5821                   x=1._r_std
5822                ELSE IF ( (stempdiag(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &
5823                     (stempdiag(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN
5824                   ! Factor 2.2 from the PhD of Isabelle Gouttevin
5825                   x=MIN(((mcs(ji)-mcr(ji)) &
5826                        *((2.2*1000.*avan(ji)*(ZeroCelsius+fr_dT/2.-stempdiag(ji, jsl)) &
5827                        *lhf/ZeroCelsius/10.)**nvan(ji)+1.)**(-m)) / &
5828                        (mc(ji,jsl, ins)-mcr(ji)),1._r_std)               
5829                ELSE
5830                   x=0._r_std 
5831                ENDIF
5832             ENDIF
5833             
5834             profil_froz_hydro_ns(ji,jsl,ins) = 1._r_std-x
5835             
5836             mc_ns(ji,jsl)=mc(ji,jsl,ins)/mcs(ji)
5837
5838          ENDDO ! loop on grid
5839       ENDDO
5840   
5841       ! Applay correction on the frozen fraction
5842       ! Depends on two external parameters: froz_frac_corr and smtot_corr
5843       froz_frac_moy(:)=zero
5844       denom=zero
5845       DO jsl=1,nslm
5846          froz_frac_moy(:)=froz_frac_moy(:)+dh(jsl)*profil_froz_hydro_ns(:,jsl,ins)
5847          denom=denom+dh(jsl)
5848       ENDDO
5849       froz_frac_moy(:)=froz_frac_moy(:)/denom
5850
5851       smtot_moy(:)=zero
5852       denom=zero
5853       DO jsl=1,nslm-1
5854          smtot_moy(:)=smtot_moy(:)+dh(jsl)*mc_ns(:,jsl)
5855          denom=denom+dh(jsl)
5856       ENDDO
5857       smtot_moy(:)=smtot_moy(:)/denom
5858
5859       DO jsl=1,nslm
5860          profil_froz_hydro_ns(:,jsl,ins)=MIN(profil_froz_hydro_ns(:,jsl,ins)* &
5861                                              (froz_frac_moy(:)**froz_frac_corr)*(smtot_moy(:)**smtot_corr), max_froz_hydro)
5862       ENDDO
5863
5864     END SUBROUTINE hydrol_soil_froz
5865     
5866
5867!! ================================================================================================================================
5868!! SUBROUTINE   : hydrol_soil_setup
5869!!
5870!>\BRIEF        This subroutine computes the matrix coef. 
5871!!
5872!! DESCRIPTION  : None
5873!!
5874!! RECENT CHANGE(S) : None
5875!!
5876!! MAIN OUTPUT VARIABLE(S) : matrix coef
5877!!
5878!! REFERENCE(S) :
5879!!
5880!! FLOWCHART    : None
5881!! \n
5882!_ ================================================================================================================================
5883
5884  SUBROUTINE hydrol_soil_setup(kjpindex,ins)
5885
5886
5887    IMPLICIT NONE
5888    !
5889    !! 0. Variable and parameter declaration
5890
5891    !! 0.1 Input variables
5892    INTEGER(i_std), INTENT(in)                        :: kjpindex          !! Domain size
5893    INTEGER(i_std), INTENT(in)                        :: ins               !! index of soil type
5894
5895    !! 0.2 Output variables
5896
5897    !! 0.3 Modified variables
5898
5899    !! 0.4 Local variables
5900
5901    INTEGER(i_std) :: jsl,ji
5902    REAL(r_std)                        :: temp3, temp4
5903
5904!_ ================================================================================================================================
5905    !-we compute tridiag matrix coefficients (LEFT and RIGHT)
5906    ! of the system to solve [LEFT]*mc_{t+1}=[RIGHT]*mc{t}+[add terms]:
5907    ! e(nslm),f(nslm),g1(nslm) for the [left] vector
5908    ! and ep(nslm),fp(nslm),gp(nslm) for the [right] vector
5909
5910    ! w_time=1 (in constantes_soil) indicates implicit computation for diffusion
5911    temp3 = w_time*(dt_sechiba/one_day)/deux
5912    temp4 = (un-w_time)*(dt_sechiba/one_day)/deux
5913
5914    ! Passage to arithmetic means for layer averages also in this subroutine : Aurelien 11/05/10
5915
5916    !- coefficient for first layer
5917    DO ji = 1, kjpindex
5918       e(ji,1) = zero
5919       f(ji,1) = trois * dz(2)/huit  + temp3 &
5920            & * ((d(ji,1)+d(ji,2))/(dz(2))+a(ji,1))
5921       g1(ji,1) = dz(2)/(huit)       - temp3 &
5922            & * ((d(ji,1)+d(ji,2))/(dz(2))-a(ji,2))
5923       ep(ji,1) = zero
5924       fp(ji,1) = trois * dz(2)/huit - temp4 &
5925            & * ((d(ji,1)+d(ji,2))/(dz(2))+a(ji,1))
5926       gp(ji,1) = dz(2)/(huit)       + temp4 &
5927            & * ((d(ji,1)+d(ji,2))/(dz(2))-a(ji,2))
5928    ENDDO
5929
5930    !- coefficient for medium layers
5931
5932    DO jsl = 2, nslm-1
5933       DO ji = 1, kjpindex
5934          e(ji,jsl) = dz(jsl)/(huit)                        - temp3 &
5935               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl))+a(ji,jsl-1))
5936
5937          f(ji,jsl) = trois * (dz(jsl)+dz(jsl+1))/huit  + temp3 &
5938               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl)) + &
5939               & (d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1)) )
5940
5941          g1(ji,jsl) = dz(jsl+1)/(huit)                     - temp3 &
5942               & * ((d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1))-a(ji,jsl+1))
5943
5944          ep(ji,jsl) = dz(jsl)/(huit)                       + temp4 &
5945               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl))+a(ji,jsl-1))
5946
5947          fp(ji,jsl) = trois * (dz(jsl)+dz(jsl+1))/huit - temp4 &
5948               & * ( (d(ji,jsl)+d(ji,jsl-1))/(dz(jsl)) + &
5949               & (d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1)) )
5950
5951          gp(ji,jsl) = dz(jsl+1)/(huit)                     + temp4 &
5952               & *((d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1))-a(ji,jsl+1))
5953       ENDDO
5954    ENDDO
5955
5956    !- coefficient for last layer
5957    DO ji = 1, kjpindex
5958       e(ji,nslm) = dz(nslm)/(huit)        - temp3 &
5959            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm))+a(ji,nslm-1))
5960       f(ji,nslm) = trois * dz(nslm)/huit  + temp3 &
5961            & * ((d(ji,nslm)+d(ji,nslm-1)) / (dz(nslm)) &
5962            & -a(ji,nslm)*(un-deux*free_drain_coef(ji,ins)))
5963       g1(ji,nslm) = zero
5964       ep(ji,nslm) = dz(nslm)/(huit)       + temp4 &
5965            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm))+a(ji,nslm-1))
5966       fp(ji,nslm) = trois * dz(nslm)/huit - temp4 &
5967            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm)) &
5968            & -a(ji,nslm)*(un-deux*free_drain_coef(ji,ins)))
5969       gp(ji,nslm) = zero
5970    ENDDO
5971
5972  END SUBROUTINE hydrol_soil_setup
5973
5974 
5975!! ================================================================================================================================
5976!! SUBROUTINE   : hydrol_split_soil
5977!!
5978!>\BRIEF        Splits 2d variables into 3d variables, per soiltile (_ns suffix), at the beginning of hydrol
5979!!              At this stage, the forcing fluxes to hydrol are transformed from grid-cell averages
5980!!              to mean fluxes over vegtot=sum(soiltile) 
5981!!
5982!! DESCRIPTION  :
5983!! 1. Split 2d variables into 3d variables, per soiltile
5984!! 1.1 Throughfall
5985!! 1.2 Bare soil evaporation
5986!! 1.2.2 ae_ns new
5987!! 1.3 transpiration
5988!! 1.4 root sink
5989!! 2. Verification: Check if the deconvolution is correct and conserves the fluxes
5990!! 2.1 precisol
5991!! 2.2 ae_ns and evapnu
5992!! 2.3 transpiration
5993!! 2.4 root sink
5994!!
5995!! RECENT CHANGE(S) : 2016 by A. Ducharne to match the simplification of hydrol_soil
5996!!
5997!! MAIN OUTPUT VARIABLE(S) :
5998!!
5999!! REFERENCE(S) :
6000!!
6001!! FLOWCHART    : None
6002!! \n
6003!_ ================================================================================================================================
6004!_ hydrol_split_soil
6005
6006  SUBROUTINE hydrol_split_soil (kjpindex, veget_max, soiltile, vevapnu, transpir, humrel, &
6007       evap_bare_lim, evap_bare_lim_ns, tot_bare_soil)
6008    !
6009    ! interface description
6010
6011    !! 0. Variable and parameter declaration
6012
6013    !! 0.1 Input variables
6014
6015    INTEGER(i_std), INTENT(in)                               :: kjpindex
6016    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(in)       :: veget_max        !! max Vegetation map
6017    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soiltile within vegtot (0-1, unitless)
6018    REAL(r_std), DIMENSION (kjpindex), INTENT (in)           :: vevapnu          !! Bare soil evaporation
6019    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: transpir         !! Transpiration
6020    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: humrel           !! Relative humidity
6021    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evap_bare_lim    !!   
6022    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(in)       :: evap_bare_lim_ns !!   
6023    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_bare_soil    !! Total evaporating bare soil fraction
6024
6025    !! 0.4 Local variables
6026
6027    INTEGER(i_std)                                :: ji, jv, jsl, jst
6028    REAL(r_std), DIMENSION (kjpindex)             :: tmp_check1
6029    REAL(r_std), DIMENSION (kjpindex)             :: tmp_check2
6030    REAL(r_std), DIMENSION (kjpindex,nstm)        :: tmp_check3
6031    LOGICAL                                       :: error
6032!_ ================================================================================================================================
6033   
6034    !! 1. Split 2d variables into 3d variables, per soiltile
6035   
6036    ! Reminders:
6037    !  corr_veg_soil(:,nvm,nstm) = PFT fraction per soiltile in each grid-cell
6038    !      corr_veg_soil(ji,jv,jst)=veget_max(ji,jv)/soiltile(ji,jst)
6039    !  soiltile(:,nstm) = fraction of vegtot covered by each soiltile (0-1, unitless)
6040    !  vegtot(:) = total fraction of grid-cell covered by PFTs (fraction with bare soil + vegetation)
6041    !  veget_max(:,nvm) = PFT fractions of vegtot+frac_nobio
6042    !  veget(:,nvm) =  fractions (of vegtot+frac_nobio) covered by vegetation in each PFT
6043    !       BUT veget(:,1)=veget_max(:,1)
6044    !  frac_bare(:,nvm) = fraction (of veget_max) with bare soil in each PFT
6045    !  tot_bare_soil(:) = fraction of grid mesh covered by all bare soil (=SUM(frac_bare*veget_max))
6046    !  frac_bare_ns(:,nstm) = evaporating bare soil fraction (of vegtot) per soiltile (defined in hydrol_vegupd)
6047   
6048    !! 1.1 Throughfall
6049    ! Transformation from precisol (flux from PFT jv in m2 of grid-mesh)
6050    ! to  precisol_ns (flux from contributing PFTs with another unit, in m2 of soiltile)
6051    precisol_ns(:,:)=zero
6052    DO jv=1,nvm
6053       DO ji=1,kjpindex
6054          jst=pref_soil_veg(jv)
6055          IF((veget_max(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT. min_sechiba)) THEN
6056             precisol_ns(ji,jst) = precisol_ns(ji,jst) + &
6057                     precisol(ji,jv) / (soiltile(ji,jst)*vegtot(ji))               
6058          ENDIF
6059       END DO
6060    END DO
6061   
6062    !! 1.2 Bare soil evaporation and ae_ns
6063    ae_ns(:,:)=zero
6064    DO jst=1,nstm
6065       DO ji=1,kjpindex
6066          IF(evap_bare_lim(ji).GT.min_sechiba) THEN       
6067             ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji)
6068          ENDIF
6069       ENDDO
6070    ENDDO
6071
6072    !! 1.3 transpiration
6073    ! Transformation from transpir (flux from PFT jv in m2 of grid-mesh)
6074    ! to tr_ns (flux from contributing PFTs with another unit, in m2 of soiltile)
6075    ! To do next: simplify the use of humrelv(ji,jv,jst) /humrel(ji,jv), since both are equal
6076    tr_ns(:,:)=zero
6077    DO jv=1,nvm
6078       jst=pref_soil_veg(jv)
6079       DO ji=1,kjpindex
6080          IF ((humrel(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT.min_sechiba))THEN
6081             tr_ns(ji,jst)= tr_ns(ji,jst) &
6082                  + transpir(ji,jv) * (humrelv(ji,jv,jst) / humrel(ji,jv)) &
6083                  / (soiltile(ji,jst)*vegtot(ji))
6084                     
6085             ENDIF
6086       END DO
6087    END DO
6088
6089    !! 1.4 root sink
6090    ! Transformation from transpir (flux from PFT jv in m2 of grid-mesh)
6091    ! to root_sink (flux from contributing PFTs and soil layer with another unit, in m2 of soiltile)
6092    rootsink(:,:,:)=zero
6093    DO jv=1,nvm
6094       jst=pref_soil_veg(jv)
6095       DO jsl=1,nslm
6096          DO ji=1,kjpindex
6097             IF ((humrel(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT.min_sechiba)) THEN
6098                rootsink(ji,jsl,jst) = rootsink(ji,jsl,jst) &
6099                        + transpir(ji,jv) * (us(ji,jv,jst,jsl) / humrel(ji,jv)) &
6100                        / (soiltile(ji,jst)*vegtot(ji))                     
6101                   ! rootsink(ji,1,jst)=0 as us(ji,jv,jst,1)=0
6102             END IF
6103          END DO
6104       END DO
6105    END DO
6106
6107
6108    !! 2. Verification: Check if the deconvolution is correct and conserves the fluxes (grid-cell average)
6109
6110    IF (check_cwrr) THEN
6111
6112       error=.FALSE.
6113
6114       !! 2.1 precisol
6115
6116       tmp_check1(:)=zero
6117       DO jst=1,nstm
6118          DO ji=1,kjpindex
6119             tmp_check1(ji)=tmp_check1(ji) + precisol_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6120          END DO
6121       END DO
6122       
6123       tmp_check2(:)=zero 
6124       DO jv=1,nvm
6125          DO ji=1,kjpindex
6126             tmp_check2(ji)=tmp_check2(ji) + precisol(ji,jv)
6127          END DO
6128       END DO
6129
6130       DO ji=1,kjpindex   
6131          IF(ABS(tmp_check1(ji) - tmp_check2(ji)).GT.allowed_err) THEN
6132             WRITE(numout,*) 'PRECISOL SPLIT FALSE:ji=',ji,tmp_check1(ji),tmp_check2(ji)
6133             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- tmp_check2(ji))
6134             WRITE(numout,*) 'vegtot',vegtot(ji)
6135             DO jv=1,nvm
6136                WRITE(numout,'(a,i2.2,"|",F13.4,"|",F13.4,"|",3(F9.6))') &
6137                     'jv,veget_max, precisol, vegetmax_soil ', &
6138                     jv,veget_max(ji,jv),precisol(ji,jv),vegetmax_soil(ji,jv,:)
6139             END DO
6140             DO jst=1,nstm
6141                WRITE(numout,*) 'jst,precisol_ns',jst,precisol_ns(ji,jst)
6142                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
6143             END DO
6144             error=.TRUE.
6145             CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6146                  & 'check_CWRR','PRECISOL SPLIT FALSE')
6147          ENDIF
6148       END DO
6149       
6150       !! 2.2 ae_ns and evapnu
6151
6152       tmp_check1(:)=zero
6153       DO jst=1,nstm
6154          DO ji=1,kjpindex
6155             tmp_check1(ji)=tmp_check1(ji) + ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6156          END DO
6157       END DO
6158
6159       DO ji=1,kjpindex   
6160
6161          IF(ABS(tmp_check1(ji) - vevapnu(ji)).GT.allowed_err) THEN
6162             WRITE(numout,*) 'VEVAPNU SPLIT FALSE:ji, Sum(ae_ns), vevapnu =',ji,tmp_check1(ji),vevapnu(ji)
6163             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- vevapnu(ji))
6164             WRITE(numout,*) 'ae_ns',ae_ns(ji,:)
6165             WRITE(numout,*) 'vegtot',vegtot(ji)
6166             WRITE(numout,*) 'evap_bare_lim, evap_bare_lim_ns',evap_bare_lim(ji), evap_bare_lim_ns(ji,:)
6167             DO jst=1,nstm
6168                WRITE(numout,*) 'jst,ae_ns',jst,ae_ns(ji,jst)
6169                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
6170             END DO
6171             error=.TRUE.
6172             CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6173                  & 'check_CWRR','VEVAPNU SPLIT FALSE')
6174          ENDIF
6175       ENDDO
6176
6177    !! 2.3 transpiration
6178
6179       tmp_check1(:)=zero
6180       DO jst=1,nstm
6181          DO ji=1,kjpindex
6182             tmp_check1(ji)=tmp_check1(ji) + tr_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
6183          END DO
6184       END DO
6185       
6186       tmp_check2(:)=zero 
6187       DO jv=1,nvm
6188          DO ji=1,kjpindex
6189             tmp_check2(ji)=tmp_check2(ji) + transpir(ji,jv)
6190          END DO
6191       END DO
6192
6193       DO ji=1,kjpindex   
6194          IF(ABS(tmp_check1(ji)- tmp_check2(ji)).GT.allowed_err) THEN
6195             WRITE(numout,*) 'TRANSPIR SPLIT FALSE:ji=',ji,tmp_check1(ji),tmp_check2(ji)
6196             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- tmp_check2(ji))
6197             WRITE(numout,*) 'vegtot',vegtot(ji)
6198             DO jv=1,nvm
6199                WRITE(numout,*) 'jv,veget_max, transpir',jv,veget_max(ji,jv),transpir(ji,jv)
6200                DO jst=1,nstm
6201                   WRITE(numout,*) 'vegetmax_soil:ji,jv,jst',ji,jv,jst,vegetmax_soil(ji,jv,jst)
6202                END DO
6203             END DO
6204             DO jst=1,nstm
6205                WRITE(numout,*) 'jst,tr_ns',jst,tr_ns(ji,jst)
6206                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
6207             END DO
6208             error=.TRUE.
6209             CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6210                  & 'check_CWRR','TRANSPIR SPLIT FALSE')
6211          ENDIF
6212
6213       END DO
6214
6215    !! 2.4 root sink
6216
6217       tmp_check3(:,:)=zero
6218       DO jst=1,nstm
6219          DO jsl=1,nslm
6220             DO ji=1,kjpindex
6221                tmp_check3(ji,jst)=tmp_check3(ji,jst) + rootsink(ji,jsl,jst)
6222             END DO
6223          END DO
6224       ENDDO
6225
6226       DO jst=1,nstm
6227          DO ji=1,kjpindex
6228             IF(ABS(tmp_check3(ji,jst) - tr_ns(ji,jst)).GT.allowed_err) THEN
6229                WRITE(numout,*) 'ROOTSINK SPLIT FALSE:ji,jst=', ji,jst,&
6230                     & tmp_check3(ji,jst),tr_ns(ji,jst)
6231                WRITE(numout,*) 'err',ABS(tmp_check3(ji,jst)- tr_ns(ji,jst))
6232                WRITE(numout,*) 'HUMREL(jv=1:13)',humrel(ji,:)
6233                WRITE(numout,*) 'TRANSPIR',transpir(ji,:)
6234                DO jv=1,nvm 
6235                   WRITE(numout,*) 'jv=',jv,'us=',us(ji,jv,jst,:)
6236                ENDDO
6237                error=.TRUE.
6238                CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
6239                  & 'check_CWRR','ROOTSINK SPLIT FALSE')
6240             ENDIF
6241          END DO
6242       END DO
6243
6244
6245       !! Exit if error was found previously in this subroutine
6246       IF ( error ) THEN
6247          WRITE(numout,*) 'One or more errors have been detected in hydrol_split_soil. Model stops.'
6248          CALL ipslerr_p(3, 'hydrol_split_soil', 'We will STOP now.',&
6249               & 'One or several fatal errors were found previously.','')
6250       END IF
6251
6252    ENDIF ! end of check_cwrr
6253
6254
6255  END SUBROUTINE hydrol_split_soil
6256 
6257
6258!! ================================================================================================================================
6259!! SUBROUTINE   : hydrol_diag_soil
6260!!
6261!>\BRIEF        Calculates diagnostic variables at the grid-cell scale
6262!!
6263!! DESCRIPTION  :
6264!! - 1. Apply mask_soiltile
6265!! - 2. Sum 3d variables in 2d variables with fraction of vegetation per soil type
6266!!
6267!! RECENT CHANGE(S) : 2016 by A. Ducharne for the claculation of shumdiag_perma
6268!!
6269!! MAIN OUTPUT VARIABLE(S) :
6270!!
6271!! REFERENCE(S) :
6272!!
6273!! FLOWCHART    : None
6274!! \n
6275!_ ================================================================================================================================
6276!_ hydrol_diag_soil
6277
6278  SUBROUTINE hydrol_diag_soil (ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, veget_max, soiltile, njsc, runoff, drainage, &
6279       & evapot, vevapnu, returnflow, reinfiltration, irrigation, &
6280       & shumdiag,shumdiag_perma, k_litt, litterhumdiag, humrel, vegstress, drysoil_frac, tot_melt)
6281    !
6282    ! interface description
6283
6284    !! 0. Variable and parameter declaration
6285
6286    !! 0.1 Input variables
6287
6288    ! input scalar
6289    INTEGER(i_std), INTENT(in)                               :: kjpindex 
6290    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: veget_max       !! Max. vegetation type
6291    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc            !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
6292    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile        !! Fraction of each soil tile within vegtot (0-1, unitless)
6293    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: ks               !! Hydraulic conductivity at saturation (mm {-1})
6294    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: nvan             !! Van Genuchten coeficients n (unitless)
6295    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: avan             !! Van Genuchten coeficients a (mm-1})
6296    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcr              !! Residual volumetric water content (m^{3} m^{-3})
6297    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcs              !! Saturated volumetric water content (m^{3} m^{-3})
6298    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcfc             !! Volumetric water content at field capacity (m^{3} m^{-3})
6299    REAL(r_std),DIMENSION (kjpindex), INTENT (in)            :: mcw              !! Volumetric water content at wilting point (m^{3} m^{-3})
6300    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot          !!
6301    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow      !! Water returning to the deep reservoir
6302    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: reinfiltration  !! Water returning to the top of the soil
6303    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: irrigation      !! Water from irrigation
6304    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_melt        !!
6305
6306    !! 0.2 Output variables
6307
6308    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: drysoil_frac    !! Function of litter wetness
6309    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: runoff          !! complete runoff
6310    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drainage        !! Drainage
6311    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)      :: shumdiag        !! relative soil moisture
6312    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)      :: shumdiag_perma  !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
6313    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: k_litt          !! litter cond.
6314    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: litterhumdiag   !! litter humidity
6315    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)       :: humrel          !! Relative humidity
6316    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(out)      :: vegstress       !! Veg. moisture stress (only for vegetation growth)
6317 
6318    !! 0.3 Modified variables
6319
6320    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapnu         !!
6321
6322    !! 0.4 Local variables
6323
6324    INTEGER(i_std)                                           :: ji, jv, jsl, jst, i
6325    REAL(r_std), DIMENSION (kjpindex)                        :: mask_vegtot
6326    REAL(r_std)                                              :: k_tmp, tmc_litter_ratio
6327
6328!_ ================================================================================================================================
6329    !
6330    ! Put the prognostics variables of soil to zero if soiltype is zero
6331
6332    !! 1. Apply mask_soiltile
6333   
6334    DO jst=1,nstm 
6335       DO ji=1,kjpindex
6336
6337             ae_ns(ji,jst) = ae_ns(ji,jst) * mask_soiltile(ji,jst)
6338             dr_ns(ji,jst) = dr_ns(ji,jst) * mask_soiltile(ji,jst)
6339             ru_ns(ji,jst) = ru_ns(ji,jst) * mask_soiltile(ji,jst)
6340             tmc(ji,jst) =  tmc(ji,jst) * mask_soiltile(ji,jst)
6341
6342             DO jv=1,nvm
6343                humrelv(ji,jv,jst) = humrelv(ji,jv,jst) * mask_soiltile(ji,jst)
6344                DO jsl=1,nslm
6345                   us(ji,jv,jst,jsl) = us(ji,jv,jst,jsl)  * mask_soiltile(ji,jst)
6346                END DO
6347             END DO
6348
6349             DO jsl=1,nslm         
6350                mc(ji,jsl,jst) = mc(ji,jsl,jst)  * mask_soiltile(ji,jst)
6351             END DO
6352
6353       END DO
6354    END DO
6355
6356    runoff(:) = zero
6357    drainage(:) = zero
6358    humtot(:) = zero
6359    shumdiag(:,:)= zero
6360    shumdiag_perma(:,:)=zero
6361    k_litt(:) = zero
6362    litterhumdiag(:) = zero
6363    tmc_litt_dry_mea(:) = zero
6364    tmc_litt_wet_mea(:) = zero
6365    tmc_litt_mea(:) = zero
6366    humrel(:,:) = zero
6367    vegstress(:,:) = zero
6368    IF (ok_freeze_cwrr) THEN
6369       profil_froz_hydro(:,:)=zero ! initialisation for the mean of profil_froz_hydro_ns
6370    ENDIF
6371   
6372    !! 2. Sum 3d variables in 2d variables with fraction of vegetation per soil type
6373
6374    DO ji = 1, kjpindex
6375       mask_vegtot(ji) = 0
6376       IF(vegtot(ji) .GT. min_sechiba) THEN
6377          mask_vegtot(ji) = 1
6378       ENDIF
6379    END DO
6380   
6381    DO ji = 1, kjpindex 
6382       ! Here we weight ae_ns by the fraction of bare evaporating soil.
6383       ! This is given by frac_bare_ns, taking into account bare soil under vegetation
6384       ae_ns(ji,:) = mask_vegtot(ji) * ae_ns(ji,:) * frac_bare_ns(ji,:)
6385    END DO
6386
6387    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6388    DO jst = 1, nstm
6389       DO ji = 1, kjpindex 
6390          drainage(ji) = mask_vegtot(ji) * (drainage(ji) + vegtot(ji)*soiltile(ji,jst) * dr_ns(ji,jst))
6391          runoff(ji) = mask_vegtot(ji) *  (runoff(ji) +   vegtot(ji)*soiltile(ji,jst) * ru_ns(ji,jst)) &
6392               &   + (1 - mask_vegtot(ji)) * (tot_melt(ji) + irrigation(ji) + returnflow(ji) + reinfiltration(ji))
6393          humtot(ji) = mask_vegtot(ji) * (humtot(ji) + vegtot(ji)*soiltile(ji,jst) * tmc(ji,jst)) 
6394          IF (ok_freeze_cwrr) THEN 
6395             !  profil_froz_hydro_ns comes from hydrol_soil, to remain the same as in the prognotic loop
6396             profil_froz_hydro(ji,:)=mask_vegtot(ji) * &
6397                  (profil_froz_hydro(ji,:) + vegtot(ji)*soiltile(ji,jst) * profil_froz_hydro_ns(ji,:, jst))
6398          ENDIF
6399       END DO
6400    END DO
6401
6402    ! we add the excess of snow sublimation to vevapnu
6403    ! - because vevapsno is modified in hydrol_snow if subsinksoil
6404    ! - it is multiplied by vegtot because it is devided by 1-tot_frac_nobio at creation in hydrol_snow
6405
6406    DO ji = 1,kjpindex
6407       vevapnu(ji) = vevapnu (ji) + subsinksoil(ji)*vegtot(ji)
6408    END DO
6409
6410    DO jst=1,nstm
6411       DO jv=1,nvm
6412          DO ji=1,kjpindex
6413             IF(veget_max(ji,jv).GT.min_sechiba) THEN
6414                vegstress(ji,jv)=vegstress(ji,jv)+vegstressv(ji,jv,jst)
6415                vegstress(ji,jv)= MAX(vegstress(ji,jv),zero)
6416             ENDIF
6417          END DO
6418       END DO
6419    END DO
6420
6421    DO jst=1,nstm
6422       DO jv=1,nvm
6423          DO ji=1,kjpindex
6424             humrel(ji,jv)=humrel(ji,jv)+humrelv(ji,jv,jst)
6425             humrel(ji,jv)=MAX(humrel(ji,jv),zero)
6426          END DO
6427       END DO
6428    END DO
6429
6430    !! Litter... the goal is to calculate drysoil_frac, to calculate the albedo in condveg
6431    ! In condveg, drysoil_frac serve to calculate the albedo of drysoil, excluding the nobio contribution which is further added
6432    ! In conclusion, we calculate drysoil_frac based on moisture averages restricted to the soiltile (no multiplication by vegtot)
6433    ! BUT THIS IS NOT USED ANYMORE WITH THE NEW BACKGROUNG ALBEDO
6434    !! k_litt is calculated here as a grid-cell average (for consistency with drainage)   
6435    !! litterhumdiag, like shumdiag, is averaged over the soiltiles for transmission to stomate
6436    DO jst=1,nstm       
6437       DO ji=1,kjpindex
6438          ! We compute here a mean k for the 'litter' used for reinfiltration from floodplains of ponds       
6439          IF ( tmc_litter(ji,jst) < tmc_litter_res(ji,jst)) THEN
6440             i = imin
6441          ELSE
6442             tmc_litter_ratio = (tmc_litter(ji,jst)-tmc_litter_res(ji,jst)) / &
6443                  & (tmc_litter_sat(ji,jst)-tmc_litter_res(ji,jst))
6444             i= MAX(MIN(INT((imax-imin)*tmc_litter_ratio)+imin, imax-1), imin)
6445          ENDIF       
6446          k_tmp = MAX(k_lin(i,1,ji)*ks(ji), zero)
6447          k_litt(ji) = k_litt(ji) + vegtot(ji)*soiltile(ji,jst) * SQRT(k_tmp) ! grid-cell average
6448       ENDDO     
6449       DO ji=1,kjpindex
6450          litterhumdiag(ji) = litterhumdiag(ji) + &
6451               & soil_wet_litter(ji,jst) * soiltile(ji,jst)
6452
6453          tmc_litt_wet_mea(ji) =  tmc_litt_wet_mea(ji) + & 
6454               & tmc_litter_awet(ji,jst)* soiltile(ji,jst)
6455
6456          tmc_litt_dry_mea(ji) = tmc_litt_dry_mea(ji) + &
6457               & tmc_litter_adry(ji,jst) * soiltile(ji,jst) 
6458
6459          tmc_litt_mea(ji) = tmc_litt_mea(ji) + &
6460               & tmc_litter(ji,jst) * soiltile(ji,jst) 
6461       ENDDO
6462    ENDDO
6463   
6464    DO ji=1,kjpindex
6465       IF ( tmc_litt_wet_mea(ji) - tmc_litt_dry_mea(ji) > zero ) THEN
6466          drysoil_frac(ji) = un + MAX( MIN( (tmc_litt_dry_mea(ji) - tmc_litt_mea(ji)) / &
6467               & (tmc_litt_wet_mea(ji) - tmc_litt_dry_mea(ji)), zero), - un)
6468       ELSE
6469          drysoil_frac(ji) = zero
6470       ENDIF
6471    END DO
6472   
6473    ! Calculate soilmoist, as a function of total water content (mc)
6474    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6475    soilmoist(:,:) = zero
6476    DO jst=1,nstm
6477       DO ji=1,kjpindex
6478             soilmoist(ji,1) = soilmoist(ji,1) + soiltile(ji,jst) * &
6479                  dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
6480             DO jsl = 2,nslm-1
6481                soilmoist(ji,jsl) = soilmoist(ji,jsl) + soiltile(ji,jst) * &
6482                     ( dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
6483                     + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit )
6484             END DO
6485             soilmoist(ji,nslm) = soilmoist(ji,nslm) + soiltile(ji,jst) * &
6486                  dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
6487       END DO
6488    END DO
6489    DO ji=1,kjpindex
6490       soilmoist(ji,:) = soilmoist(ji,:) * vegtot(ji) ! conversion to grid-cell average
6491    ENDDO
6492
6493    soilmoist_liquid(:,:) = zero
6494    DO jst=1,nstm
6495       DO ji=1,kjpindex
6496          soilmoist_liquid(ji,1) = soilmoist_liquid(ji,1) + soiltile(ji,jst) * &
6497               dz(2) * ( trois*mcl(ji,1,jst) + mcl(ji,2,jst) )/huit
6498          DO jsl = 2,nslm-1
6499             soilmoist_liquid(ji,jsl) = soilmoist_liquid(ji,jsl) + soiltile(ji,jst) * &
6500                  ( dz(jsl) * (trois*mcl(ji,jsl,jst)+mcl(ji,jsl-1,jst))/huit &
6501                  + dz(jsl+1) * (trois*mcl(ji,jsl,jst)+mcl(ji,jsl+1,jst))/huit )
6502          END DO
6503          soilmoist_liquid(ji,nslm) = soilmoist_liquid(ji,nslm) + soiltile(ji,jst) * &
6504               dz(nslm) * (trois*mcl(ji,nslm,jst) + mcl(ji,nslm-1,jst))/huit
6505       ENDDO
6506    ENDDO
6507    DO ji=1,kjpindex
6508        soilmoist_liquid(ji,:) = soilmoist_liquid(ji,:) * vegtot_old(ji) ! grid cell average
6509    ENDDO
6510   
6511   
6512    ! Shumdiag: we start from soil_wet_ns, change the range over which the relative moisture is calculated,
6513    ! then do a spatial average, excluding the nobio fraction on which stomate doesn't act
6514    DO jst=1,nstm     
6515       DO jsl=1,nslm
6516          DO ji=1,kjpindex
6517             shumdiag(ji,jsl) = shumdiag(ji,jsl) + soil_wet_ns(ji,jsl,jst) * soiltile(ji,jst) * &
6518                               ((mcs(ji)-mcw(ji))/(mcfc(ji)-mcw(ji)))
6519             shumdiag(ji,jsl) = MAX(MIN(shumdiag(ji,jsl), un), zero) 
6520          ENDDO
6521       ENDDO
6522    ENDDO
6523   
6524    ! Shumdiag_perma is based on soilmoist / moisture at saturation in the layer
6525    ! Her we start from grid averages by hydrol soil layer and transform it to the diag levels
6526    ! We keep a grid-cell average, like for all variables transmitted to ok_freeze
6527    DO jsl=1,nslm             
6528       DO ji=1,kjpindex
6529          shumdiag_perma(ji,jsl) = soilmoist(ji,jsl) / (dh(jsl)*mcs(ji))
6530          shumdiag_perma(ji,jsl) = MAX(MIN(shumdiag_perma(ji,jsl), un), zero) 
6531       ENDDO
6532    ENDDO
6533   
6534  END SUBROUTINE hydrol_diag_soil 
6535
6536
6537!! ================================================================================================================================
6538!! SUBROUTINE   : hydrol_alma
6539!!
6540!>\BRIEF        This routine computes the changes in soil moisture and interception storage for the ALMA outputs. 
6541!!
6542!! DESCRIPTION  : None
6543!!
6544!! RECENT CHANGE(S) : None
6545!!
6546!! MAIN OUTPUT VARIABLE(S) :
6547!!
6548!! REFERENCE(S) :
6549!!
6550!! FLOWCHART    : None
6551!! \n
6552!_ ================================================================================================================================
6553!_ hydrol_alma
6554
6555  SUBROUTINE hydrol_alma (kjpindex, index, lstep_init, qsintveg, snow, snow_nobio, soilwet)
6556    !
6557    !! 0. Variable and parameter declaration
6558
6559    !! 0.1 Input variables
6560
6561    INTEGER(i_std), INTENT (in)                        :: kjpindex     !! Domain size
6562    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index        !! Indeces of the points on the map
6563    LOGICAL, INTENT (in)                               :: lstep_init   !! At which time is this routine called ?
6564    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintveg     !! Water on vegetation due to interception
6565    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: snow         !! Snow water equivalent
6566    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio !! Water balance on ice, lakes, .. [Kg/m^2]
6567
6568    !! 0.2 Output variables
6569
6570    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: soilwet     !! Soil wetness
6571
6572    !! 0.3 Modified variables
6573
6574    !! 0.4 Local variables
6575
6576    INTEGER(i_std) :: ji
6577    REAL(r_std) :: watveg
6578
6579!_ ================================================================================================================================
6580    !
6581    !
6582    IF ( lstep_init ) THEN
6583       ! Initialize variables if they were not found in the restart file
6584
6585       DO ji = 1, kjpindex
6586          watveg = SUM(qsintveg(ji,:))
6587          tot_watveg_beg(ji) = watveg
6588          tot_watsoil_beg(ji) = humtot(ji)
6589          snow_beg(ji)        = snow(ji) + SUM(snow_nobio(ji,:))
6590       ENDDO
6591
6592       RETURN
6593
6594    ENDIF
6595    !
6596    ! Calculate the values for the end of the time step
6597    !
6598    DO ji = 1, kjpindex
6599       watveg = SUM(qsintveg(ji,:)) ! average within the mesh
6600       tot_watveg_end(ji) = watveg
6601       tot_watsoil_end(ji) = humtot(ji) ! average within the mesh
6602       snow_end(ji) = snow(ji)+ SUM(snow_nobio(ji,:)) ! average within the mesh
6603
6604       delintercept(ji) = tot_watveg_end(ji) - tot_watveg_beg(ji) ! average within the mesh
6605       delsoilmoist(ji) = tot_watsoil_end(ji) - tot_watsoil_beg(ji)
6606       delswe(ji)       = snow_end(ji) - snow_beg(ji) ! average within the mesh
6607    ENDDO
6608    !
6609    !
6610    ! Transfer the total water amount at the end of the current timestep top the begining of the next one.
6611    !
6612    tot_watveg_beg = tot_watveg_end
6613    tot_watsoil_beg = tot_watsoil_end
6614    snow_beg(:) = snow_end(:)
6615    !
6616    DO ji = 1,kjpindex
6617       IF ( mx_eau_var(ji) > 0 ) THEN
6618          soilwet(ji) = tot_watsoil_end(ji) / mx_eau_var(ji)
6619       ELSE
6620          soilwet(ji) = zero
6621       ENDIF
6622    ENDDO
6623    !
6624  END SUBROUTINE hydrol_alma
6625  !
6626
6627!! ================================================================================================================================
6628!! SUBROUTINE   : hydrol_nudge_mc_read
6629!!
6630!>\BRIEF         Read soil moisture from file and interpolate to the current time step
6631!!
6632!! 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.
6633!!                This subroutine reads and interpolates spatialy if necessary and temporary the soil moisture from file.
6634!!                The values for the soil moisture will be applaied later using hydrol_nudge_mc
6635!!
6636!! RECENT CHANGE(S) : None
6637!!
6638!! \n
6639!_ ================================================================================================================================
6640
6641  SUBROUTINE hydrol_nudge_mc_read(kjit)
6642
6643    !! 0.1 Input variables
6644    INTEGER(i_std), INTENT(in)                         :: kjit        !! Timestep number
6645
6646    !! 0.3 Locals variables
6647    REAL(r_std)                                :: tau                   !! Position between to values in nudge mc file
6648    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
6649    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
6650    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
6651    REAL(r_std), DIMENSION(nbp_glo,nslm,nstm)  :: mc_read_glo1D         !! mc_read_glo2D on land-only vector form, in global
6652    INTEGER(i_std), SAVE                       :: istart_mc !! start index to read from input file
6653!$OMP THREADPRIVATE(istart_mc)
6654    INTEGER(i_std)                             :: iend                  !! end index to read from input file
6655    INTEGER(i_std)                             :: i, j, ji, jg, jst, jsl!! loop index
6656    INTEGER(i_std)                             :: iim_file, jjm_file, llm_file !! Dimensions in input file
6657    INTEGER(i_std), SAVE                       :: ttm_mc      !! Time dimensions in input file
6658!$OMP THREADPRIVATE(ttm_mc)
6659    INTEGER(i_std), SAVE                       :: mc_id        !! index for netcdf files
6660!$OMP THREADPRIVATE(mc_id)
6661    LOGICAL, SAVE                              :: firsttime_mc=.TRUE.
6662!$OMP THREADPRIVATE(firsttime_mc)
6663
6664 
6665    !! 1. Nudging of soil moisture
6666
6667       !! 1.2 Read mc from file, once a day only
6668       !!     The forcing file must contain daily frequency variable for the full year of the simulation
6669       IF (MOD(kjit,INT(one_day/dt_sechiba)) == 1) THEN 
6670          ! Save mc read from file from previous day
6671          mc_read_prev = mc_read_next
6672
6673          IF (nudge_interpol_with_xios) THEN
6674             ! Read mc from input file. XIOS interpolates it to the model grid before it is received here.
6675             CALL xios_orchidee_recv_field("moistc_interp", mc_read_next)
6676
6677             ! Read and interpolation the mask for variable mc from input file.
6678             ! This is only done to be able to output the mask it later for validation purpose.
6679             ! The mask corresponds to the fraction of the input source file which was underlaying the model grid cell.
6680             ! 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.
6681             CALL xios_orchidee_recv_field("mask_moistc_interp", mask_mc_interp)
6682
6683          ELSE
6684
6685             ! Only read fields from the file. We here suppose that no interpolation is needed.
6686             IF (is_root_prc) THEN
6687                IF (firsttime_mc) THEN
6688                   ! Open and read dimenions in file
6689                   CALL flininfo('nudge_moistc.nc',  iim_file, jjm_file, llm_file, ttm_mc, mc_id)
6690                   
6691                   ! Coherence test between dimension in the file and in the model run
6692                   IF ((iim_file /= iim_g) .OR. (jjm_file /= jjm_g)) THEN
6693                      WRITE(numout,*) 'hydrol_nudge: iim_file, jjm_file, llm_file, ttm_mc=', &
6694                           iim_file, jjm_file, llm_file, ttm_mc
6695                      WRITE(numout,*) 'hydrol_nudge: iim_g, jjm_g=', iim_g, jjm_g
6696                      CALL ipslerr_p(2,'hydrol_nudge','Problem in coherence between dimensions in nudge_moistc.nc file and model',&
6697                           'iim_file should be equal to iim_g','jjm_file should be equal to jjm_g')
6698                   END IF
6699                   
6700                   firsttime_mc=.FALSE.
6701                   istart_mc=julian_diff-1 ! initialize time counter to read
6702                   IF (printlev>=2) WRITE(numout,*) "Start read nudge_moistc.nc file at time step: ", istart_mc+1
6703                END IF
6704
6705                istart_mc=istart_mc+1  ! read next time step in the file
6706                iend=istart_mc         ! only read 1 time step
6707               
6708                ! Read mc from file, one variable per soiltile
6709                IF (printlev>=3) WRITE(numout,*) &
6710                     "Read variables moistc_1, moistc_2 and moistc_3 from nudge_moistc.nc at time step: ", istart_mc
6711                CALL flinget (mc_id, 'moistc_1', iim_g, jjm_g, nslm, ttm_mc, istart_mc, iend, mc_read_glo2D_1)
6712                CALL flinget (mc_id, 'moistc_2', iim_g, jjm_g, nslm, ttm_mc, istart_mc, iend, mc_read_glo2D_2)
6713                CALL flinget (mc_id, 'moistc_3', iim_g, jjm_g, nslm, ttm_mc, istart_mc, iend, mc_read_glo2D_3)
6714
6715                ! Transform from global 2D(iim_g, jjm_g) into into land-only global 1D(nbp_glo)
6716                ! Put the variables on the 3 soiltiles in the same file
6717                DO ji = 1, nbp_glo
6718                   j = ((index_g(ji)-1)/iim_g) + 1
6719                   i = (index_g(ji) - (j-1)*iim_g)
6720                   mc_read_glo1D(ji,:,1) = mc_read_glo2D_1(i,j,:,1)
6721                   mc_read_glo1D(ji,:,2) = mc_read_glo2D_2(i,j,:,1)
6722                   mc_read_glo1D(ji,:,3) = mc_read_glo2D_3(i,j,:,1)
6723                END DO
6724             END IF
6725
6726             ! Distribute the fields on all processors
6727             CALL scatter(mc_read_glo1D, mc_read_next)
6728
6729             ! No interpolation is done, set the mask to 1
6730             mask_mc_interp(:,:,:) = 1
6731
6732          END IF ! nudge_interpol_with_xios
6733       END IF ! MOD(kjit,INT(one_day/dt_sechiba)) == 1
6734       
6735     
6736       !! 1.3 Linear time interpolation between daily fields to the current time step
6737       tau   = (kjit-1)*dt_sechiba/one_day - AINT((kjit-1)*dt_sechiba/one_day)
6738       mc_read_current(:,:,:) = (1.-tau)*mc_read_prev(:,:,:) + tau*mc_read_next(:,:,:)
6739
6740       !! 1.4 Output daily fields and time interpolated fields only for debugging and validation purpose
6741       CALL xios_orchidee_send_field("mc_read_next", mc_read_next)
6742       CALL xios_orchidee_send_field("mc_read_current", mc_read_current)
6743       CALL xios_orchidee_send_field("mc_read_prev", mc_read_prev)
6744       CALL xios_orchidee_send_field("mask_mc_interp_out", mask_mc_interp)
6745
6746
6747  END SUBROUTINE hydrol_nudge_mc_read
6748
6749!! ================================================================================================================================
6750!! SUBROUTINE   : hydrol_nudge_mc
6751!!
6752!>\BRIEF         Applay nuding for soil moisture
6753!!
6754!! DESCRIPTION  : Applay nudging for soil moisture. The nuding values were previously read and interpolated using
6755!!                the subroutine hydrol_nudge_mc_read
6756!!                This subroutine is called from a loop over all soil tiles.
6757!!
6758!! RECENT CHANGE(S) : None
6759!!
6760!! \n
6761!_ ================================================================================================================================
6762  SUBROUTINE hydrol_nudge_mc(kjpindex, jst, mc_loc)
6763
6764    !! 0.1 Input variables
6765    INTEGER(i_std), INTENT(in)                         :: kjpindex    !! Domain size
6766    INTEGER(i_std), INTENT(in)                         :: jst         !! Index for current soil tile
6767       
6768    !! 0.2 Modified variables
6769    REAL(r_std), DIMENSION(kjpindex,nslm,nstm), INTENT(inout) :: mc_loc      !! Soil moisture
6770   
6771    !! 0.2 Locals variables
6772    REAL(r_std), DIMENSION(kjpindex,nslm,nstm) :: mc_aux                !! Temorary variable for calculation of nudgincsm
6773    INTEGER(i_std)                             :: ji, jsl               !! loop index   
6774   
6775   
6776    !! 1.5 Applay nudging of soil moisture using alpha_nudge_mc at each model sechiba time step.
6777    !!     alpha_mc_nudge calculated using the parameter for relaxation time NUDGE_TAU_MC set in module constantes.
6778    !!     alpha_nudge_mc is between 0-1
6779    !!     If alpha_nudge_mc=1, the new mc will be replaced by the one read from file
6780    mc_loc(:,:,jst) = (1-alpha_nudge_mc)*mc_loc(:,:,jst) + alpha_nudge_mc * mc_read_current(:,:,jst)
6781   
6782   
6783    !! 1.6 Calculate diagnostic for nudging increment of water in soil moisture
6784    !!     Here calculate tmc_aux for the current soil tile. Later in hydrol_nudge_mc_diag, this will be used to calculate nudgincsm
6785    mc_aux(:,:,jst)  = alpha_nudge_mc * ( mc_read_current(:,:,jst) - mc_loc(:,:,jst))
6786    DO ji=1,kjpindex
6787       tmc_aux(ji,jst) = dz(2) * ( trois*mc_aux(ji,1,jst) + mc_aux(ji,2,jst) )/huit
6788       DO jsl = 2,nslm-1
6789          tmc_aux(ji,jst) = tmc_aux(ji,jst) + dz(jsl) *  (trois*mc_aux(ji,jsl,jst)+mc_aux(ji,jsl-1,jst))/huit &
6790               + dz(jsl+1) * (trois*mc_aux(ji,jsl,jst)+mc_aux(ji,jsl+1,jst))/huit
6791       ENDDO
6792       tmc_aux(ji,jst) = tmc_aux(ji,jst) + dz(nslm) * (trois*mc_aux(ji,nslm,jst) + mc_aux(ji,nslm-1,jst))/huit
6793    ENDDO
6794       
6795
6796  END SUBROUTINE hydrol_nudge_mc
6797
6798
6799  SUBROUTINE hydrol_nudge_mc_diag(kjpindex, soiltile)
6800    !! 0.1 Input variables   
6801    INTEGER(i_std), INTENT(in)                         :: kjpindex    !! Domain size
6802    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT (in) :: soiltile    !! Fraction of each soil tile within vegtot (0-1, unitless)
6803
6804    !! 0.2 Locals variables
6805    REAL(r_std), DIMENSION(kjpindex)           :: nudgincsm             !! Nudging increment of water in soil moisture
6806    INTEGER(i_std)                             :: ji, jst               !! loop index
6807
6808
6809    ! Average over grid-cell
6810    nudgincsm(:) = zero
6811    DO jst=1,nstm
6812       DO ji=1,kjpindex
6813          nudgincsm(ji) = nudgincsm(ji) + vegtot(ji) * soiltile(ji,jst) * tmc_aux(ji,jst)
6814       ENDDO
6815    ENDDO
6816   
6817    CALL xios_orchidee_send_field("nudgincsm", nudgincsm)
6818
6819  END SUBROUTINE hydrol_nudge_mc_diag
6820
6821
6822  !! ================================================================================================================================
6823  !! SUBROUTINE   : hydrol_nudge_snow
6824  !!
6825  !>\BRIEF         Read, interpolate and applay nudging snow variables
6826  !!
6827  !! DESCRIPTION  : Nudging of snow variables is done if OK_NUDGE_SNOW=y is set in run.def
6828  !!
6829  !! RECENT CHANGE(S) : None
6830  !!
6831  !! MAIN IN-OUTPUT VARIABLE(S) : snowdz, snowrho, snowtemp
6832  !!
6833  !! REFERENCE(S) :
6834  !!
6835  !! \n
6836  !_ ================================================================================================================================
6837
6838
6839  SUBROUTINE hydrol_nudge_snow(kjit,   kjpindex, snowdz, snowrho, snowtemp )
6840
6841    !! 0.1 Input variables
6842    INTEGER(i_std), INTENT(in)                         :: kjit        !! Timestep number
6843    INTEGER(i_std), INTENT(in)                         :: kjpindex    !! Domain size
6844
6845    !! 0.2 Modified variables
6846    REAL(r_std), DIMENSION(kjpindex,nsnow), INTENT(inout)     :: snowdz      !! Snow layer thickness
6847    REAL(r_std), DIMENSION(kjpindex,nsnow), INTENT(inout)     :: snowrho     !! Snow density
6848    REAL(r_std), DIMENSION(kjpindex,nsnow), INTENT(inout)     :: snowtemp    !! Snow temperature
6849
6850
6851
6852    !! 0.3 Locals variables
6853    REAL(r_std)                                :: tau                   !! Position between to values in nudge mc file
6854    REAL(r_std), DIMENSION(kjpindex,nsnow)     :: snowdz_read_current   !! snowdz from file interpolated to current timestep
6855    REAL(r_std), DIMENSION(kjpindex,nsnow)     :: snowrho_read_current  !! snowrho from file interpolated to current timestep
6856    REAL(r_std), DIMENSION(kjpindex,nsnow)     :: snowtemp_read_current !! snowtemp from file interpolated to current timestep
6857    REAL(r_std), DIMENSION(kjpindex)           :: nudgincswe            !! Nudging increment of water in snow
6858    REAL(r_std), DIMENSION(iim_g,jjm_g,nsnow,1):: snowdz_read_glo2D     !! snowdz from file at global 2D(lat,lon) grid
6859    REAL(r_std), DIMENSION(iim_g,jjm_g,nsnow,1):: snowrho_read_glo2D    !! snowrho from file at global 2D(lat,lon) grid
6860    REAL(r_std), DIMENSION(iim_g,jjm_g,nsnow,1):: snowtemp_read_glo2D   !! snowrho from file at global 2D(lat,lon) grid
6861    REAL(r_std), DIMENSION(nbp_glo,nsnow)      :: snowdz_read_glo1D     !! snowdz_read_glo2D on land-only vector form, in global
6862    REAL(r_std), DIMENSION(nbp_glo,nsnow)      :: snowrho_read_glo1D    !! snowdz_read_glo2D on land-only vector form, in global
6863    REAL(r_std), DIMENSION(nbp_glo,nsnow)      :: snowtemp_read_glo1D   !! snowdz_read_glo2D on land-only vector form, in global
6864    INTEGER(i_std), SAVE                       ::  istart_snow!! start index to read from input file
6865!$OMP THREADPRIVATE(istart_snow)
6866    INTEGER(i_std)                             :: iend                  !! end index to read from input file
6867    INTEGER(i_std)                             :: i, j, ji, jg, jst, jsl!! loop index
6868    INTEGER(i_std)                             :: iim_file, jjm_file, llm_file !! Dimensions in input file
6869    INTEGER(i_std), SAVE                       :: ttm_snow      !! Time dimensions in input file
6870!$OMP THREADPRIVATE(ttm_snow)
6871    INTEGER(i_std), SAVE                       :: snow_id        !! index for netcdf files
6872!$OMP THREADPRIVATE(snow_id)
6873    LOGICAL, SAVE                              :: firsttime_snow=.TRUE.
6874!$OMP THREADPRIVATE(firsttime_snow)
6875
6876 
6877    !! 2. Nudging of snow variables
6878    IF (ok_nudge_snow) THEN
6879
6880       !! 2.1 Read snow variables from file, once a day only
6881       !!     The forcing file must contain daily frequency values for the full year of the simulation
6882       IF (MOD(kjit,INT(one_day/dt_sechiba)) == 1) THEN 
6883          ! Save variables from previous day
6884          snowdz_read_prev   = snowdz_read_next
6885          snowrho_read_prev  = snowrho_read_next
6886          snowtemp_read_prev = snowtemp_read_next
6887         
6888          IF (nudge_interpol_with_xios) THEN
6889             ! Read and interpolation snow variables and the mask from input file
6890             CALL xios_orchidee_recv_field("snowdz_interp", snowdz_read_next)
6891             CALL xios_orchidee_recv_field("snowrho_interp", snowrho_read_next)
6892             CALL xios_orchidee_recv_field("snowtemp_interp", snowtemp_read_next)
6893             CALL xios_orchidee_recv_field("mask_snow_interp", mask_snow_interp)
6894
6895          ELSE
6896             ! Only read fields from the file. We here suppose that no interpolation is needed.
6897             IF (is_root_prc) THEN
6898                IF (firsttime_snow) THEN
6899                   ! Open and read dimenions in file
6900                   CALL flininfo('nudge_snow.nc',  iim_file, jjm_file, llm_file, ttm_snow, snow_id)
6901                   
6902                   ! Coherence test between dimension in the file and in the model run
6903                   IF ((iim_file /= iim_g) .OR. (jjm_file /= jjm_g)) THEN
6904                      WRITE(numout,*) 'hydrol_nudge: iim_file, jjm_file, llm_file, ttm_snow=', &
6905                           iim_file, jjm_file, llm_file, ttm_snow
6906                      WRITE(numout,*) 'hydrol_nudge: iim_g, jjm_g=', iim_g, jjm_g
6907                      CALL ipslerr_p(3,'hydrol_nudge','Problem in coherence between dimensions in nudge_snow.nc file and model',&
6908                           'iim_file should be equal to iim_g','jjm_file should be equal to jjm_g')
6909                   END IF
6910                                         
6911                   firsttime_snow=.FALSE.
6912                   istart_snow=julian_diff-1  ! initialize time counter to read
6913                   IF (printlev>=2) WRITE(numout,*) "Start read nudge_snow.nc file at time step: ", istart_snow+1
6914                END IF
6915
6916                istart_snow=istart_snow+1  ! read next time step in the file
6917                iend=istart_snow      ! only read 1 time step
6918               
6919                ! Read snowdz, snowrho and snowtemp from file
6920                IF (printlev>=2) WRITE(numout,*) &
6921                  "Read variables snowdz, snowrho and snowtemp from nudge_snow.nc at time step: ", istart_snow,ttm_snow
6922                CALL flinget (snow_id, 'snowdz', iim_g, jjm_g, nsnow, ttm_snow, istart_snow, iend, snowdz_read_glo2D)
6923                CALL flinget (snow_id, 'snowrho', iim_g, jjm_g, nsnow, ttm_snow, istart_snow, iend, snowrho_read_glo2D)
6924                CALL flinget (snow_id, 'snowtemp', iim_g, jjm_g, nsnow, ttm_snow, istart_snow, iend, snowtemp_read_glo2D)
6925
6926
6927                ! Transform from global 2D(iim_g, jjm_g) variables into into land-only global 1D variables (nbp_glo)
6928                DO ji = 1, nbp_glo
6929                   j = ((index_g(ji)-1)/iim_g) + 1
6930                   i = (index_g(ji) - (j-1)*iim_g)
6931                   snowdz_read_glo1D(ji,:) = snowdz_read_glo2D(i,j,:,1)
6932                   snowrho_read_glo1D(ji,:) = snowrho_read_glo2D(i,j,:,1)
6933                   snowtemp_read_glo1D(ji,:) = snowtemp_read_glo2D(i,j,:,1)
6934                END DO
6935             END IF
6936
6937             ! Distribute the fields on all processors
6938             CALL scatter(snowdz_read_glo1D, snowdz_read_next)
6939             CALL scatter(snowrho_read_glo1D, snowrho_read_next)
6940             CALL scatter(snowtemp_read_glo1D, snowtemp_read_next)
6941
6942             ! No interpolation is done, set the mask to 1
6943             mask_snow_interp=1
6944
6945          END IF ! nudge_interpol_with_xios
6946
6947         
6948          ! Test if the values for depth of snow is in a valid range when read from the file,
6949          ! else set as no snow cover
6950          DO ji=1,kjpindex
6951             IF ((SUM(snowdz_read_next(ji,:)) .LE. 0.0) .OR. (SUM(snowdz_read_next(ji,:)) .GT. 100)) THEN
6952                ! Snowdz has no valide values in the file, set here as no snow
6953                snowdz_read_next(ji,:)   = 0
6954                snowrho_read_next(ji,:)  = 50.0
6955                snowtemp_read_next(ji,:) = tp_00
6956             END IF
6957          END DO
6958
6959       END IF ! MOD(kjit,INT(one_day/dt_sechiba)) == 1
6960       
6961     
6962       !! 2.2 Linear time interpolation between daily fields for current time step
6963       tau   = (kjit-1)*dt_sechiba/one_day - AINT((kjit-1)*dt_sechiba/one_day)
6964       snowdz_read_current(:,:) = (1.-tau)*snowdz_read_prev(:,:) + tau*snowdz_read_next(:,:)
6965       snowrho_read_current(:,:) = (1.-tau)*snowrho_read_prev(:,:) + tau*snowrho_read_next(:,:)
6966       snowtemp_read_current(:,:) = (1.-tau)*snowtemp_read_prev(:,:) + tau*snowtemp_read_next(:,:)
6967
6968       !! 2.3 Output daily fields and time interpolated fields only for debugging and validation purpose
6969       CALL xios_orchidee_send_field("snowdz_read_next", snowdz_read_next)
6970       CALL xios_orchidee_send_field("snowdz_read_current", snowdz_read_current)
6971       CALL xios_orchidee_send_field("snowdz_read_prev", snowdz_read_prev)
6972       CALL xios_orchidee_send_field("snowrho_read_next", snowrho_read_next)
6973       CALL xios_orchidee_send_field("snowrho_read_current", snowrho_read_current)
6974       CALL xios_orchidee_send_field("snowrho_read_prev", snowrho_read_prev)
6975       CALL xios_orchidee_send_field("snowtemp_read_next", snowtemp_read_next)
6976       CALL xios_orchidee_send_field("snowtemp_read_current", snowtemp_read_current)
6977       CALL xios_orchidee_send_field("snowtemp_read_prev", snowtemp_read_prev)
6978       CALL xios_orchidee_send_field("mask_snow_interp_out", mask_snow_interp)
6979
6980       !! 2.4 Applay nudging of snow variables using alpha_nudge_snow at each model sechiba time step.
6981       !!     alpha_snow_nudge calculated using the parameter for relaxation time NUDGE_TAU_SNOW set in module constantes.
6982       !!     alpha_nudge_snow is between 0-1
6983       !!     If alpha_nudge_snow=1, the new snow variables will be replaced by the ones read from file.
6984       snowdz(:,:) = (1-alpha_nudge_snow)*snowdz(:,:) + alpha_nudge_snow * snowdz_read_current(:,:)
6985       snowrho(:,:) = (1-alpha_nudge_snow)*snowrho(:,:) + alpha_nudge_snow * snowrho_read_current(:,:)
6986       snowtemp(:,:) = (1-alpha_nudge_snow)*snowtemp(:,:) + alpha_nudge_snow * snowtemp_read_current(:,:)
6987
6988       !! 2.5 Calculate diagnostic for the nudging increment of water in snow
6989       nudgincswe=0.
6990       DO jg = 1, nsnow 
6991          nudgincswe(:) = nudgincswe(:) +  &
6992               alpha_nudge_snow*(snowdz_read_current(:,jg)*snowrho_read_current(:,jg)-snowdz(:,jg)*snowrho(:,jg))
6993       END DO
6994       CALL xios_orchidee_send_field("nudgincswe", nudgincswe)
6995       
6996    END IF
6997
6998  END SUBROUTINE hydrol_nudge_snow
6999
7000END MODULE hydrol
Note: See TracBrowser for help on using the repository browser.