source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_sechiba/hydrol.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

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