source: branches/publications/ORCHIDEE_CAMEO_gmd_2022/src_sechiba/hydrol.f90 @ 7693

Last change on this file since 7693 was 6608, checked in by josefine.ghattas, 4 years ago

Followed coding guidelines: remove mcs and mcfc as public variables in hydrol module as introduced in [6606].

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