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

Last change on this file since 8418 was 8418, checked in by bertrand.guenet, 5 months ago

The Moyano function describing the soil moisture effect on OM decomposition is added

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