source: branches/publications/ORCHIDEE_gmd-2018-261/src_sechiba/hydrol.f90 @ 5520

Last change on this file since 5520 was 4988, checked in by nicolas.vuichard, 7 years ago

rev08082017

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