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

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

As done in the trunk rev [6188]: Corrections done by A. Jornet. These errors crashed the model only in coupled mode with serveral treadds OMP.

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