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

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

Integrated new irrigation scheme developed by Pedro Arboleda. See ticket #857
This corresponds to revsion 7708 of version pedro.arboleda/ORCHIDEE. Following differences were made but were not made on the pedro.arboleda/ORCHIDEE :

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