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

Last change on this file since 8320 was 8320, checked in by josefine.ghattas, 7 months ago

Integrated changes done in [8289] : New default Values for irrig param, root zone def based on user-def depth.

See also ticket #857

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