source: branches/publications/ORCHIDEE_gmd_2018_MICT-LEAK/src_sechiba/hydrol.f90 @ 6591

Last change on this file since 6591 was 5383, checked in by simon.bowring, 6 years ago

last update

  • Property svn:keywords set to Revision Date HeadURL Date Author Revision
File size: 424.5 KB
Line 
1! ===================================================================================================\n
2! MODULE        : hydrol
3!
4! CONTACT       : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE       : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module computes the soil moisture processes on continental points.
10!!
11!!\n DESCRIPTION : contains hydrol_main, hydrol_initialize, hydrol_finalise, hydrol_init,
12!!                 hydrol_var_init, hydrol_waterbal, hydrol_alma,
13!!                 hydrol_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_p
60  USE grid
61  USE explicitsnow
62
63!pss:+USE TOPMODEL routines
64!  USE extrac_cti
65  USE ioipsl_para
66  USE init_top
67  USE hydro_subgrid
68!pss:-
69  USE interpol_help
70
71
72  IMPLICIT NONE
73
74  PRIVATE
75  PUBLIC :: hydrol_main, hydrol_initialize, hydrol_finalize, hydrol_clear, hydrol_rotation_update
76
77  !
78  ! variables used inside hydrol module : declaration and initialisation
79  !
80  LOGICAL, SAVE                                   :: first_hydrol_main=.TRUE.  !! Initialisation has to be done one time (true/false)
81!$OMP THREADPRIVATE(first_hydrol_main)
82  LOGICAL, SAVE                                   :: doponds=.FALSE.           !! Reinfiltration flag (true/false)
83!$OMP THREADPRIVATE(doponds)
84
85!pss:+
86  LOGICAL,SAVE                                    :: TOPM_calcul             !! flag of TOPMODEL usage
87!$OMP THREADPRIVATE(TOPM_calcul)
88!pss:-
89
90  REAL(r_std), SAVE                               :: froz_frac_corr            !! Coefficient for water frozen fraction correction
91!$OMP THREADPRIVATE(froz_frac_corr)
92  REAL(r_std), SAVE                               :: max_froz_hydro            !! Coefficient for water frozen fraction correction
93!$OMP THREADPRIVATE(max_froz_hydro)
94  REAL(r_std), SAVE                               :: smtot_corr                !! Coefficient for water frozen fraction correction
95!$OMP THREADPRIVATE(smtot_corr)
96  LOGICAL, SAVE                                   :: do_rsoil=.FALSE.          !! Flag to calculate rsoil for bare soile evap
97                                                                               !! (true/false)
98!$OMP THREADPRIVATE(do_rsoil)
99  LOGICAL, SAVE                                   :: ok_dynroot                !! Flag to activate dynamic root profile to optimize soil 
100                                                                               !! moisture usage, similar to Beer et al.2007
101!$OMP THREADPRIVATE(ok_dynroot)
102  CHARACTER(LEN=80) , SAVE                        :: var_name                  !! To store variables names for I/O
103!$OMP THREADPRIVATE(var_name)
104  !
105  REAL(r_std), PARAMETER                          :: allowed_err =  2.0E-8_r_std
106  REAL(r_std), PARAMETER                          :: EPS1 = EPSILON(un)      !! A small number
107  ! one dimension array allocated, computed, saved and got in hydrol module
108  ! Values per soil type
109  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: nvan                !! Van Genuchten coeficients n (unitless)
110                                                                          ! RK: 1/n=1-m
111!$OMP THREADPRIVATE(nvan)                                                 
112  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: avan                !! Van Genuchten coeficients a
113                                                                         !!  @tex $(mm^{-1})$ @endtex
114!$OMP THREADPRIVATE(avan)                                               
115  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcr                 !! Residual volumetric water content
116                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
117!$OMP THREADPRIVATE(mcr)                                                 
118  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcs_mineral         !! Saturated volumetric water content
119                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
120!$OMP THREADPRIVATE(mcs_mineral)                                                 
121  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: ks                  !! Hydraulic conductivity at saturation
122                                                                         !!  @tex $(mm d^{-1})$ @endtex
123!$OMP THREADPRIVATE(ks)                                                 
124  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: pcent               !! Fraction of saturated volumetric soil moisture above
125                                                                         !! which transpir is max (0-1, unitless)
126!$OMP THREADPRIVATE(pcent)
127  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcf_mineral         !! Volumetric water content at field capacity
128                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
129!$OMP THREADPRIVATE(mcf_mineral)                                                 
130  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcw_mineral         !! Volumetric water content at wilting point
131                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
132!$OMP THREADPRIVATE(mcw_mineral)                                                 
133  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcs               
134!$OMP THREADPRIVATE(mcs)                                                 
135  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcf 
136!$OMP THREADPRIVATE(mcf)
137  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mcw 
138!$OMP THREADPRIVATE(mcw)                                                 
139  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: VG_m
140!$OMP THREADPRIVATE(VG_m)                                                 
141  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: VG_n
142!$OMP THREADPRIVATE(VG_n)                                                 
143  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: VG_alpha
144!$OMP THREADPRIVATE(VG_alpha)                                                 
145  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: VG_psi_fc
146!$OMP THREADPRIVATE(VG_psi_fc)                                                 
147  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: VG_psi_wp
148!$OMP THREADPRIVATE(VG_psi_wp)                                                 
149
150  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_awet             !! Vol. wat. cont. above which albedo is cst
151                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
152!$OMP THREADPRIVATE(mc_awet)                                             
153  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: mc_adry             !! Vol. wat. cont. below which albedo is cst
154                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
155!$OMP THREADPRIVATE(mc_adry)                                             
156
157  ! Values per grid point
158  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_water_beg    !! Total amount of water at start of time step
159                                                                         !!  @tex $(kg m^{-2})$ @endtex
160!$OMP THREADPRIVATE(tot_water_beg)                                       
161  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_water_end    !! Total amount of water at end of time step
162                                                                         !!  @tex $(kg m^{-2})$ @endtex
163!$OMP THREADPRIVATE(tot_water_end)                                       
164  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_flux         !! Total water flux 
165                                                                         !!  @tex $(kg m^{-2})$ @endtex
166!$OMP THREADPRIVATE(tot_flux)                                           
167  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watveg_beg   !! Total amount of water on vegetation at start of time
168                                                                         !! step @tex $(kg m^{-2})$ @endtex
169!$OMP THREADPRIVATE(tot_watveg_beg)                                     
170  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watveg_end   !! Total amount of water on vegetation at end of time step
171                                                                         !!  @tex $(kg m^{-2})$ @endtex
172!$OMP THREADPRIVATE(tot_watveg_end)                                     
173  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watsoil_beg  !! Total amount of water in the soil at start of time step
174                                                                         !!  @tex $(kg m^{-2})$ @endtex
175!$OMP THREADPRIVATE(tot_watsoil_beg)                                     
176  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tot_watsoil_end  !! Total amount of water in the soil at end of time step
177                                                                         !!  @tex $(kg m^{-2})$ @endtex
178!$OMP THREADPRIVATE(tot_watsoil_end)                                     
179  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snow_beg         !! Total amount of snow at start of time step
180                                                                         !!  @tex $(kg m^{-2})$ @endtex
181!$OMP THREADPRIVATE(snow_beg)                                           
182  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snow_end         !! Total amount of snow at end of time step
183                                                                         !!  @tex $(kg m^{-2})$ @endtex
184!$OMP THREADPRIVATE(snow_end)                                           
185  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delsoilmoist     !! Change in soil moisture @tex $(kg m^{-2})$ @endtex
186!$OMP THREADPRIVATE(delsoilmoist)                                         
187  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delintercept     !! Change in interception storage
188                                                                         !!  @tex $(kg m^{-2})$ @endtex
189!$OMP THREADPRIVATE(delintercept)                                       
190  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: delswe           !! Change in SWE @tex $(kg m^{-2})$ @endtex
191!$OMP THREADPRIVATE(delswe)
192  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION (:)       :: undermcr         !! Nb of tiles under mcr for a given time step
193!$OMP THREADPRIVATE(undermcr)
194
195!pss+
196  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: mcs_grid              !! Saturation dim kjpindex
197  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: mcw_grid              !! Wilting point dim kjpindex 
198!pss-
199
200  ! array allocated, computed, saved and got in hydrol module
201  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mask_veget       !! zero/one when veget fraction is zero/higher (1)
202!$OMP THREADPRIVATE(mask_veget)
203  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: mask_soiltile    !! zero/one where soil tile is zero/higher (1)
204!$OMP THREADPRIVATE(mask_soiltile)
205  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: humrelv          !! Water stress index for transpiration
206                                                                         !! for each soiltile x PFT couple (0-1, unitless)
207!$OMP THREADPRIVATE(humrelv)
208  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: vegstressv       !! Water stress index for vegetation growth
209                                                                         !! for each soiltile x PFT couple (0-1, unitless)
210!$OMP THREADPRIVATE(vegstressv)
211  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:,:):: us               !! Water stress index for transpiration
212                                                                         !! (by soil layer and PFT) (0-1, unitless)
213!$OMP THREADPRIVATE(us)
214  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: precisol         !! Throughfall per PFT
215                                                                         !!  @tex $(kg m^{-2})$ @endtex
216!$OMP THREADPRIVATE(precisol)
217  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: precisol_ns      !! Throughfall per soiltile
218                                                                         !!  @tex $(kg m^{-2})$ @endtex
219!$OMP THREADPRIVATE(precisol_ns)
220  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ae_ns            !! Bare soil evaporation per soiltile
221                                                                         !!  @tex $(kg m^{-2})$ @endtex
222!$OMP THREADPRIVATE(ae_ns)
223  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: evap_bare_lim_ns !! Limitation factor (beta) for bare soil evaporation
224                                                                         !! per soiltile (used to deconvoluate vevapnu) 
225                                                                         !!  (0-1, unitless)
226!$OMP THREADPRIVATE(evap_bare_lim_ns)
227  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: free_drain_coef  !! Coefficient for free drainage at bottom
228                                                                         !!  (0-1, unitless)
229!$OMP THREADPRIVATE(free_drain_coef)
230  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: zwt_force        !! Prescribed water table depth (m)
231!$OMP THREADPRIVATE(zwt_force)
232  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: frac_bare_ns     !! Evaporating bare soil fraction per soiltile
233                                                                         !!  (0-1, unitless)
234!$OMP THREADPRIVATE(frac_bare_ns)
235  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: rootsink         !! Transpiration sink by soil layer and soiltile
236                                                                         !! @tex $(kg m^{-2})$ @endtex
237!$OMP THREADPRIVATE(rootsink)
238  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: subsnowveg       !! Sublimation of snow on vegetation
239                                                                         !!  @tex $(kg m^{-2})$ @endtex
240!$OMP THREADPRIVATE(subsnowveg)
241  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: subsnownobio     !! Sublimation of snow on other surface types 
242                                                                         !! (ice, lakes,...) @tex $(kg m^{-2})$ @endtex
243!$OMP THREADPRIVATE(subsnownobio)
244  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: snowmelt          !! Quantite de glace fondue
245!$OMP THREADPRIVATE(snowmelt)
246  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: icemelt          !! Quantite de glace fondue
247!$OMP THREADPRIVATE(icemelt)
248  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: subsinksoil      !! Excess of sublimation as a sink for the soil
249                                                                         !! @tex $(kg m^{-2})$ @endtex
250!$OMP THREADPRIVATE(subsinksoil)
251  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: vegtot           !! Total Total fraction of grid-cell covered by PFTs
252                                                                         !! (bare soil + vegetation) (1; 1)
253!$OMP THREADPRIVATE(vegtot)
254  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: resdist          !! Soiltile values from previous time-step (1; 1)
255!$OMP THREADPRIVATE(resdist)
256  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: vegtot_old       !! Total Total fraction of grid-cell covered by PFTs
257                                                                         !! from previous time-step (1; 1)
258!$OMP THREADPRIVATE(vegtot_old)
259  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: mx_eau_var       !! Maximum water content of the soil @tex $(kg m^{-2})$ @endtex
260!$OMP THREADPRIVATE(mx_eau_var)
261  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: irrig_fin        !! final application of irrigation water
262!$OMP THREADPRIVATE(irrig_fin)
263
264  ! arrays used by cwrr scheme
265  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: nroot            !! Normalized root length fraction in each soil layer
266                                                                         !! (0-1, unitless)
267                                                                         !! DIM = kjpindex * nvm * nslm
268!$OMP THREADPRIVATE(nroot)
269
270  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: kfact_root       !! Factor to increase Ks towards the surface
271                                                                         !! (unitless)
272                                                                         !! DIM = kjpindex * nslm * nstm
273!$OMP THREADPRIVATE(kfact_root)
274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: kfact            !! Factor to reduce Ks with depth (unitless)
275                                                                         !! DIM = nslm * nscm
276!$OMP THREADPRIVATE(kfact)
277  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: zz               !! Depth of nodes [znh in vertical_soil] transformed into (mm)
278!$OMP THREADPRIVATE(zz)
279  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: dz               !! Internode thickness [dnh in vertical_soil] transformed into (mm)
280!$OMP THREADPRIVATE(dz)
281  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: dh               !! Layer thickness [dlh in vertical_soil] transformed into (mm)
282!$OMP THREADPRIVATE(dh)
283  INTEGER(i_std), SAVE                               :: itopmax          !! Number of layers where the node is above 0.1m depth
284!$OMP THREADPRIVATE(itopmax)
285  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: mc_lin   !! 50 Vol. Wat. Contents to linearize K and D, for each texture
286                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
287                                                                 !! DIM = imin:imax * nscm
288!$OMP THREADPRIVATE(mc_lin)
289  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: k_lin    !! 50 values of unsaturated K, for each soil layer and texture
290                                                                 !!  @tex $(mm d^{-1})$ @endtex
291                                                                 !! DIM = imin:imax * nslm * nscm
292!$OMP THREADPRIVATE(k_lin)
293  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: d_lin    !! 50 values of diffusivity D, for each soil layer and texture
294                                                                 !!  @tex $(mm^2 d^{-1})$ @endtex
295                                                                 !! DIM = imin:imax * nslm * nscm
296!$OMP THREADPRIVATE(d_lin)
297  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: a_lin    !! 50 values of the slope in K=a*mc+b, for each soil layer and texture
298                                                                 !!  @tex $(mm d^{-1})$ @endtex
299                                                                 !! DIM = imin:imax * nslm * nscm
300!$OMP THREADPRIVATE(a_lin)
301  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: b_lin    !! 50 values of y-intercept in K=a*mc+b, for each soil layer and texture
302                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
303                                                                 !! DIM = imin:imax * nslm * nscm
304!$OMP THREADPRIVATE(b_lin)
305
306  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: humtot   !! Total Soil Moisture @tex $(kg m^{-2})$ @endtex
307!$OMP THREADPRIVATE(humtot)
308  LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:)          :: resolv   !! Mask of land points where to solve the diffusion equation
309                                                                 !! (true/false)
310!$OMP THREADPRIVATE(resolv)
311
312!! linarization coefficients of hydraulic conductivity K (hydrol_soil_coef)
313  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: k        !! Hydraulic conductivity K for each soil layer
314                                                                 !!  @tex $(mm d^{-1})$ @endtex
315                                                                 !! DIM = (:,nslm)
316!$OMP THREADPRIVATE(k)
317  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: kk_moy   !! Mean hydraulic conductivity over soiltiles (mm/d)
318!$OMP THREADPRIVATE(kk_moy)
319  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: kk       !! Hydraulic conductivity for each soiltiles (mm/d)
320!$OMP THREADPRIVATE(kk)
321  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: a        !! Slope in K=a*mc+b(:,nslm)
322                                                                 !!  @tex $(mm d^{-1})$ @endtex
323                                                                 !! DIM = (:,nslm)
324!$OMP THREADPRIVATE(a)
325  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: b        !! y-intercept in K=a*mc+b
326                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
327                                                                 !! DIM = (:,nslm)
328!$OMP THREADPRIVATE(b)
329!! linarization coefficients of hydraulic diffusivity D (hydrol_soil_coef)
330  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: d        !! Diffusivity D for each soil layer
331                                                                 !!  @tex $(mm^2 d^{-1})$ @endtex
332                                                                 !! DIM = (:,nslm)
333!$OMP THREADPRIVATE(d)
334!! matrix coefficients (hydrol_soil_tridiag and hydrol_soil_setup), see De Rosnay (1999), p155-157
335  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: e        !! Left-hand tridiagonal matrix coefficients
336!$OMP THREADPRIVATE(e)
337  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: f        !! Left-hand tridiagonal matrix coefficients
338!$OMP THREADPRIVATE(f)
339  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: g1       !! Left-hand tridiagonal matrix coefficients
340!$OMP THREADPRIVATE(g1)
341
342  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ep       !! Right-hand matrix coefficients
343!$OMP THREADPRIVATE(ep)
344  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: fp       !! Right-hand atrix coefficients
345!$OMP THREADPRIVATE(fp)
346  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: gp       !! Right-hand atrix coefficients
347!$OMP THREADPRIVATE(gp)
348  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: rhs      !! Right-hand system
349!$OMP THREADPRIVATE(rhs)
350  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: srhs     !! Temporarily stored rhs
351!$OMP THREADPRIVATE(srhs)
352  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: tmat             !! Left-hand tridiagonal matrix
353!$OMP THREADPRIVATE(tmat)
354  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: stmat            !! Temporarily stored tmat
355  !$OMP THREADPRIVATE(stmat)
356  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: water2infilt     !! Water to be infiltrated
357                                                                         !! @tex $(kg m^{-2})$ @endtex
358!$OMP THREADPRIVATE(water2infilt)
359  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc              !! Total moisture content per soiltile
360                                                                         !!  @tex $(kg m^{-2})$ @endtex
361!$OMP THREADPRIVATE(tmc)
362  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcr             !! Total moisture constent at residual per soiltile
363                                                                         !!  @tex $(kg m^{-2})$ @endtex
364!$OMP THREADPRIVATE(tmcr)
365  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmcs             !! Total moisture constent at saturation per soiltile
366                                                                         !!  @tex $(kg m^{-2})$ @endtex
367!$OMP THREADPRIVATE(tmcs)
368  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter       !! Total moisture in the litter per soiltile
369                                                                         !!  @tex $(kg m^{-2})$ @endtex
370!$OMP THREADPRIVATE(tmc_litter)
371  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_mea     !! Total moisture in the litter over the grid
372                                                                         !!  @tex $(kg m^{-2})$ @endtex
373!$OMP THREADPRIVATE(tmc_litt_mea)
374  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_wilt  !! Total moisture of litter at wilt point per soiltile
375                                                                         !!  @tex $(kg m^{-2})$ @endtex
376!$OMP THREADPRIVATE(tmc_litter_wilt)
377  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_field !! Total moisture of litter at field cap. per soiltile
378                                                                         !!  @tex $(kg m^{-2})$ @endtex
379!$OMP THREADPRIVATE(tmc_litter_field)
380!!! A CHANGER DANS TOUT HYDROL: tmc_litter_res et sat ne devraient pas dependre de ji - tdo
381  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_res   !! Total moisture of litter at residual moisture per soiltile
382                                                                         !!  @tex $(kg m^{-2})$ @endtex
383!$OMP THREADPRIVATE(tmc_litter_res)
384  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_sat   !! Total moisture of litter at saturation per soiltile
385                                                                         !!  @tex $(kg m^{-2})$ @endtex
386!$OMP THREADPRIVATE(tmc_litter_sat)
387  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_awet  !! Total moisture of litter at mc_awet per soiltile
388                                                                         !!  @tex $(kg m^{-2})$ @endtex
389!$OMP THREADPRIVATE(tmc_litter_awet)
390  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_litter_adry  !! Total moisture of litter at mc_adry per soiltile
391                                                                         !!  @tex $(kg m^{-2})$ @endtex
392!$OMP THREADPRIVATE(tmc_litter_adry)
393  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_wet_mea !! Total moisture in the litter over the grid below which
394                                                                         !! albedo is fixed constant
395                                                                         !!  @tex $(kg m^{-2})$ @endtex
396!$OMP THREADPRIVATE(tmc_litt_wet_mea)
397  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: tmc_litt_dry_mea !! Total moisture in the litter over the grid above which
398                                                                         !! albedo is constant
399                                                                         !!  @tex $(kg m^{-2})$ @endtex
400!$OMP THREADPRIVATE(tmc_litt_dry_mea)
401  LOGICAL, SAVE                                      :: tmc_init_updated = .FALSE. !! Flag allowing to determine if tmc is initialized.
402!$OMP THREADPRIVATE(tmc_init_updated)
403
404  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: v1               !! Temporary variable (:)
405!$OMP THREADPRIVATE(v1)
406
407  !! par type de sol :
408  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ru_ns            !! Surface runoff per soiltile
409                                                                         !!  @tex $(kg m^{-2})$ @endtex
410!$OMP THREADPRIVATE(ru_ns)
411  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: dr_ns            !! Drainage per soiltile
412                                                                         !!  @tex $(kg m^{-2})$ @endtex
413!$OMP THREADPRIVATE(dr_ns)
414  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tr_ns            !! Transpiration per soiltile
415!$OMP THREADPRIVATE(tr_ns)
416  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: vegetmax_soil    !! (:,nvm,nstm) percentage of each veg. type on each soil
417                                                                         !! of each grid point
418!$OMP THREADPRIVATE(vegetmax_soil)
419REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: mc                 !! Total volumetric water content at the calculation nodes
420                                                                         !! (eg : liquid + frozen)
421                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
422!$OMP THREADPRIVATE(mc)
423   REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: mcl              !! Liquid water content
424                                                                         !!  @tex $(m^{3} m^{-3})$ @endtex
425!$OMP THREADPRIVATE(mcl)
426  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soilmoist        !! (:,nslm) Mean of each soil layer's moisture
427                                                                         !! across soiltiles
428                                                                         !!  @tex $(kg m^{-2})$ @endtex
429!$OMP THREADPRIVATE(soilmoist)
430  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: soil_wet         !! Soil wetness above mcw (0-1, unitless)
431!$OMP THREADPRIVATE(soil_wet)
432  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: soil_wet_litter  !! Soil wetness aove mvw in the litter (0-1, unitless)
433!$OMP THREADPRIVATE(soil_wet_litter)
434  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: qflux            !! Diffusive water fluxes between soil layers
435!$OMP THREADPRIVATE(qflux)
436  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: frac_hydro_diag       !!
437!$OMP THREADPRIVATE(frac_hydro_diag)
438  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: profil_froz_hydro     !! Frozen fraction for each hydrological soil layer
439!$OMP THREADPRIVATE(profil_froz_hydro)
440  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: profil_froz_hydro_ns  !! As  profil_froz_hydro per soiltile
441!$OMP THREADPRIVATE(profil_froz_hydro_ns)
442  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: temp_hydro            !! Temp profile on hydrological levels
443!$OMP THREADPRIVATE(temp_hydro)
444
445!pss:+ TOPMODEL
446  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: fsat             !! field capacity fraction
447  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: fwet             !! wetland fraction with WTD = 0 cm
448  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: fwt1             !! wetland fraction with WTD entre 0 et -3cm
449  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: fwt2             !! wetland fraction with WTD entre -3cm et -6cm
450  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: fwt3             !! wetland fraction with WTD entre ... et ...
451  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: fwt4             !! etc.
452  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)      :: drunoff        !! runoff de Dunne
453!pss:-
454
455!pss:+ TOPMODEL parameter
456  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZMEAN            !! statistiques de la fonction de distribution des indices topo au sein de chaque maille
457  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZSTDT
458  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZSKEW
459  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZMIN
460  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZMAX
461!!  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: NB_PIXE
462!  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZWWILT           !! wilting point
463!  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZWSAT            !! saturation point
464!  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZWFC             !! field capacity
465!  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZD_TOP           !! profondeur de sol pour TOPMODEL
466  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZM               !! parametre TOPMODEL
467  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: ZZPAS            !! pas des veceturs d indice topo au sein de chaque maille
468! vecteurs calculees par TOPMODEL pour chaque maille (contenu = f(indice seuil); fsat = f(indice seuil); etc.)
469  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ZTAB_FSAT       
470  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ZTAB_WTOP
471  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ZTAB_FWET
472  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: ZTAB_WTOP_WET
473!pss:-
474
475!gmjc top 5 layer soil moisture for grazing
476  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)    :: tmc_trampling
477!$OMP THREADPRIVATE(tmc_trampling)
478!end gmjc
479  REAL(r_std), ALLOCATABLE, SAVE,DIMENSION(:)    :: refSOC_1d            !!initialize soil organic carbon only used to calculate thermal insulating effect
480  LOGICAL, SAVE                                  :: use_refSOC_hydrol = .TRUE. !! consider impacts of soil organic carbon on hydrologic parameters
481
482
483CONTAINS
484
485!! ================================================================================================================================
486!! SUBROUTINE   : hydrol_initialize
487!!
488!>\BRIEF         Allocate module variables, read from restart file or initialize with default values
489!!
490!! DESCRIPTION :
491!!
492!! MAIN OUTPUT VARIABLE(S) :
493!!
494!! REFERENCE(S) :
495!!
496!! FLOWCHART    : None
497!! \n
498!_ ================================================================================================================================
499
500  SUBROUTINE hydrol_initialize ( kjit,           kjpindex,  index,         rest_id,   &
501                                 njsc,           soiltile,  veget,         veget_max,        &
502                                 humrel,         vegstress, drysoil_frac,                    &
503                                 shumdiag_perma,    qsintveg,                        &
504                                 evap_bare_lim,  snow,      snow_age,      snow_nobio,       &
505!                                 evap_bare_lim,  evap_bare_lim_pft, snow,      snow_age,      snow_nobio,       &
506                                 snow_nobio_age, snowrho,   snowtemp,                        &
507                                 snowgrain,      snowdz,    snowheat,      fwet_out,         &
508                                 totfrac_nobio,  precip_rain, precip_snow, returnflow,       &
509                                 reinfiltration, irrigation,tot_melt,      vevapwet,         &
510                                 transpir,       vevapnu,   vevapsno,      vevapflo,         &
511                                 floodout,       runoff,    drainage,                        &
512                                 mc_layh,        mcl_layh,  tmc_layh,                        &
513                                 mc_layh_s,      mcl_layh_s, tmc_layh_s, &
514!gmjc
515                                 tmc_topgrass, humcste_use, altmax)
516!end gmjc
517
518    !! 0. Variable and parameter declaration
519    !! 0.1 Input variables
520    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number
521    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size
522    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map
523    INTEGER(i_std),INTENT (in)                         :: rest_id          !! Restart file identifier
524    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
525    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
526    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type           
527    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty)
528
529    !! 0.2 Output variables
530    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: humrel         !! Relative humidity
531    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: vegstress      !! Veg. moisture stress (only for vegetation growth)
532    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: drysoil_frac   !! function of litter wetness
533    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out)  :: shumdiag_perma !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
534    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)   :: qsintveg       !! Water on vegetation due to interception
535    REAL(r_std),DIMENSION (kjpindex), INTENT(out)        :: evap_bare_lim  !! Limitation factor for bare soil evaporation
536!    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(out)    :: evap_bare_lim_pft  !! Limitation factor for bare soil evaporation
537    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: snow           !! Snow mass [Kg/m^2]
538    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: snow_age       !! Snow age
539    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out):: snow_nobio     !! Water balance on ice, lakes, .. [Kg/m^2]
540    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out):: snow_nobio_age !! Snow age on ice, lakes, ...
541    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowrho        !! Snow density
542    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowtemp       !! Snow temperature
543    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowgrain      !! Snow grainsize
544    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowdz         !! Snow layer thickness
545    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(out) :: snowheat       !! Snow heat content
546    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: mc_layh        !! Volumetric moisture content for each layer in hydrol (liquid+ice) m3/m3
547    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: mcl_layh       !! Volumetric moisture content for each layer in hydrol (liquid) m3/m3
548    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (out)  :: tmc_layh       !! Total soil moisture content for each layer in hydrol (liquid+ice), mm
549    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT (out)  :: mc_layh_s        !! Volumetric moisture content for each layer in hydrol (liquid+ice) m3/m3
550    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT (out)  :: mcl_layh_s       !! Volumetric moisture content for each layer in hydrol (liquid) m3/m3
551    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT (out)  :: tmc_layh_s       !! Total soil moisture content for each layer in hydrol (liquid+ice), mm
552    REAL(r_std),DIMENSION (kjpindex)                     :: soilwetdummy   !! Temporary variable never used
553
554!gmjc
555    REAL(r_std),DIMENSION (kjpindex),INTENT(out)         :: tmc_topgrass
556!end gmjc
557    REAL(r_std),DIMENSION (kjpindex,nvm),INTENT(out)         :: humcste_use
558    REAL(r_std),DIMENSION (kjpindex,nvm),INTENT(in)         :: altmax
559    INTEGER(i_std)                                      :: ier
560    !! 0.4 Local variables
561    LOGICAL(r_std)                                       :: TOPMODEL_CTI
562    CHARACTER(LEN=80)                                    :: filename       !! To store file names for I/O
563    INTEGER(i_std)                                       :: iml, jml, lml, tml, fid
564    REAL(r_std),ALLOCATABLE,DIMENSION(:,:)               :: Zminf, Zmaxf, Zmeanf, Zstdf, Zskewf
565    REAL(r_std),ALLOCATABLE,DIMENSION(:)                 :: lon_temp, lat_temp
566    REAL(r_std)                                          :: lev(1), pssdate, pssdt
567    INTEGER(i_std)                                       :: pssitau(1)
568    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)             :: lat_rel, lon_rel
569    INTEGER(r_std)                                       :: ALLOC_ERR
570    INTEGER(i_std) :: il, ils, ip, ix, iy, imin, jmin
571    REAL(r_std) :: dlon, dlonmin, dlat, dlatmin
572
573    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: fwet_out       !! output wetland fraction to change energy or runoff ???!!!
574    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: totfrac_nobio    !! Total fraction of ice+lakes+...
575    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: precip_rain      !! Rain precipitation
576    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: precip_snow      !! Snow precipitation
577    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: returnflow       !! Routed water which comes back into the soil (from the
578                                                                             !! bottom)
579    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: reinfiltration   !! Routed water which comes back into the soil (at the
580                                                                             !! top)
581    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: irrigation       !! Water from irrigation returning to soil moisture 
582    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: tot_melt         !! Total melt
583    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: vevapwet         !! Interception loss
584    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: transpir         !! Transpiration
585    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapnu          !! Bare soil evaporation
586    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapsno         !! Snow evaporation
587    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapflo         !! Floodplain evaporation
588    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)       :: floodout     !! Flux out of floodplains
589    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)       :: runoff       !! Complete runoff
590    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)       :: drainage     !! Drainage
591
592    INTEGER(i_std)                                       :: jsl
593!_ ================================================================================================================================
594
595    !Config Key   = use_refSOC_hydrol
596    !Config Desc  =
597    !Config Def   =
598    !Config If    =
599    !Config Help  =
600    !Config         
601    !Config Units =
602    !
603    CALL getin_p('use_refSOC_hydrol',use_refSOC_hydrol)
604
605    IF (use_refSOC_hydrol) THEN
606      ALLOCATE (refSOC_1d(kjpindex),stat=ier)
607      IF (ier /= 0) CALL ipslerr_p(3,'hydrol_initialize', 'Error in allocation of refSOC_1d','','')
608 
609      CALL restget_p (rest_id, 'refSOC_1d', nbp_glo, 1, 1, kjit, .TRUE., refSOC_1d, "gather", nbp_glo, index_g)
610
611      IF (ALL(refSOC_1d(:) == val_exp)) THEN
612           CALL read_refSOC_1dfile(kjpindex,lalo,neighbours, resolution, contfrac)
613      ENDIF
614    ENDIF
615
616    CALL hydrol_init (kjit, kjpindex, index, rest_id, veget_max, soiltile, &
617         humrel, vegstress, snow,       snow_age,   snow_nobio, snow_nobio_age, qsintveg, &
618         snowdz, snowgrain, snowrho,    snowtemp,   snowheat, &
619         drysoil_frac, evap_bare_lim,  &
620!         snowflx,snowcap,   cgrnd_snow, dgrnd_snow, drysoil_frac, evap_bare_lim, evap_bare_lim_pft, &
621         fwet_out ) 
622   
623    CALL hydrol_var_init (kjpindex, veget, veget_max, &
624         soiltile, njsc, mx_eau_var, shumdiag_perma, &
625         drysoil_frac, qsintveg, mc_layh, mcl_layh, tmc_layh, &
626         mc_layh_s, mcl_layh_s, tmc_layh_s, &
627!gmjc
628         tmc_topgrass, humcste_use,altmax)
629!end gmjc
630!pss+       
631       !Config Key   = TOPM_CALCUL
632       !Config Desc  = Enable or disable TOPMODEL module
633       !Config Def   = False
634       !Config If    = OK_SECHIBA
635       !Config Help  = Enable or disable TOPMODEL module.
636       !Config         
637       !Config Units = [-]
638       TOPM_calcul  = .FALSE.
639       CALL getin_p('TOPM_CALCUL', TOPM_calcul)
640   
641       IF (TOPM_calcul) THEN
642
643          TOPMODEL_CTI = .TRUE.
644          IF (TOPMODEL_CTI) THEN
645            !  Needs to be a configurable variable
646            !
647            !
648            !Config Key   = TOPMODEL_PARAMETERS_FILE
649            !Config Desc  = Name of file from which TOPMODEL parameters file are read
650            !Config Def   = TOPMODEL_param_1deg.nc
651            !Config If    = TOPM_CALCUL and NOT(IMPOSE_VEG)
652            !Config Help  = The name of the file to be opened to read the TOPMODEL parameters.
653            !Config         
654            !Config Units = [FILE]
655            !
656            filename = 'TOPMODEL_param_1deg.nc'
657            CALL getin_p('TOPMODEL_PARAMETERS_FILE',filename)
658            !
659            IF (is_root_prc) THEN
660               CALL flininfo(filename,iml, jml, lml, tml, fid)
661               CALL flinclo(fid)
662            ENDIF
663            CALL bcast(iml)
664            CALL bcast(jml)
665            CALL bcast(lml)
666            CALL bcast(tml)
667            !
668            ! soils_param.nc file is 1° soit texture file.
669            !
670            ALLOC_ERR=-1
671            ALLOCATE(lat_rel(iml,jml), STAT=ALLOC_ERR)
672            IF (ALLOC_ERR/=0) THEN
673              WRITE(numout,*) "ERROR IN ALLOCATION of lat_rel : ",ALLOC_ERR
674              STOP
675            ENDIF
676            ALLOC_ERR=-1
677            ALLOCATE(lon_rel(iml,jml), STAT=ALLOC_ERR)
678            IF (ALLOC_ERR/=0) THEN
679              WRITE(numout,*) "ERROR IN ALLOCATION of lon_rel : ",ALLOC_ERR
680              STOP
681            ENDIF
682
683            ALLOC_ERR=-1
684            ALLOCATE(Zminf(iml,jml), STAT=ALLOC_ERR)
685            IF (ALLOC_ERR/=0) THEN
686              WRITE(numout,*) "ERROR IN ALLOCATION of ZMINf : ",ALLOC_ERR
687              STOP
688            ENDIF
689            ALLOC_ERR=-1
690            ALLOCATE(Zmaxf(iml,jml), STAT=ALLOC_ERR)
691            IF (ALLOC_ERR/=0) THEN
692              WRITE(numout,*) "ERROR IN ALLOCATION of ZMAXf : ",ALLOC_ERR
693              STOP
694            ENDIF
695            ALLOC_ERR=-1
696            ALLOCATE(Zmeanf(iml,jml), STAT=ALLOC_ERR)
697            IF (ALLOC_ERR/=0) THEN
698              WRITE(numout,*) "ERROR IN ALLOCATION of ZMEANf : ",ALLOC_ERR
699              STOP
700            ENDIF
701            ALLOC_ERR=-1
702            ALLOCATE(Zstdf(iml,jml), STAT=ALLOC_ERR)
703            IF (ALLOC_ERR/=0) THEN
704              WRITE(numout,*) "ERROR IN ALLOCATION of ZSTDTf : ",ALLOC_ERR
705              STOP
706            ENDIF
707            ALLOC_ERR=-1
708            ALLOCATE(Zskewf(iml,jml), STAT=ALLOC_ERR)
709            IF (ALLOC_ERR/=0) THEN
710              WRITE(numout,*) "ERROR IN ALLOCATION of ZSKEWf : ",ALLOC_ERR
711              STOP
712            ENDIF
713
714            ALLOC_ERR=-1
715            ALLOCATE (lon_temp(iml),lat_temp(jml), STAT=ALLOC_ERR)
716            IF (ALLOC_ERR/=0) THEN
717              WRITE(numout,*) "ERROR IN ALLOCATION of lon_temp,lat_temp : ",ALLOC_ERR
718              STOP
719            ENDIF
720            !
721            IF (is_root_prc) CALL flinopen(filename, .FALSE., iml, jml, lml, lon_rel, lat_rel, lev, tml, pssitau, pssdate, pssdt, fid)
722            CALL bcast(lon_rel)
723            CALL bcast(lat_rel)
724            CALL bcast(pssitau)
725            CALL bcast(pssdate)
726            CALL bcast(pssdt)
727
728            !
729            IF (is_root_prc) CALL flinget(fid, 'Zmin', iml, jml, lml, tml, 1, 1, Zminf)
730            IF (is_root_prc) CALL flinget(fid, 'Zmax', iml, jml, lml, tml, 1, 1, Zmaxf)
731            IF (is_root_prc) CALL flinget(fid, 'Zmean', iml, jml, lml, tml, 1, 1, Zmeanf)
732            IF (is_root_prc) CALL flinget(fid, 'Zstdev', iml, jml, lml, tml, 1, 1, Zstdf)
733            IF (is_root_prc) CALL flinget(fid, 'Zskew', iml, jml, lml, tml, 1, 1, Zskewf)
734
735            CALL bcast(Zminf)
736            CALL bcast(Zmaxf)
737            CALL bcast(Zmeanf)
738            CALL bcast(Zstdf)
739            CALL bcast(Zskewf)
740            !
741            IF (is_root_prc) CALL flinclo(fid)
742
743        !!!! TOPMODEL parameters 2D into 1D
744               lon_temp(:) = lon_rel(:,1)
745               lat_temp(:) = lat_rel(1,:)
746
747               DO ip = 1, kjpindex
748                  dlonmin = HUGE(1.)
749                  DO ix = 1,iml
750                     dlon = MIN( ABS(lalo(ip,2)-lon_temp(ix)), ABS(lalo(ip,2)+360.-lon_temp(ix)), ABS(lalo(ip,2)-360.-lon_temp(ix)) )
751                     IF ( dlon .LT. dlonmin ) THEN
752                        imin = ix
753                        dlonmin = dlon
754                     ENDIF
755                  ENDDO
756                  dlatmin = HUGE(1.)
757                  DO iy = 1,jml
758                     dlat = ABS(lalo(ip,1)-lat_temp(iy))
759                     IF ( dlat .LT. dlatmin ) THEN
760                        jmin = iy
761                        dlatmin = dlat
762                     ENDIF
763                  ENDDO
764                  ZMIN(ip) = Zminf(imin,jmin)
765                  ZMAX(ip) = Zmaxf(imin,jmin)
766                  ZMEAN(ip) = Zmeanf(imin,jmin)
767                  ZSTDT(ip) = Zstdf(imin,jmin)
768                  ZSKEW(ip) = Zskewf(imin,jmin)
769               ENDDO
770
771               DEALLOCATE (lon_temp)
772               DEALLOCATE (lat_temp)
773               DEALLOCATE (Zminf)
774               DEALLOCATE (Zmaxf)
775               DEALLOCATE (Zmeanf)
776               DEALLOCATE (Zstdf)
777               DEALLOCATE (Zskewf)
778             
779             TOPMODEL_CTI = .FALSE.
780             write (numout,*) 'STATS CTI OK num1!'
781             write (numout,*) 'psstest2'
782          ELSE
783             write (*,*) 'topmodel data already calculate!'
784             write (numout,*) 'psstest3'
785          ENDIF
786       ELSE
787         
788          ZMIN(:)=0.
789          ZMAX(:)=0.
790          ZMEAN(:)=0.
791          ZSTDT(:)=0.
792          ZSKEW(:)=0.
793
794       ENDIF
795
796       IF(TOPM_calcul) THEN
797 
798        !le deficit utilise pour TOPMODEL va etre calcule par rapport a la saturation
799        !ZM(:)=(ZWFC(:)-ZWWILT(:))*ZD_TOP(:)/4.
800
801        !ZM(:) = (mcs du grid_cell - mcw du grid_cell)*zmaxh/4.
802        mcs_grid(:) = mcs(1)*soiltile(:,1)+mcs(2)*soiltile(:,2)+mcs(3)*soiltile(:,3)
803        mcw_grid(:) = mcw(1)*soiltile(:,1)+mcw(2)*soiltile(:,2)+mcw(3)*soiltile(:,3)
804        ZM(:) = ( mcs_grid(:) -  mcw_grid(:) )*zmaxh/4.
805
806
807          !2 obtention des differentes fonctions necessaires a TOPMODEL en chaque grid-cell 
808          CALL init_top_main(kjpindex, lalo, veget_max, mcw_grid,mcs_grid,zmaxh, ZM,ZMIN, ZMAX, &
809               & ZMEAN, ZSTDT, ZSKEW, ZTAB_FSAT, ZTAB_WTOP, ZTAB_FWET, ZTAB_WTOP_WET, ZZPAS)
810         
811       ELSE
812
813          ZTAB_FSAT=0
814          ZTAB_WTOP=0
815          ZTAB_FWET=0
816          ZTAB_WTOP_WET=0
817          ZZPAS=0
818
819       ENDIF
820
821!pss:-
822      !! Initialize alma output variables if they were not found in the restart file. This is done in the end of
823      !! hydrol_initialize so that all variables(humtot,..) that will be used are initialized.
824      IF (ALL(tot_watveg_beg(:)==val_exp) .OR.  ALL(tot_watsoil_beg(:)==val_exp) .OR. ALL(snow_beg(:)==val_exp)) THEN
825            ! The output variable soilwetdummy is not calculated at first call to hydrol_alma.
826            CALL hydrol_alma(kjpindex, index, .TRUE., qsintveg, snow, snow_nobio, soilwetdummy)
827       END IF
828
829       ! If we check the water balance we first save the total amount of water
830       !! X if check_waterbal ==> hydrol_waterbal
831       ! init var, just in case is not initialized
832       tot_melt(:) = zero
833       IF (check_waterbal) THEN
834          CALL hydrol_waterbal(kjpindex, index, veget_max, &
835               & totfrac_nobio, qsintveg, snow, snow_nobio,&
836               & precip_rain, precip_snow, returnflow, reinfiltration, irrigation, tot_melt, &
837               & vevapwet, transpir, vevapnu, vevapsno, vevapflo, floodout, runoff,drainage)
838       ENDIF
839   
840
841    !! Calculate itopmax indicating the number of layers where the node is above 0.1m depth
842    itopmax=1
843    DO jsl = 1, nslm
844       ! znh : depth of nodes
845       IF (znh(jsl) <= 0.1) THEN
846          itopmax=jsl
847       END IF
848    END DO
849    IF (printlev>=3) WRITE(numout,*) "Number of layers where the node is above 0.1m depth: itopmax=",itopmax
850
851  END SUBROUTINE hydrol_initialize
852
853
854!! ================================================================================================================================
855!! SUBROUTINE   : hydrol_main
856!!
857!>\BRIEF         
858!!
859!! DESCRIPTION :
860!! - called every time step
861!! - initialization and finalization part are not done in here
862!!
863!! - 1 computes snow  ==> hydrol_snow
864!! - 2 computes vegetations reservoirs  ==> hydrol_vegupd
865!! - 3 computes canopy  ==> hydrol_canop
866!! - 4 computes surface reservoir  ==> hydrol_flood
867!! - 5 computes soil hydrology ==> hydrol_soil
868!! - X if check_waterbal ==> hydrol_waterbal
869!!
870!! IMPORTANT NOTICE : The water fluxes are used in their integrated form, over the time step
871!! dt_sechiba, with a unit of kg m^{-2}.
872!!
873!! RECENT CHANGE(S) : None
874!!
875!! MAIN OUTPUT VARIABLE(S) :
876!!
877!! REFERENCE(S) :
878!!
879!! FLOWCHART    : None
880!! \n
881!_ ================================================================================================================================
882
883  SUBROUTINE hydrol_main (kjit, kjpindex, &
884       & index, indexveg, indexsoil, indexlayer, indexnbdl, &
885       & temp_sol_new, floodout, runoff, drainage, frac_nobio, totfrac_nobio, vevapwet, veget, veget_max, njsc, &
886       & qsintmax, qsintveg, vevapnu, vevapnu_pft, vevapsno, vevapflo, snow, snow_age, snow_nobio, snow_nobio_age,  &
887       & tot_melt, transpir, precip_rain, precip_snow, returnflow, reinfiltration, irrigation, vegstress_old, transpot, &
888       & humrel, vegstress, drysoil_frac, evapot, evapot_penm, evap_bare_lim, flood_frac, flood_res, &
889!       & humrel, vegstress, drysoil_frac, evapot, evapot_penm, evap_bare_lim, evap_bare_lim_pft, flood_frac, flood_res, &
890       & shumdiag,shumdiag_perma, k_litt, litterhumdiag, soilcap, soiltile, reinf_slope, &
891         rest_id, hist_id, hist2_id, soil_deficit, is_crop_soil, &
892       & stempdiag, &
893       & temp_air, pb, u, v, tq_cdrag, pgflux, &
894       & snowrho,snowtemp, snowgrain,snowdz,snowheat,snowliq,&
895       & grndflux,gtemp, tot_bare_soil, &
896       & soilflxresid, mc_layh, mcl_layh, tmc_layh, &
897       !!!SIMON ORCHIDOC ADD
898       & runoff_per_soil, drainage_per_soil, soil_mc, &
899       & litter_mc, wat_flux0, wat_flux, &
900       & precip2canopy, precip2ground, canopy2ground, &
901       !!!SIMON ORCHIDOC ADD
902       & mc_layh_s, mcl_layh_s, tmc_layh_s, drunoff_tot, fwet_out, &
903       & lambda_snow, cgrnd_snow, dgrnd_snow, temp_sol_add, &
904!gmjc
905       & tmc_topgrass, humcste_use)
906!end gmjc
907
908    !! 0. Variable and parameter declaration
909
910    !! 0.1 Input variables
911 
912    INTEGER(i_std), INTENT(in)                         :: kjit             !! Time step number
913    INTEGER(i_std), INTENT(in)                         :: kjpindex         !! Domain size
914    INTEGER(i_std),INTENT (in)                         :: rest_id,hist_id  !! _Restart_ file and _history_ file identifier
915    INTEGER(i_std),INTENT (in)                         :: hist2_id         !! _history_ file 2 identifier
916    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index            !! Indeces of the points on the map
917    INTEGER(i_std),DIMENSION (kjpindex*nvm), INTENT (in):: indexveg        !! Indeces of the points on the 3D map for veg
918    INTEGER(i_std),DIMENSION (kjpindex*nstm), INTENT (in):: indexsoil      !! Indeces of the points on the 3D map for soil
919    INTEGER(i_std),DIMENSION (kjpindex*nslm), INTENT (in):: indexlayer     !! Indeces of the points on the 3D map for soil layers
920    INTEGER(i_std),DIMENSION (kjpindex*nslm), INTENT (in):: indexnbdl      !! Indeces of the points on the 3D map for of diagnostic soil layers
921
922    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_rain      !! Rain precipitation
923    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_snow      !! Snow precipitation
924    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: returnflow       !! Routed water which comes back into the soil (from the
925                                                                           !! bottom)
926    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinfiltration   !! Routed water which comes back into the soil (at the
927                                                                           !! top)
928    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: irrigation       !! Water from irrigation returning to soil moisture 
929    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: vegstress_old    !! vegstress of previous step
930    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: transpot         !! potential transpiratio
931
932    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: temp_sol_new     !! New soil temperature
933
934    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
935    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: frac_nobio     !! Fraction of ice, lakes, ...
936    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: totfrac_nobio    !! Total fraction of ice+lakes+...
937    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: soilcap          !! Soil capacity
938    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
939    LOGICAL, DIMENSION (nstm), INTENT (in) :: is_crop_soil                 !! whether soil tile is under cropland
940    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: vevapwet         !! Interception loss
941    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget            !! Fraction of vegetation type           
942    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max        !! Max. fraction of vegetation type (LAI -> infty)
943    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintmax         !! Maximum water on vegetation for interception
944    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: transpir         !! Transpiration
945    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinf_slope      !! Slope coef
946    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot           !! Soil Potential Evaporation
947    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: evapot_penm      !! Soil Potential Evaporation Correction
948    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: flood_frac       !! flood fraction
949    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (in) :: stempdiag        !! Diagnostic temp profile from thermosoil
950    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: temp_air         !! Air temperature
951    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: u,v              !! Horizontal wind speed
952    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: tq_cdrag         !! Surface drag coefficient (-)
953    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: pb               !! Surface pressure
954    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: pgflux           !! Net energy into snowpack
955    REAL(r_std),DIMENSION (kjpindex),INTENT(inout)     :: soilflxresid     !! Energy flux to the snowpack
956    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: gtemp            !! First soil layer temperature
957    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: tot_bare_soil    !! Total evaporating bare soil fraction
958    REAL(r_std),DIMENSION (kjpindex), INTENT(in)       :: lambda_snow      !! Coefficient of the linear extrapolation of surface temperature
959    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in):: cgrnd_snow       !! Integration coefficient for snow numerical scheme
960    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in):: dgrnd_snow       !! Integration coefficient for snow numerical scheme
961    !! 0.2 Output variables
962
963    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out) :: vegstress        !! Veg. moisture stress (only for vegetation growth)
964    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: drysoil_frac     !! function of litter wetness
965    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out):: shumdiag         !! Relative soil moisture in each soil layer
966                                                                           !! with respect to (mcf-mcw)
967                                                                           !! (unitless; can be out of 0-1)
968    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out):: shumdiag_perma   !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
969    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: k_litt           !! litter approximate conductivity
970    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: litterhumdiag    !! litter humidity
971    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: tot_melt         !! Total melt   
972    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: floodout         !! Flux out of floodplains
973   
974!pss:+
975    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)     :: drunoff_tot    !! Dunne runoff
976    REAL(r_std),DIMENSION (kjpindex), INTENT (out)     :: fwet_out   !! fwet: to change the balance of energy according to wetland fraction
977!pss:-
978
979    !! 0.3 Modified variables
980
981    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout):: qsintveg         !! Water on vegetation due to interception
982    REAL(r_std),DIMENSION (kjpindex), INTENT(inout)    :: evap_bare_lim    !! Limitation factor (beta) for bare soil evaporation   
983!    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout) :: evap_bare_lim_pft    !! Limitation factor (beta) for bare soil evaporation   
984    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(out) :: soil_deficit    !! water deficit to reach IRRIG_FULFILL of holding capacity
985    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(inout):: humrel           !! Relative humidity
986    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapnu          !! Bare soil evaporation
987    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout) :: vevapnu_pft      !! Bare soil evaporation
988    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapsno         !! Snow evaporation
989    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: vevapflo         !! Floodplain evaporation
990    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: flood_res        !! flood reservoir estimate
991    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: snow             !! Snow mass [kg/m^2]
992    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)   :: snow_age         !! Snow age
993    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (inout) :: snow_nobio  !! Water balance on ice, lakes, .. [Kg/m^2]
994    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (inout) :: snow_nobio_age !! Snow age on ice, lakes, ...
995    !! We consider that any water on the ice is snow and we only peforme a water balance to have consistency.
996    !! The water balance is limite to + or - 10^6 so that accumulation is not endless
997
998    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: runoff       !! Complete surface runoff
999    REAL(r_std),DIMENSION (kjpindex), INTENT (out)         :: drainage     !! Drainage
1000    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(out)    :: runoff_per_soil !! runoff for each soil type[mm]
1001    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(out)    :: drainage_per_soil !! drainage for each soil type [mm]
1002    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowrho      !! Snow density
1003    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowtemp     !! Snow temperature
1004    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowgrain    !! Snow grainsize
1005    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowdz       !! Snow layer thickness
1006    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowheat     !! Snow heat content
1007    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(inout) :: snowliq      !! Snow liquid content (m)
1008    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)       :: grndflux     !! Net flux into soil W/m2
1009    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: mc_layh      !! Volumetric moisture content for each layer in hydrol(liquid + ice) [m3/m3)]
1010    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: mcl_layh     !! Volumetric moisture content for each layer in hydrol(liquid) [m3/m3]
1011    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT(out)     :: tmc_layh     !! Total soil moisture content for each layer in hydrol(liquid + ice) [mm]
1012    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(out)  :: mc_layh_s      !! Volumetric moisture content for each layer in hydrol(liquid + ice) [m3/m3)]
1013    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(out)  :: mcl_layh_s     !! Volumetric moisture content for each layer in hydrol(liquid) [m3/m3]
1014    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(out)  :: tmc_layh_s     !! Total soil moisture content for each layer in hydrol(liquid + ice) [mm]
1015    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)       :: temp_sol_add !! additional surface temperature due to the melt of first layer
1016                                                                           !! at the present time-step @tex ($K$) @endtex
1017    REAL(r_std),DIMENSION (kjpindex,nbdl,nstm), INTENT(out):: soil_mc        !! soil moisture content \f($m^3 \times m^3$)\f
1018    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(out)     :: litter_mc      !! litter moisture content \f($m^3 \times m^3$)\f
1019    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(out)     :: wat_flux0      !! Water flux in the first soil layers exported for soil C calculations
1020    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(out):: wat_flux       !! Water flux in the soil layers exported for soil C calculations
1021    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(out)      :: precip2canopy  !! Precipitation onto the canopy
1022    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(out)      :: precip2ground  !! Precipitation not intercepted by canopy
1023    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT(out)      :: canopy2ground  !! Water flux from canopy to the ground
1024   
1025
1026!gmjc
1027    REAL(r_std),DIMENSION (kjpindex), INTENT(out)       :: tmc_topgrass
1028!end gmjc
1029    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: humcste_use
1030    !! 0.4 Local variables
1031
1032    INTEGER(i_std)                                     :: jst              !! Index of soil tiles (unitless, 1-3)
1033    INTEGER(i_std)                                     :: jsl              !! Index of soil layers (unitless)
1034    INTEGER(i_std)                                     :: ji, jv
1035    REAL(r_std)                                        :: tempfrac         !! temporary fraction for irrigation
1036    REAL(r_std),DIMENSION (kjpindex)                   :: soilwet          !! A temporary diagnostic of soil wetness
1037    REAL(r_std),DIMENSION (kjpindex)                   :: snowdepth        !! Depth of snow layer, only for diagnostics with ok_explicitsnow=n
1038    REAL(r_std),DIMENSION (kjpindex)                   :: njsc_tmp         !! Temporary REAL value for njsc to write it
1039    REAL(r_std),DIMENSION (kjpindex,nvm)               :: irrig_demand_ratio !! irrigation demand for different PFTs
1040    REAL(r_std), DIMENSION (kjpindex)                  :: snowmelt         !! Snow melt [mm/dt_sechiba]
1041    REAL(r_std), DIMENSION (kjpindex,nstm)             :: tmc_top          !! Moisture content in the itopmax upper layers, per tile
1042    REAL(r_std), DIMENSION (kjpindex)                  :: humtot_top       !! Moisture content in the itopmax upper layers, for diagnistics
1043    REAL(r_std), DIMENSION(kjpindex)                   :: histvar          !! Temporary variable when computations are needed
1044    REAL(r_std), DIMENSION (kjpindex,nvm)              :: frac_bare        !! Fraction(of veget_max) of bare soil in each vegetation type
1045!pss:+
1046    logical                                           :: filealive, TOPMODEL_CTI
1047    INTEGER(i_std)                                    :: ind_spe, iet
1048!pss:-
1049!pss:+
1050    CHARACTER(LEN=80) :: filename   !! To store file names for I/O
1051    INTEGER(i_std) :: il, ils, ip, ix, iy, imin, jmin
1052    REAL(r_std) :: dlon, dlonmin, dlat, dlatmin
1053    INTEGER(i_std) :: iml, jml, lml, tml, fid
1054    REAL(r_std),ALLOCATABLE,DIMENSION(:,:) :: Zminf, Zmaxf, Zmeanf, Zstdf, Zskewf
1055    REAL(r_std),ALLOCATABLE,DIMENSION(:) :: lon_temp, lat_temp
1056    REAL(r_std) :: lev(1), pssdate, pssdt
1057    INTEGER(i_std) :: pssitau(1)
1058    REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: lat_rel, lon_rel
1059    INTEGER                  :: ALLOC_ERR
1060
1061!pss-
1062    REAL(r_std), DIMENSION(kjpindex)                   :: twbr             !! Grid-cell mean of TWBR Total Water Budget Residu[kg/m2/dt]
1063    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_nroot       !! To ouput the grid-cell mean of nroot
1064    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_dlh         !! To ouput the soil layer thickness on all grid points [m]
1065    REAL(r_std),DIMENSION (kjpindex,nslm)              :: land_mcs         !! To ouput the grid-cell mean of mcs
1066    REAL(r_std),DIMENSION (kjpindex)                   :: drain_upd        !! Change in drainage due to decrease in vegtot
1067                                                                           !! on mc [kg/m2/dt]
1068    REAL(r_std),DIMENSION (kjpindex)                   :: runoff_upd       !! Change in runoff due to decrease in vegtot
1069                                                                           !! on water2infilt[kg/m2/dt]
1070   
1071
1072!_ ================================================================================================================================
1073    !! 1. Update vegtot_old and recalculate vegtot
1074    vegtot_old(:) = vegtot(:)
1075
1076    DO ji = 1, kjpindex
1077       vegtot(ji) = SUM(veget_max(ji,:))
1078    ENDDO
1079
1080    !! 3. Shared time step
1081    IF (printlev>=3) WRITE (numout,*) 'hydrol pas de temps = ',dt_sechiba
1082
1083!pss:+
1084    !! 3.0 Calculate wetland fractions
1085       
1086    IF (TOPM_calcul) THEN
1087        CALL hydro_subgrid_main(kjpindex, ZTAB_FSAT, ZTAB_WTOP, humtot, profil_froz_hydro, fsat,&
1088           & ZTAB_FWET,ZTAB_WTOP_WET,fwet, zmaxh, &
1089           & 1000*(mcs_grid(:)-mcw_grid(:)), fwt1, fwt2, fwt3, fwt4, ZM, ZMIN, ZMAX, ZZPAS, dz)
1090
1091    ELSE
1092        fsat(:)=0.0
1093        fwet(:)=0.0
1094        fwt1(:)=0.0
1095        fwt2(:)=0.0
1096        fwt3(:)=0.0
1097        fwt4(:)=0.0
1098    ENDIF
1099
1100    fwet_out(:)=fwet(:)
1101!pss:-
1102
1103    !
1104    !! 3.1 Calculate snow processes with explicit method or bucket snow model
1105    IF (ok_explicitsnow) THEN
1106       ! Explicit snow model
1107       IF (printlev>=3) WRITE (numout,*) ' ok_explicitsnow : use multi-snow layer '
1108    IF (ANY(vevapsno < -10e+30)) CALL ipslerr_p(3, 'hydrol_snow', 'vevapsno is too big', '', '')
1109       
1110       CALL explicitsnow_main(kjpindex,    precip_rain,   precip_snow,    temp_air,   pb,       &
1111                              u,           v,             temp_sol_new,   soilcap,    pgflux,   &
1112                              frac_nobio,  totfrac_nobio, gtemp,                                &
1113                              lambda_snow, cgrnd_snow,    dgrnd_snow,                           & 
1114                              vevapsno,    snow_age,      snow_nobio_age, snow_nobio, snowrho,  &
1115                              snowgrain,   snowdz,        snowtemp,       snowheat,   snow,     &
1116                              temp_sol_add,                                                     &
1117                              snowliq,     subsnownobio,  grndflux,       snowmelt,   tot_melt, &
1118                              soilflxresid,subsinksoil)
1119    IF (ANY(vevapsno < -10e+30)) CALL ipslerr_p(3, 'hydrol_snow', 'vevapsno is too big', '', '')
1120 
1121    ELSE
1122       ! Bucket snow model
1123       CALL hydrol_snow(kjpindex, precip_rain, precip_snow, temp_sol_new, soilcap, &
1124            frac_nobio, totfrac_nobio, vevapsno, snow, snow_age, snow_nobio, snow_nobio_age, &
1125            tot_melt, snowdepth,snowmelt)
1126    END IF
1127       
1128    !
1129    !! 3.2 computes vegetations reservoirs  ==>hydrol_vegupd
1130! Modif temp vuichard
1131    CALL hydrol_vegupd(kjpindex, veget, veget_max, soiltile, qsintveg, frac_bare, drain_upd, runoff_upd)
1132
1133    !! Calculate kfact_root
1134    !! An exponential factor is used to increase ks near the surface depending on the amount of roots in the soil
1135    !! through a geometric average over the vegets
1136    !! This comes from the PhD thesis of d'Orgeval, 2006, p82; d'Orgeval et al. 2008, Eqs. 3-4
1137    !! (Calibrated against Hapex-Sahel measurements)
1138    !! Since rev 2916: veget_max/2 is used instead of veget
1139    kfact_root(:,:,:) = un
1140    DO jsl = 1, nslm
1141       DO jv = 2, nvm
1142          jst = pref_soil_veg(jv)
1143          DO ji = 1, kjpindex
1144             IF(soiltile(ji,jst) .GT. min_sechiba) THEN
1145                kfact_root(ji,jsl,jst) = kfact_root(ji,jsl,jst) * &
1146                     & MAX((MAXVAL(ks_usda)/ks(njsc(ji)))**(- vegetmax_soil(ji,jv,jst)/2 * (humcste(jv)*zz(jsl)/mille - un)/deux), &
1147                     un) 
1148             ENDIF
1149          ENDDO
1150       ENDDO
1151    ENDDO
1152!write(numout,*) 'hydrol.f90 kfact_root=',kfact_root
1153    !
1154    !! 3.3 computes canopy  ==>hydrol_canop
1155    CALL hydrol_canop(kjpindex, precip_rain, vevapwet, veget_max, veget, qsintmax, qsintveg,precisol,tot_melt, &
1156         & precip2canopy, precip2ground, canopy2ground)
1157
1158    !
1159    !! 3.4 computes surface reservoir  ==>hydrol_flood
1160    CALL hydrol_flood(kjpindex,  vevapflo, flood_frac, flood_res, floodout)
1161
1162    !
1163    !! 3.5 computes soil hydrology ==>hydrol_soil
1164    !!! calculating ratio of irrigation for each pft at each point
1165    irrig_demand_ratio(:,:) = zero
1166!    irrig_totfrac(:) = zero
1167    DO ji = 1,kjpindex
1168        DO jv = 2,nvm
1169            IF (veget_max(ji,jv) .GT. zero) THEN
1170                IF (irrig_drip) THEN
1171                    tempfrac = veget(ji,jv)/veget_max(ji,jv)
1172                    IF ( ok_LAIdev(jv) .AND. (vegstress_old(ji,jv) .LT. irrig_threshold(jv)) .AND.  &
1173                        & (transpot(ji,jv)*tempfrac + evapot(ji)*(1-tempfrac) .GT. precip_rain(ji)) ) THEN
1174        !                irrig_totfrac(ji) = irrig_totfrac(ji) + veget_max(ji,jv)
1175                        irrig_demand_ratio(ji,jv) = MIN( irrig_dosmax, irrig_fulfill(jv) * &
1176                                                    & ( transpot(ji,jv)*tempfrac &
1177                                                    & + evapot(ji)*(1-tempfrac) &
1178                                                    & - precip_rain(ji) ) ) * veget_max(ji,jv)
1179                        !!!! reconsider if evapot or evapot_corr to be used as irrigation demand
1180                        !!!! if re-infiltration is considered in sechiba, it
1181                        !should also be considered here, xuhui
1182                    ENDIF ! since irrigated ratio is the same across pfts on the same grid, no need to consider
1183                ELSE ! flooding
1184                    IF ( ok_LAIdev(jv) .AND. (vegstress_old(ji,jv) .LT. irrig_threshold(jv)) ) THEN
1185                        irrig_demand_ratio(ji,jv) = MIN( irrig_dosmax, MAX( zero, soil_deficit(ji,jv) ) ) * veget_max(ji,jv)
1186                    ENDIF
1187                    !!!! if re-infiltration is considered in sechiba, it
1188                        !should also be considered here, xuhui
1189                ENDIF
1190            ENDIF
1191        ENDDO
1192        IF ( SUM(irrig_demand_ratio(ji,:)) .GT. zero ) THEN
1193            irrig_demand_ratio(ji,:) = irrig_demand_ratio(ji,:) / SUM(irrig_demand_ratio(ji,:))
1194        ENDIF
1195    ENDDO
1196
1197    !!! end ratio_irrig, Xuhui
1198
1199    CALL hydrol_soil(kjpindex, veget_max, soiltile, njsc, reinf_slope,  &
1200         transpir, vevapnu, vevapnu_pft, evapot, evapot_penm, runoff, &
1201         drainage, returnflow, reinfiltration, irrigation, irrig_demand_ratio, &
1202         tot_melt,evap_bare_lim, shumdiag, shumdiag_perma, &
1203!         tot_melt,evap_bare_lim, evap_bare_lim_pft, shumdiag, shumdiag_perma, &
1204         k_litt, litterhumdiag, humrel, vegstress, drysoil_frac, &
1205         irrig_fin, is_crop_soil, &
1206         stempdiag,snow,snowdz, tot_bare_soil, &
1207         u, v, tq_cdrag, &
1208         mc_layh, mcl_layh, tmc_layh, mc_layh_s, mcl_layh_s, &
1209         soil_mc, litter_mc,wat_flux0, wat_flux,drainage_per_soil, runoff_per_soil, &
1210         drunoff_tot, fsat, &
1211!gmjc
1212         tmc_topgrass)
1213!end gmjc
1214
1215    DO ji = 1,kjpindex
1216        DO jv = 2,nvm
1217           IF (.NOT. natural(jv) .AND. ok_LAIdev(jv)) THEN
1218               IF (.NOT. is_crop_soil(pref_soil_veg(jv))) THEN
1219                   STOP 'hydrol irrig'
1220               ENDIF
1221               !! soil_deficit(ji,jv) = MAX( zero, irrig_fulfill(jv)*tmcs(ji,4) - tmc(ji,4) ) !mm
1222               ! note that since crop soil may not necessarily be the fourth
1223               ! soil colum, this needs to be changed !xuhui 151214
1224               soil_deficit(ji,jv) = MAX( zero, irrig_fulfill(jv)*tmcs(ji,pref_soil_veg(jv)) - tmc(ji,pref_soil_veg(jv)) ) !mm
1225           ENDIF
1226        ENDDO
1227    ENDDO
1228
1229
1230    ! The update fluxes come from hydrol_vegupd
1231    drainage(:) =  drainage(:) +  drain_upd(:)
1232    runoff(:) =  runoff(:) +  runoff_upd(:)
1233
1234    ! If we check the water balance we end with the comparison of total water change and fluxes
1235    IF (check_waterbal) THEN
1236       CALL hydrol_waterbal(kjpindex, index, veget_max, totfrac_nobio, &
1237            & qsintveg, snow,snow_nobio, precip_rain, precip_snow, returnflow, reinfiltration, &
1238            & irrigation, tot_melt, vevapwet, transpir, vevapnu, vevapsno, vevapflo, floodout, runoff, drainage)
1239    ENDIF
1240
1241    !! 4 write out file  ==> hydrol_alma/histwrite(*)
1242    !
1243    ! If we use the ALMA standards
1244    CALL hydrol_alma(kjpindex, index, .FALSE., qsintveg, snow, snow_nobio, soilwet)
1245   
1246
1247    ! Calculate the moisture in the upper itopmax layers corresponding to 0.1m (humtot_top):
1248    ! For ORCHIDEE with nslm=11 and zmaxh=2, itopmax=6.
1249    ! We compute tmc_top as tmc but only for the first itopmax layers. Then we compute a humtot with this variable.
1250    DO jst=1,nstm
1251       DO ji=1,kjpindex
1252          tmc_top(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
1253          DO jsl = 2, itopmax
1254             tmc_top(ji,jst) = tmc_top(ji,jst) + dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
1255                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
1256          ENDDO
1257       ENDDO
1258    ENDDO
1259 
1260    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
1261    humtot_top(:) = zero
1262    DO jst=1,nstm
1263       DO ji=1,kjpindex
1264          humtot_top(ji) = humtot_top(ji) + soiltile(ji,jst) * tmc_top(ji,jst) * vegtot(ji)
1265       ENDDO
1266    ENDDO
1267
1268    ! Calculate the Total Water Budget Residu (in kg/m2 over dt_sechiba)
1269    ! All the delstocks and fluxes below are averaged over the mesh
1270    ! snow_nobio included in delswe
1271    ! Does not include the routing reservoirs, although the flux to/from routing are integrated
1272    DO ji=1,kjpindex
1273       twbr(ji) = (delsoilmoist(ji) + delintercept(ji) + delswe(ji)) &
1274            - ( precip_rain(ji) + precip_snow(ji) + irrigation(ji) + floodout(ji) &
1275            + returnflow(ji) + reinfiltration(ji) ) &
1276            + ( runoff(ji) + drainage(ji) + SUM(vevapwet(ji,:)) &
1277            + SUM(transpir(ji,:)) + vevapnu(ji) + vevapsno(ji) + vevapflo(ji) ) 
1278    ENDDO
1279    ! Transform unit from kg/m2/dt to kg/m2/s (or mm/s)
1280    CALL xios_orchidee_send_field("twbr",twbr/dt_sechiba)
1281    CALL xios_orchidee_send_field("undermcr",undermcr) ! nb of tiles undermcr at end of timestep
1282
1283    ! Calculate land_nroot : grid-cell mean of nroot
1284    ! Do not treat PFT1 because it has no roots
1285    land_nroot(:,:) = zero
1286    DO jsl=1,nslm
1287       DO jv=2,nvm
1288          DO ji=1,kjpindex
1289               IF ( vegtot(ji) > min_sechiba ) THEN
1290               land_nroot(ji,jsl) = land_nroot(ji,jsl) + veget_max(ji,jv) * nroot(ji,jv,jsl) / vegtot(ji) 
1291            END IF
1292          END DO
1293       ENDDO
1294    ENDDO
1295    CALL xios_orchidee_send_field("nroot",land_nroot)   
1296
1297    DO jsl=1,nslm
1298       land_dlh(:,jsl)=dlh(jsl)
1299    ENDDO
1300    CALL xios_orchidee_send_field("dlh",land_dlh)
1301
1302    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
1303    land_mcs(:,:) = zero
1304    DO jsl=1,nslm
1305       DO jst=1,nstm
1306          DO ji=1,kjpindex
1307             land_mcs(ji,jsl) = land_mcs(ji,jsl) + soiltile(ji,jst) * tmcs(ji,jst) * vegtot(ji) 
1308          ENDDO
1309       ENDDO
1310    ENDDO
1311    CALL xios_orchidee_send_field("mcs",land_mcs/(zmaxh* mille)) ! in m3/m3
1312    CALL xios_orchidee_send_field("water2infilt",water2infilt)   
1313
1314    CALL xios_orchidee_send_field("mc",mc)
1315    CALL xios_orchidee_send_field("kfact_root",kfact_root)
1316    CALL xios_orchidee_send_field("vegetmax_soil",vegetmax_soil)
1317
1318    CALL xios_orchidee_send_field("evapnu_soil",ae_ns/dt_sechiba)
1319    CALL xios_orchidee_send_field("drainage_soil",dr_ns/dt_sechiba)
1320    CALL xios_orchidee_send_field("transpir_soil",tr_ns/dt_sechiba)
1321    CALL xios_orchidee_send_field("runoff_soil",ru_ns/dt_sechiba)
1322    CALL xios_orchidee_send_field("humrel",humrel)     
1323    CALL xios_orchidee_send_field("irrig_fin",irrig_fin*one_day/dt_sechiba)
1324    CALL xios_orchidee_send_field("drainage",drainage/dt_sechiba) ! [kg m-2 s-1]
1325    CALL xios_orchidee_send_field("runoff",runoff/dt_sechiba) ! [kg m-2 s-1]
1326    CALL xios_orchidee_send_field("precisol",precisol/dt_sechiba)
1327    CALL xios_orchidee_send_field("precip_rain",precip_rain/dt_sechiba)
1328    CALL xios_orchidee_send_field("precip_snow",precip_snow/dt_sechiba)
1329    CALL xios_orchidee_send_field("qsintmax",qsintmax)
1330    CALL xios_orchidee_send_field("qsintveg",qsintveg)
1331    CALL xios_orchidee_send_field("qsintveg_tot",SUM(qsintveg(:,:),dim=2))
1332    histvar(:)=(precip_rain(:)-SUM(precisol(:,:),dim=2))
1333    CALL xios_orchidee_send_field("prveg",histvar/dt_sechiba)
1334
1335    IF ( do_floodplains ) THEN
1336       CALL xios_orchidee_send_field("floodout",floodout/dt_sechiba)
1337    END IF
1338
1339    IF (check_waterbal) THEN
1340       CALL xios_orchidee_send_field("tot_flux",tot_flux/dt_sechiba)
1341    END IF
1342
1343    CALL xios_orchidee_send_field("snowmelt",snowmelt/dt_sechiba)
1344    CALL xios_orchidee_send_field("tot_melt",tot_melt/dt_sechiba)
1345
1346    CALL xios_orchidee_send_field("soilmoist",soilmoist)
1347    CALL xios_orchidee_send_field("tmc",tmc)
1348    CALL xios_orchidee_send_field("humtot",humtot)
1349    CALL xios_orchidee_send_field("humtot_top",humtot_top)
1350
1351    IF (ok_explicitsnow) THEN
1352       CALL xios_orchidee_send_field("snowdz",snowdz)
1353    ELSE
1354       CALL xios_orchidee_send_field("snowdz",snowdepth)
1355    END IF
1356
1357    CALL xios_orchidee_send_field("frac_bare",frac_bare)
1358
1359    CALL xios_orchidee_send_field("soilwet",soilwet)
1360    CALL xios_orchidee_send_field("delsoilmoist",delsoilmoist)
1361    CALL xios_orchidee_send_field("delswe",delswe)
1362    CALL xios_orchidee_send_field("delintercept",delintercept) 
1363
1364    IF (ok_freeze_cwrr) THEN
1365       CALL xios_orchidee_send_field("profil_froz_hydro",profil_froz_hydro)
1366       CALL xios_orchidee_send_field("temp_hydro",temp_hydro)
1367       CALL xios_orchidee_send_field("kk_moy",kk_moy)
1368       CALL xios_orchidee_send_field("profil_froz_hydro_ns", profil_froz_hydro_ns)
1369    END IF
1370   
1371
1372    IF ( .NOT. almaoutput ) THEN
1373       CALL histwrite_p(hist_id, 'frac_bare', kjit, frac_bare, kjpindex*nvm, indexveg)
1374
1375       DO jst=1,nstm
1376          ! var_name= "mc_1" ... "mc_3"
1377          WRITE (var_name,"('moistc_',i1)") jst
1378          CALL histwrite_p(hist_id, TRIM(var_name), kjit,mc(:,:,jst), kjpindex*nslm, indexlayer)
1379
1380          ! var_name= "kfactroot_1" ... "kfactroot_3"
1381          WRITE (var_name,"('kfactroot_',i1)") jst
1382          CALL histwrite_p(hist_id, TRIM(var_name), kjit, kfact_root(:,:,jst), kjpindex*nslm, indexlayer)
1383
1384          ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1385          WRITE (var_name,"('vegetsoil_',i1)") jst
1386          CALL histwrite_p(hist_id, TRIM(var_name), kjit,vegetmax_soil(:,:,jst), kjpindex*nvm, indexveg)
1387       ENDDO
1388       CALL histwrite_p(hist_id, 'precip_soil', kjit, precisol_ns, kjpindex*nstm, indexsoil)
1389       CALL histwrite_p(hist_id, 'evapnu_soil', kjit, ae_ns, kjpindex*nstm, indexsoil)
1390       CALL histwrite_p(hist_id, 'drainage_soil', kjit, dr_ns, kjpindex*nstm, indexsoil)
1391       CALL histwrite_p(hist_id, 'transpir_soil', kjit, tr_ns, kjpindex*nstm, indexsoil)
1392       CALL histwrite_p(hist_id, 'runoff_soil', kjit, ru_ns, kjpindex*nstm, indexsoil)
1393       CALL histwrite_p(hist_id, 'humtot_soil', kjit, tmc, kjpindex*nstm, indexsoil)
1394       ! mrso is a perfect duplicate of humtot
1395       CALL histwrite_p(hist_id, 'humtot', kjit, humtot, kjpindex, index)
1396       CALL histwrite_p(hist_id, 'mrso', kjit, humtot, kjpindex, index)
1397       CALL histwrite_p(hist_id, 'mrsos', kjit, humtot_top, kjpindex, index)
1398       njsc_tmp(:)=njsc(:)
1399       CALL histwrite_p(hist_id, 'soilindex', kjit, njsc_tmp, kjpindex, index)
1400       CALL histwrite_p(hist_id, 'humrel',   kjit, humrel,   kjpindex*nvm, indexveg)
1401       CALL histwrite_p(hist_id, 'vegstress',   kjit, vegstress, kjpindex*nvm, indexveg)
1402       ! CROP variable
1403       IF (ANY(ok_LAIdev)) CALL histwrite_p(hist_id, 'soil_deficit', kjit, soil_deficit, kjpindex*nvm, indexveg)
1404       CALL histwrite_p(hist_id, 'drainage', kjit, drainage, kjpindex, index)
1405       ! NB! According to histdef in intersurf, the variables 'runoff' and 'mrros' have different units
1406       CALL histwrite_p(hist_id, 'runoff', kjit, runoff, kjpindex, index)
1407       CALL histwrite_p(hist_id, 'mrros', kjit, runoff, kjpindex, index)
1408       histvar(:)=(runoff(:)+drainage(:))
1409       CALL histwrite_p(hist_id, 'mrro', kjit, histvar, kjpindex, index)
1410       CALL histwrite_p(hist_id, 'precisol', kjit, precisol, kjpindex*nvm, indexveg)
1411       CALL histwrite_p(hist_id, 'rain', kjit, precip_rain, kjpindex, index)
1412
1413       histvar(:)=(precip_rain(:)-SUM(precisol(:,:),dim=2))
1414       CALL histwrite_p(hist_id, 'prveg', kjit, histvar, kjpindex, index)
1415
1416       CALL histwrite_p(hist_id, 'snowf', kjit, precip_snow, kjpindex, index)
1417       CALL histwrite_p(hist_id, 'qsintmax', kjit, qsintmax, kjpindex*nvm, indexveg)
1418       CALL histwrite_p(hist_id, 'qsintveg', kjit, qsintveg, kjpindex*nvm, indexveg)
1419       CALL histwrite_p(hist_id, 'irrig_fin', kjit, irrig_fin, kjpindex*nvm, indexveg)
1420       CALL histwrite_p(hist_id, 'snowmelt',kjit,snowmelt,kjpindex,index)
1421       CALL histwrite_p(hist_id, 'shumdiag_perma',kjit,shumdiag_perma,kjpindex*nbdl,indexnbdl)
1422
1423!pss:+ ! write out wetland fraction and CTI parameters
1424       CALL histwrite_p(hist_id, 'fsat', kjit, fsat, kjpindex, index)
1425       CALL histwrite_p(hist_id, 'fwet', kjit, fwet, kjpindex, index)
1426       CALL histwrite_p(hist_id, 'fwt1', kjit, fwt1, kjpindex, index)
1427       CALL histwrite_p(hist_id, 'fwt2', kjit, fwt2, kjpindex, index)
1428       CALL histwrite_p(hist_id, 'fwt3', kjit, fwt3, kjpindex, index)
1429       CALL histwrite_p(hist_id, 'fwt4', kjit, fwt4, kjpindex, index)
1430       CALL histwrite_p(hist_id, 'ZMIN', kjit, ZMIN, kjpindex, index)
1431       CALL histwrite_p(hist_id, 'ZMAX', kjit, ZMAX, kjpindex, index)
1432       CALL histwrite_p(hist_id, 'ZMEAN', kjit, ZMEAN, kjpindex, index)
1433       !CALL histwrite_p(hist_id, 'NB_PIXE', kjit, NB_PIXE, kjpindex, index)
1434       CALL histwrite_p(hist_id, 'ZSTDT', kjit, ZSTDT, kjpindex, index)
1435       CALL histwrite_p(hist_id, 'ZSKEW', kjit, ZSKEW, kjpindex, index)
1436!       CALL histwrite_p(hist_id, 'dsg', kjit, dsg, kjpindex*nvm, indexveg)
1437!       CALL histwrite_p(hist_id, 'dsp', kjit, dsp, kjpindex*nvm, indexveg)
1438!       CALL histwrite_p(hist_id, 'ZWSAT', kjit, ZWSAT, kjpindex, index)
1439!       CALL histwrite_p(hist_id, 'ZWWILT', kjit, ZWWILT, kjpindex, index)
1440!       CALL histwrite_p(hist_id, 'ZWFC', kjit, ZWFC, kjpindex, index)
1441!       CALL histwrite_p(hist_id, 'RU', kjit, ruu_ch, kjpindex, index)
1442!       CALL histwrite_p(hist_id, 'mx_eau_var', kjit, mx_eau_var, kjpindex, index)
1443       CALL histwrite_p(hist_id, 'drunoff_tot', kjit, drunoff_tot, kjpindex, index)
1444!pss:-
1445
1446       IF ( river_routing .AND. do_floodplains ) THEN
1447          CALL histwrite_p(hist_id, 'floodout', kjit, floodout, kjpindex, index)
1448       ENDIF
1449       !
1450       IF ( hist2_id > 0 ) THEN
1451          DO jst=1,nstm
1452             ! var_name= "mc_1" ... "mc_3"
1453             WRITE (var_name,"('moistc_',i1)") jst
1454             CALL histwrite_p(hist2_id, TRIM(var_name), kjit,mc(:,:,jst), kjpindex*nslm, indexlayer)
1455
1456             ! var_name= "kfactroot_1" ... "kfactroot_3"
1457             WRITE (var_name,"('kfactroot_',i1)") jst
1458             CALL histwrite_p(hist2_id, TRIM(var_name), kjit, kfact_root(:,:,jst), kjpindex*nslm, indexlayer)
1459
1460             ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1461             WRITE (var_name,"('vegetsoil_',i1)") jst
1462             CALL histwrite_p(hist2_id, TRIM(var_name), kjit,vegetmax_soil(:,:,jst), kjpindex*nvm, indexveg)
1463          ENDDO
1464          CALL histwrite_p(hist2_id, 'evapnu_soil', kjit, ae_ns, kjpindex*nstm, indexsoil)
1465          CALL histwrite_p(hist2_id, 'drainage_soil', kjit, dr_ns, kjpindex*nstm, indexsoil)
1466          CALL histwrite_p(hist2_id, 'transpir_soil', kjit, tr_ns, kjpindex*nstm, indexsoil)
1467          CALL histwrite_p(hist2_id, 'runoff_soil', kjit, ru_ns, kjpindex*nstm, indexsoil)
1468          CALL histwrite_p(hist2_id, 'humtot_soil', kjit, tmc, kjpindex*nstm, indexsoil)
1469          ! mrso is a perfect duplicate of humtot
1470          CALL histwrite_p(hist2_id, 'humtot', kjit, humtot, kjpindex, index)
1471          CALL histwrite_p(hist2_id, 'mrso', kjit, humtot, kjpindex, index)
1472          CALL histwrite_p(hist2_id, 'mrsos', kjit, humtot_top, kjpindex, index)
1473          njsc_tmp(:)=njsc(:)
1474          CALL histwrite_p(hist2_id, 'soilindex', kjit, njsc_tmp, kjpindex, index)
1475          CALL histwrite_p(hist2_id, 'humrel',   kjit, humrel,   kjpindex*nvm, indexveg)
1476          CALL histwrite_p(hist2_id, 'drainage', kjit, drainage, kjpindex, index)
1477          ! NB! According to histdef in intersurf, the variables 'runoff' and 'mrros' have different units
1478          CALL histwrite_p(hist2_id, 'runoff', kjit, runoff, kjpindex, index)
1479          CALL histwrite_p(hist2_id, 'mrros', kjit, runoff, kjpindex, index)
1480          histvar(:)=(runoff(:)+drainage(:))
1481          CALL histwrite_p(hist2_id, 'mrro', kjit, histvar, kjpindex, index)
1482
1483          IF ( river_routing .AND. do_floodplains ) THEN
1484             CALL histwrite_p(hist2_id, 'floodout', kjit, floodout, kjpindex, index)
1485          ENDIF
1486          CALL histwrite_p(hist2_id, 'precisol', kjit, precisol, kjpindex*nvm, indexveg)
1487          CALL histwrite_p(hist2_id, 'rain', kjit, precip_rain, kjpindex, index)
1488          CALL histwrite_p(hist2_id, 'snowf', kjit, precip_snow, kjpindex, index)
1489          CALL histwrite_p(hist2_id, 'snowmelt',kjit,snowmelt,kjpindex,index)
1490          CALL histwrite_p(hist2_id, 'qsintmax', kjit, qsintmax, kjpindex*nvm, indexveg)
1491          CALL histwrite_p(hist2_id, 'qsintveg', kjit, qsintveg, kjpindex*nvm, indexveg)
1492          CALL histwrite_p(hist2_id, 'irrig_fin', kjit, irrig_fin, kjpindex*nvm, indexveg)
1493
1494          IF (check_waterbal) THEN
1495             CALL histwrite_p(hist2_id, 'TotWater', kjit, tot_water_end, kjpindex, index)
1496             CALL histwrite_p(hist2_id, 'TotWaterFlux', kjit, tot_flux, kjpindex, index)
1497          ENDIF
1498       ENDIF
1499    ELSE
1500       CALL histwrite_p(hist_id, 'Snowf', kjit, precip_snow, kjpindex, index)
1501       CALL histwrite_p(hist_id, 'Rainf', kjit, precip_rain, kjpindex, index)
1502       CALL histwrite_p(hist_id, 'Qs', kjit, runoff, kjpindex, index)
1503       CALL histwrite_p(hist_id, 'Qsb', kjit, drainage, kjpindex, index)
1504       CALL histwrite_p(hist_id, 'Qsm', kjit, snowmelt, kjpindex, index)
1505       CALL histwrite_p(hist_id, 'DelSoilMoist', kjit, delsoilmoist, kjpindex, index)
1506       CALL histwrite_p(hist_id, 'DelSWE', kjit, delswe, kjpindex, index)
1507       CALL histwrite_p(hist_id, 'DelIntercept', kjit, delintercept, kjpindex, index)
1508       !
1509       CALL histwrite_p(hist_id, 'SoilMoist', kjit, soilmoist, kjpindex*nslm, indexlayer)
1510       CALL histwrite_p(hist_id, 'SoilWet', kjit, soilwet, kjpindex, index)
1511       !
1512       CALL histwrite_p(hist_id, 'RootMoist', kjit, tot_watsoil_end, kjpindex, index)
1513       CALL histwrite_p(hist_id, 'SubSnow', kjit, vevapsno, kjpindex, index)
1514       !
1515       IF (.NOT. ok_explicitsnow) CALL histwrite_p(hist_id, 'SnowDepth', kjit, snowdepth, kjpindex, index)
1516       !
1517       IF ( hist2_id > 0 ) THEN
1518          CALL histwrite_p(hist2_id, 'Snowf', kjit, precip_snow, kjpindex, index)
1519          CALL histwrite_p(hist2_id, 'Rainf', kjit, precip_rain, kjpindex, index)
1520          CALL histwrite_p(hist2_id, 'Qs', kjit, runoff, kjpindex, index)
1521          CALL histwrite_p(hist2_id, 'Qsb', kjit, drainage, kjpindex, index)
1522          CALL histwrite_p(hist2_id, 'Qsm', kjit, snowmelt, kjpindex, index)
1523          CALL histwrite_p(hist2_id, 'DelSoilMoist', kjit, delsoilmoist, kjpindex, index)
1524          CALL histwrite_p(hist2_id, 'DelSWE', kjit, delswe, kjpindex, index)
1525          CALL histwrite_p(hist2_id, 'DelIntercept', kjit, delintercept, kjpindex, index)
1526          !
1527          CALL histwrite_p(hist2_id, 'SoilMoist', kjit, soilmoist, kjpindex*nslm, indexlayer)
1528          CALL histwrite_p(hist2_id, 'SoilWet', kjit, soilwet, kjpindex, index)
1529          !
1530          CALL histwrite_p(hist2_id, 'RootMoist', kjit, tot_watsoil_end, kjpindex, index)
1531          CALL histwrite_p(hist2_id, 'SubSnow', kjit, vevapsno, kjpindex, index)
1532          !
1533          IF (.NOT. ok_explicitsnow) CALL histwrite_p(hist2_id, 'SnowDepth', kjit, snowdepth, kjpindex, index)
1534       ENDIF
1535    ENDIF
1536
1537    IF (ok_freeze_cwrr) THEN
1538       CALL histwrite_p(hist_id, 'profil_froz_hydro', kjit,profil_froz_hydro , kjpindex*nslm, indexlayer)
1539       DO jst=1,nstm
1540          WRITE (var_name,"('profil_froz_hydro_',i1)") jst
1541          CALL histwrite_p(hist_id, TRIM(var_name), kjit, profil_froz_hydro_ns(:,:,jst), kjpindex*nslm, indexlayer)
1542       ENDDO
1543       CALL histwrite_p(hist_id, 'temp_hydro', kjit,temp_hydro , kjpindex*nslm, indexlayer)
1544       CALL histwrite_p(hist_id, 'kk_moy', kjit, kk_moy,kjpindex*nslm, indexlayer) ! averaged over soiltiles
1545    ENDIF
1546
1547    IF (first_hydrol_main) THEN
1548       first_hydrol_main=.FALSE.
1549    ENDIF
1550    IF (printlev>=3) WRITE (numout,*) ' hydrol_main Done '
1551
1552  END SUBROUTINE hydrol_main
1553
1554
1555!! ================================================================================================================================
1556!! SUBROUTINE   : hydrol_finalize
1557!!
1558!>\BRIEF         
1559!!
1560!! DESCRIPTION : This subroutine writes the module variables and variables calculated in hydrol to restart file
1561!!
1562!! MAIN OUTPUT VARIABLE(S) :
1563!!
1564!! REFERENCE(S) :
1565!!
1566!! FLOWCHART    : None
1567!! \n
1568!_ ================================================================================================================================
1569
1570  SUBROUTINE hydrol_finalize( kjit,           kjpindex, rest_id,  vegstress,  &
1571                              qsintveg,       humrel,                         &
1572                              snow,           snow_age, snow_nobio,           &
1573                              snow_nobio_age, snowrho,  snowtemp,             &
1574                              snowdz,         snowheat,                       &
1575                              fwet_out,                                       &
1576                              snowgrain, drysoil_frac, evap_bare_lim)
1577!                              snowcap,        snowgrain, drysoil_frac, evap_bare_lim, evap_bare_lim_pft)
1578
1579    !! 0. Variable and parameter declaration
1580    !! 0.1 Input variables
1581    INTEGER(i_std), INTENT(in)                           :: kjit           !! Time step number
1582    INTEGER(i_std), INTENT(in)                           :: kjpindex       !! Domain size
1583    INTEGER(i_std),INTENT (in)                           :: rest_id        !! Restart file identifier
1584    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: vegstress      !! Veg. moisture stress (only for vegetation growth)
1585    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: qsintveg       !! Water on vegetation due to interception
1586    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: humrel
1587    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow           !! Snow mass [Kg/m^2]
1588    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow_age       !! Snow age
1589    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio     !! Water balance on ice, lakes, .. [Kg/m^2]
1590    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio_age !! Snow age on ice, lakes, ...
1591    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowrho        !! Snow density
1592    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowtemp       !! Snow temperature
1593    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowdz         !! Snow layer thickness
1594    REAL(r_std), DIMENSION (kjpindex,nsnow), INTENT(in)  :: snowheat       !! Snow heat content
1595    REAL(r_std),DIMENSION (kjpindex),INTENT(in)          :: drysoil_frac   !! function of litter wetness
1596    REAL(r_std),DIMENSION (kjpindex),INTENT(in)          :: evap_bare_lim
1597!    REAL(r_std),DIMENSION (kjpindex,nvm),INTENT(in)       :: evap_bare_lim_pft
1598
1599    REAL(r_std),DIMENSION (kjpindex), INTENT (out)       :: fwet_out       !! output wetland fraction to change energy or runoff ???!!!
1600    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT(in)   :: snowgrain      !! Snow grain size
1601
1602    !! 0.4 Local variables
1603    INTEGER(i_std)                                       :: jst, jsl
1604   
1605!_ ================================================================================================================================
1606
1607
1608    IF (printlev>=3) WRITE (numout,*) ' we have to complete restart file with HYDROLOGIC variables '
1609
1610    CALL restput_p(rest_id, 'moistc', nbp_glo,  nslm, nstm, kjit, mc, 'scatter',  nbp_glo, index_g)
1611    CALL restput_p(rest_id, 'moistcl', nbp_glo,  nslm, nstm, kjit, mcl, 'scatter',  nbp_glo, index_g)
1612     
1613    CALL restput_p(rest_id, 'us', nbp_glo,nvm, nstm, nslm, kjit,us,'scatter',nbp_glo,index_g)
1614   
1615    CALL restput_p(rest_id, 'free_drain_coef', nbp_glo,   nstm, 1, kjit,  free_drain_coef, 'scatter',  nbp_glo, index_g)
1616    CALL restput_p(rest_id, 'zwt_force', nbp_glo,   nstm, 1, kjit,  zwt_force, 'scatter',  nbp_glo, index_g)
1617    CALL restput_p(rest_id, 'water2infilt', nbp_glo,   nstm, 1, kjit,  water2infilt, 'scatter',  nbp_glo, index_g)
1618    CALL restput_p(rest_id, 'ae_ns', nbp_glo,   nstm, 1, kjit,  ae_ns, 'scatter',  nbp_glo, index_g)
1619    CALL restput_p(rest_id, 'vegstress', nbp_glo,   nvm, 1, kjit,  vegstress, 'scatter',  nbp_glo, index_g)
1620    CALL restput_p(rest_id, 'snow', nbp_glo,   1, 1, kjit,  snow, 'scatter',  nbp_glo, index_g)
1621    CALL restput_p(rest_id, 'snow_age', nbp_glo,   1, 1, kjit,  snow_age, 'scatter',  nbp_glo, index_g)
1622    CALL restput_p(rest_id, 'snow_nobio', nbp_glo,   nnobio, 1, kjit,  snow_nobio, 'scatter', nbp_glo, index_g)
1623    CALL restput_p(rest_id, 'snow_nobio_age', nbp_glo,   nnobio, 1, kjit,  snow_nobio_age, 'scatter', nbp_glo, index_g)
1624    CALL restput_p(rest_id, 'qsintveg', nbp_glo, nvm, 1, kjit,  qsintveg, 'scatter',  nbp_glo, index_g)
1625    CALL restput_p(rest_id, 'evap_bare_lim_ns', nbp_glo, nstm, 1, kjit,  evap_bare_lim_ns, 'scatter',  nbp_glo, index_g)
1626    CALL restput_p(rest_id, 'evap_bare_lim', nbp_glo, 1, 1, kjit,  evap_bare_lim, 'scatter',  nbp_glo, index_g)
1627    CALL restput_p(rest_id, 'resdist', nbp_glo, nstm, 1, kjit,  resdist, 'scatter',  nbp_glo, index_g) 
1628    CALL restput_p(rest_id, 'vegtot_old', nbp_glo, 1, 1, kjit,  vegtot_old, 'scatter',  nbp_glo, index_g)           
1629    CALL restput_p(rest_id, 'drysoil_frac', nbp_glo,   1, 1, kjit, drysoil_frac, 'scatter', nbp_glo, index_g)
1630    CALL restput_p(rest_id, 'humrel', nbp_glo,   nvm, 1, kjit,  humrel, 'scatter',  nbp_glo, index_g)
1631    IF (use_refSOC_hydrol)  CALL restput_p (rest_id, 'refSOC_1d', nbp_glo, 1, 1, kjit, refSOC_1d, 'scatter', nbp_glo, index_g)
1632
1633    !
1634    !pss:+
1635    !
1636    var_name= 'fwet_out'
1637    CALL restput_p(rest_id, var_name, nbp_glo,   1, 1, kjit,  fwet_out, 'scatter',  nbp_glo, index_g)
1638    !
1639    !pss:-
1640    !
1641    IF ( check_waterbal ) THEN
1642      CALL restput_p(rest_id, 'tot_water_beg', nbp_glo,   1, 1, kjit,  tot_water_end, 'scatter', nbp_glo, index_g)
1643!??      CALL restput_p(rest_id, 'tot_water_end', nbp_glo,   1, 1, kjit,  tot_water_end, 'scatter', nbp_glo, index_g)
1644    ENDIF
1645
1646    CALL restput_p(rest_id, 'tot_watveg_beg', nbp_glo,  1, 1, kjit,  tot_watveg_beg, 'scatter',  nbp_glo, index_g)
1647    CALL restput_p(rest_id, 'tot_watsoil_beg', nbp_glo, 1, 1, kjit,  tot_watsoil_beg, 'scatter',  nbp_glo, index_g)
1648    CALL restput_p(rest_id, 'snow_beg', nbp_glo,        1, 1, kjit,  snow_beg, 'scatter',  nbp_glo, index_g)
1649   
1650    ! Write variables for explictsnow module to restart file
1651    IF (ok_explicitsnow) THEN
1652
1653      CALL explicitsnow_finalize ( kjit,     kjpindex, rest_id,    snowrho,   &
1654                                    snowtemp, snowdz,   snowheat,   snowgrain)
1655    END IF
1656
1657  END SUBROUTINE hydrol_finalize
1658
1659
1660!! ================================================================================================================================
1661!! SUBROUTINE   : hydrol_init
1662!!
1663!>\BRIEF        Initializations and memory allocation   
1664!!
1665!! DESCRIPTION  :
1666!! - 1 Some initializations
1667!! - 2 make dynamic allocation with good dimension
1668!! - 2.1 array allocation for soil textur
1669!! - 2.2 Soil texture choice
1670!! - 3 Other array allocation
1671!! - 4 Open restart input file and read data for HYDROLOGIC process
1672!! - 5 get restart values if none were found in the restart file
1673!! - 6 Vegetation array     
1674!! - 7 set humrelv from us
1675!!
1676!! RECENT CHANGE(S) : None
1677!!
1678!! MAIN OUTPUT VARIABLE(S) :
1679!!
1680!! REFERENCE(S) :
1681!!
1682!! FLOWCHART    : None
1683!! \n
1684!_ ================================================================================================================================
1685!!_ hydrol_init
1686
1687  SUBROUTINE hydrol_init(kjit, kjpindex, index, rest_id, veget_max, soiltile, &
1688         humrel, vegstress, snow,       snow_age,   snow_nobio, snow_nobio_age, qsintveg, &
1689         snowdz, snowgrain, snowrho,    snowtemp,   snowheat, &
1690         drysoil_frac, evap_bare_lim,  &
1691!         snowflx,snowcap,   cgrnd_snow, dgrnd_snow, drysoil_frac, evap_bare_lim, evap_bare_lim_pft, &
1692         fwet_out) 
1693
1694    !! 0. Variable and parameter declaration
1695
1696    !! 0.1 Input variables
1697
1698    INTEGER(i_std), INTENT (in)                         :: kjit               !! Time step number
1699    INTEGER(i_std), INTENT (in)                         :: kjpindex           !! Domain size
1700    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: index              !! Indeces of the points on the map
1701    INTEGER(i_std), INTENT (in)                         :: rest_id            !! _Restart_ file identifier
1702    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max          !! Carte de vegetation max
1703    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT (in)  :: soiltile           !! Fraction of each soil tile within vegtot (0-1, unitless)
1704
1705    !! 0.2 Output variables
1706
1707    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: humrel             !! Stress hydrique, relative humidity
1708    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: vegstress          !! Veg. moisture stress (only for vegetation growth)
1709    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: snow               !! Snow mass [Kg/m^2]
1710    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: snow_age           !! Snow age
1711    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out) :: snow_nobio       !! Snow on ice, lakes, ...
1712    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (out) :: snow_nobio_age   !! Snow age on ice, lakes, ...
1713    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)    :: qsintveg         !! Water on vegetation due to interception
1714    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowdz           !! Snow depth
1715    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowgrain        !! Snow grain size
1716    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowheat         !! Snow heat content
1717    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowtemp         !! Snow temperature
1718    REAL(r_std),DIMENSION (kjpindex,nsnow),INTENT(out)    :: snowrho          !! Snow density
1719!pss:+
1720    REAL(r_std),DIMENSION (kjpindex), INTENT (out)  :: fwet_out            !! output wetland fraction to change energy or runoff ???!!!
1721!pss:-
1722    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: drysoil_frac     !! function of litter wetness
1723    REAL(r_std),DIMENSION (kjpindex),INTENT(out)          :: evap_bare_lim
1724!    REAL(r_std),DIMENSION (kjpindex,nvm),INTENT(out)          ::evap_bare_lim_pft
1725
1726    !! 0.3 Modified variable
1727
1728    !! 0.4 Local variables
1729
1730    INTEGER(i_std)                                     :: ier                   !! Error code
1731    INTEGER(i_std)                                     :: ji                    !! Index of land grid cells (1)
1732    INTEGER(i_std)                                     :: jv                    !! Index of PFTs (1)
1733    INTEGER(i_std)                                     :: jst                   !! Index of soil tiles (1)
1734    INTEGER(i_std)                                     :: jsl                   !! Index of soil layers (1)
1735    INTEGER(i_std)                                     :: jsc                   !! Index of soil texture (1)
1736    INTEGER(i_std), PARAMETER                          :: error_level = 3       !! Error level for consistency check
1737                                                                                !! Switch to 2 tu turn fatal errors into warnings 
1738    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: free_drain_max        !! Temporary var for initialization of free_drain_coef
1739    REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: zwt_default           !! Temporary variable for initialization of zwt_force
1740    LOGICAL                                            :: zforce                !! To test if we force the WT in any of the soiltiles
1741
1742!_ ================================================================================================================================
1743
1744    !! 1 Some initializations
1745    !
1746    !Config Key   = DO_PONDS
1747    !Config Desc  = Should we include ponds
1748    !Config Def   = n
1749    !Config If    = HYDROL_CWRR
1750    !Config Help  = This parameters allows the user to ask the model
1751    !Config         to take into account the ponds and return
1752    !Config         the water into the soil moisture. If this is
1753    !Config         activated, then there is no reinfiltration
1754    !Config         computed inside the hydrol module.
1755    !Config Units = [FLAG]
1756    !
1757    doponds = .FALSE.
1758    CALL getin_p('DO_PONDS', doponds)
1759
1760    !Config Key   = FROZ_FRAC_CORR
1761    !Config Desc  = Coefficient for the frozen fraction correction
1762    !Config Def   = 1.0
1763    !Config If    = HYDROL_CWRR and OK_FREEZE
1764    !Config Help  =
1765    !Config Units = [-]
1766    froz_frac_corr = 1.0
1767    CALL getin_p("FROZ_FRAC_CORR", froz_frac_corr)
1768
1769    !Config Key   = MAX_FROZ_HYDRO
1770    !Config Desc  = Coefficient for the frozen fraction correction
1771    !Config Def   = 1.0
1772    !Config If    = HYDROL_CWRR and OK_FREEZE
1773    !Config Help  =
1774    !Config Units = [-]
1775    max_froz_hydro = 1.0
1776    CALL getin_p("MAX_FROZ_HYDRO", max_froz_hydro)
1777
1778    !Config Key   = SMTOT_CORR
1779    !Config Desc  = Coefficient for the frozen fraction correction
1780    !Config Def   = 2.0
1781    !Config If    = HYDROL_CWRR and OK_FREEZE
1782    !Config Help  =
1783    !Config Units = [-]
1784    smtot_corr = 2.0
1785    CALL getin_p("SMTOT_CORR", smtot_corr)
1786
1787    !Config Key   = DO_RSOIL
1788    !Config Desc  = Should we reduce soil evaporation with a soil resistance
1789    !Config Def   = n
1790    !Config If    = HYDROL_CWRR
1791    !Config Help  = This parameters allows the user to ask the model
1792    !Config         to calculate a soil resistance to reduce the soil evaporation
1793    !Config Units = [FLAG]
1794    !
1795    do_rsoil = .FALSE.
1796    CALL getin_p('DO_RSOIL', do_rsoil) 
1797
1798    !Config Key   = OK_DYNROOT
1799    !Config Desc  = Calculate dynamic root profile to optimize soil moisture usage 
1800    !Config Def   = y
1801    !Config If    = HYDROL_CWRR
1802    !Config Help  =
1803    !Config Units = [FLAG]
1804    ok_dynroot = .TRUE.
1805    CALL getin_p('OK_DYNROOT',ok_dynroot)
1806
1807    !! 2 make dynamic allocation with good dimension
1808
1809    !! 2.1 array allocation for soil texture
1810
1811    ALLOCATE (nvan(nscm),stat=ier)
1812    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nvan','','')
1813
1814    ALLOCATE (avan(nscm),stat=ier)
1815    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable avan','','')
1816
1817    ALLOCATE (mcr(nscm),stat=ier)
1818    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcr','','')
1819
1820    ALLOCATE (mcs_mineral(nscm),stat=ier)
1821    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcs_mineral','','')
1822
1823    ALLOCATE (ks(nscm),stat=ier)
1824    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ks','','')
1825
1826    ALLOCATE (pcent(nscm),stat=ier)
1827    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable pcent','','')
1828
1829    ALLOCATE (mcf_mineral(nscm),stat=ier)
1830    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcf_mineral','','')
1831
1832    ALLOCATE (mcw_mineral(nscm),stat=ier)
1833    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcw_mineral','','')
1834   
1835    ALLOCATE (mcs(kjpindex),stat=ier)
1836    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcs','','')
1837   
1838    ALLOCATE (mcw(kjpindex),stat=ier)
1839    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcw','','')
1840   
1841    ALLOCATE (mcf(kjpindex),stat=ier)
1842    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcf','','')
1843   
1844    ALLOCATE (VG_m(nscm),stat=ier)
1845    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable VG_m','','')
1846
1847    ALLOCATE (VG_n(nscm),stat=ier)
1848    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable VG_n','','')
1849
1850    ALLOCATE (VG_alpha(nscm),stat=ier)
1851    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable VG_alpha','','')
1852
1853    ALLOCATE (VG_psi_fc(nscm),stat=ier)
1854    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable VG_psi_fc','','')
1855
1856    ALLOCATE (VG_psi_wp(nscm),stat=ier)
1857    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable VG_psi_wp','','')
1858
1859    ALLOCATE (mc_awet(nscm),stat=ier)
1860    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_awet','','')
1861
1862    ALLOCATE (mc_adry(nscm),stat=ier)
1863    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_adry','','')
1864       
1865    !!__2.2 Soil texture choose
1866
1867    SELECTCASE (nscm)
1868    CASE (3)
1869             
1870       nvan(:) = nvan_fao(:)       
1871       avan(:) = avan_fao(:)
1872       mcr(:) = mcr_fao(:)
1873       mcs_mineral(:) = mcs_fao(:)
1874       ks(:) = ks_fao(:)
1875       pcent(:) = pcent_fao(:)
1876       mcf_mineral(:) = mcf_fao(:)
1877       mcw_mineral(:) = mcw_fao(:)
1878       mc_awet(:) = mc_awet_fao(:)
1879       mc_adry(:) = mc_adry_fao(:)
1880    CASE (12)
1881       
1882       nvan(:) = nvan_usda(:)
1883       avan(:) = avan_usda(:)
1884       mcr(:) = mcr_usda(:)
1885       mcs_mineral(:) = mcs_usda(:)
1886       ks(:) = ks_usda(:)
1887       pcent(:) = pcent_usda(:)
1888       mcf_mineral(:) = mcf_usda(:)
1889       mcw_mineral(:) = mcw_usda(:)
1890       mc_awet(:) = mc_awet_usda(:)
1891       mc_adry(:) = mc_adry_usda(:)
1892       VG_m(:)=VG_m_usda(:)
1893       VG_n(:)=VG_n_usda(:)
1894       VG_alpha(:)=VG_alpha_usda(:)
1895       VG_psi_fc(:)=VG_psi_fc_usda(:)
1896       VG_psi_wp(:)=VG_psi_wp_usda(:)
1897       
1898    CASE DEFAULT
1899       WRITE (numout,*) 'Unsupported soil type classification. Choose between zobler and usda according to the map'
1900       CALL ipslerr_p(3,'hydrol_init','Unsupported soil type classification. ',&
1901            'Choose between zobler and usda according to the map','')
1902    ENDSELECT
1903
1904    !! 2.3 Read in the run.def the parameters values defined by the user
1905
1906    !Config Key   = CWRR_N_VANGENUCHTEN
1907    !Config Desc  = Van genuchten coefficient n
1908    !Config If    = HYDROL_CWRR
1909    !Config Def   = 1.89, 1.56, 1.31
1910    !Config Help  = This parameter will be constant over the entire
1911    !Config         simulated domain, thus independent from soil
1912    !Config         texture.   
1913    !Config Units = [-]
1914    CALL getin_p("CWRR_N_VANGENUCHTEN",nvan)
1915
1916    !! Check parameter value (correct range)
1917    IF ( ANY(nvan(:) <= zero) ) THEN
1918       CALL ipslerr_p(error_level, "hydrol_init.", &
1919            &     "Wrong parameter value for CWRR_N_VANGENUCHTEN.", &
1920            &     "This parameter should be positive. ", &
1921            &     "Please, check parameter value in run.def. ")
1922    END IF
1923
1924
1925    !Config Key   = CWRR_A_VANGENUCHTEN
1926    !Config Desc  = Van genuchten coefficient a
1927    !Config If    = HYDROL_CWRR
1928    !Config Def   = 0.0075, 0.0036, 0.0019
1929    !Config Help  = This parameter will be constant over the entire
1930    !Config         simulated domain, thus independent from soil
1931    !Config         texture.   
1932    !Config Units = [1/mm] 
1933    CALL getin_p("CWRR_A_VANGENUCHTEN",avan)
1934
1935    !! Check parameter value (correct range)
1936    IF ( ANY(avan(:) <= zero) ) THEN
1937       CALL ipslerr_p(error_level, "hydrol_init.", &
1938            &     "Wrong parameter value for CWRR_A_VANGENUCHTEN.", &
1939            &     "This parameter should be positive. ", &
1940            &     "Please, check parameter value in run.def. ")
1941    END IF
1942
1943
1944    !Config Key   = VWC_RESIDUAL
1945    !Config Desc  = Residual soil water content
1946    !Config If    = HYDROL_CWRR
1947    !Config Def   = 0.065, 0.078, 0.095
1948    !Config Help  = This parameter will be constant over the entire
1949    !Config         simulated domain, thus independent from soil
1950    !Config         texture.   
1951    !Config Units = [m3/m3] 
1952    CALL getin_p("VWC_RESIDUAL",mcr)
1953
1954    !! Check parameter value (correct range)
1955    IF ( ANY(mcr(:) < zero) .OR. ANY(mcr(:) > 1.)  ) THEN
1956       CALL ipslerr_p(error_level, "hydrol_init.", &
1957            &     "Wrong parameter value for VWC_RESIDUAL.", &
1958            &     "This parameter is ranged between 0 and 1. ", &
1959            &     "Please, check parameter value in run.def. ")
1960    END IF
1961
1962   
1963    !Config Key   = VWC_SAT
1964    !Config Desc  = Saturated soil water content
1965    !Config If    = HYDROL_CWRR
1966    !Config Def   = 0.41, 0.43, 0.41
1967    !Config Help  = This parameter will be constant over the entire
1968    !Config         simulated domain, thus independent from soil
1969    !Config         texture.   
1970    !Config Units = [m3/m3] 
1971    CALL getin_p("VWC_SAT",mcs_mineral)
1972
1973    !! Check parameter value (correct range)
1974    IF ( ANY(mcs_mineral(:) < zero) .OR. ANY(mcs_mineral(:) > 1.) .OR. ANY(mcs_mineral(:) <= mcr(:)) ) THEN
1975       CALL ipslerr_p(error_level, "hydrol_init.", &
1976            &     "Wrong parameter value for VWC_SAT.", &
1977            &     "This parameter should be greater than VWC_RESIDUAL and less than 1. ", &
1978            &     "Please, check parameter value in run.def. ")
1979    END IF
1980
1981
1982    !Config Key   = CWRR_KS
1983    !Config Desc  = Hydraulic conductivity Saturation
1984    !Config If    = HYDROL_CWRR
1985    !Config Def   = 1060.8, 249.6, 62.4
1986    !Config Help  = This parameter will be constant over the entire
1987    !Config         simulated domain, thus independent from soil
1988    !Config         texture.   
1989    !Config Units = [mm/d]   
1990    CALL getin_p("CWRR_KS",ks)
1991
1992    !! Check parameter value (correct range)
1993    IF ( ANY(ks(:) <= zero) ) THEN
1994       CALL ipslerr_p(error_level, "hydrol_init.", &
1995            &     "Wrong parameter value for CWRR_KS.", &
1996            &     "This parameter should be positive. ", &
1997            &     "Please, check parameter value in run.def. ")
1998    END IF
1999
2000
2001    !Config Key   = WETNESS_TRANSPIR_MAX
2002    !Config Desc  = Soil moisture above which transpir is max
2003    !Config If    = HYDROL_CWRR
2004    !Config Def   = 0.5, 0.5, 0.5
2005    !Config Help  = This parameter is independent from soil texture for
2006    !Config         the time being.
2007    !Config Units = [-]   
2008    CALL getin_p("WETNESS_TRANSPIR_MAX",pcent)
2009
2010    !! Check parameter value (correct range)
2011    IF ( ANY(pcent(:) <= zero) .OR. ANY(pcent(:) > 1.) ) THEN
2012       CALL ipslerr_p(error_level, "hydrol_init.", &
2013            &     "Wrong parameter value for WETNESS_TRANSPIR_MAX.", &
2014            &     "This parameter should be positive and less or equals than 1. ", &
2015            &     "Please, check parameter value in run.def. ")
2016    END IF
2017
2018
2019    !Config Key   = VWC_FC
2020    !Config Desc  = Volumetric water content field capacity
2021    !Config If    = HYDROL_CWRR
2022    !Config Def   = 0.32, 0.32, 0.32
2023    !Config Help  = This parameter is independent from soil texture for
2024    !Config         the time being.
2025    !Config Units = [m3/m3]   
2026    CALL getin_p("VWC_FC",mcf_mineral)
2027
2028    !! Check parameter value (correct range)
2029    IF ( ANY(mcf_mineral(:) > mcs_mineral(:)) ) THEN
2030       CALL ipslerr_p(error_level, "hydrol_init.", &
2031            &     "Wrong parameter value for VWC_FC.", &
2032            &     "This parameter should be less than VWC_SAT. ", &
2033            &     "Please, check parameter value in run.def. ")
2034    END IF
2035
2036
2037    !Config Key   = VWC_WP
2038    !Config Desc  = Volumetric water content Wilting pt
2039    !Config If    = HYDROL_CWRR
2040    !Config Def   = 0.10, 0.10, 0.10
2041    !Config Help  = This parameter is independent from soil texture for
2042    !Config         the time being.
2043    !Config Units = [m3/m3]   
2044    CALL getin_p("VWC_WP",mcw_mineral)
2045
2046    !! Check parameter value (correct range)
2047    IF ( ANY(mcw_mineral(:) > mcf_mineral(:)) .OR. ANY(mcw_mineral(:) < mcr(:)) ) THEN
2048       CALL ipslerr_p(error_level, "hydrol_init.", &
2049            &     "Wrong parameter value for VWC_WP.", &
2050            &     "This parameter should be greater or equal than VWC_RESIDUAL and less or equal than VWC_SAT.", &
2051            &     "Please, check parameter value in run.def. ")
2052    END IF
2053
2054
2055    !Config Key   = VWC_MIN_FOR_WET_ALB
2056    !Config Desc  = Vol. wat. cont. above which albedo is cst
2057    !Config If    = HYDROL_CWRR
2058    !Config Def   = 0.25, 0.25, 0.25
2059    !Config Help  = This parameter is independent from soil texture for
2060    !Config         the time being.
2061    !Config Units = [m3/m3] 
2062    CALL getin_p("VWC_MIN_FOR_WET_ALB",mc_awet)
2063
2064    !! Check parameter value (correct range)
2065    IF ( ANY(mc_awet(:) < 0) ) THEN
2066       CALL ipslerr_p(error_level, "hydrol_init.", &
2067            &     "Wrong parameter value for VWC_MIN_FOR_WET_ALB.", &
2068            &     "This parameter should be positive. ", &
2069            &     "Please, check parameter value in run.def. ")
2070    END IF
2071
2072
2073    !Config Key   = VWC_MAX_FOR_DRY_ALB
2074    !Config Desc  = Vol. wat. cont. below which albedo is cst
2075    !Config If    = HYDROL_CWRR
2076    !Config Def   = 0.1, 0.1, 0.1
2077    !Config Help  = This parameter is independent from soil texture for
2078    !Config         the time being.
2079    !Config Units = [m3/m3]   
2080    CALL getin_p("VWC_MAX_FOR_DRY_ALB",mc_adry)
2081
2082    !! Check parameter value (correct range)
2083    IF ( ANY(mc_adry(:) < 0) .OR. ANY(mc_adry(:) > mc_awet(:)) ) THEN
2084       CALL ipslerr_p(error_level, "hydrol_init.", &
2085            &     "Wrong parameter value for VWC_MAX_FOR_DRY_ALB.", &
2086            &     "This parameter should be positive and not greater than VWC_MIN_FOR_WET_ALB.", &
2087            &     "Please, check parameter value in run.def. ")
2088    END IF
2089
2090
2091    !! 3 Other array allocation
2092
2093
2094    ALLOCATE (mask_veget(kjpindex,nvm),stat=ier)
2095    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_veget','','')
2096
2097    ALLOCATE (irrig_fin(kjpindex,nvm),stat=ier)
2098    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable irrig_fin','','')
2099
2100    ALLOCATE (mask_soiltile(kjpindex,nstm),stat=ier)
2101    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mask_soiltile','','')
2102
2103    ALLOCATE (humrelv(kjpindex,nvm,nstm),stat=ier)
2104    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable humrelv','','')
2105
2106    ALLOCATE (vegstressv(kjpindex,nvm,nstm),stat=ier) 
2107    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegstressv','','')
2108
2109    ALLOCATE (us(kjpindex,nvm,nstm,nslm),stat=ier) 
2110    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable us','','')
2111
2112    ALLOCATE (precisol(kjpindex,nvm),stat=ier) 
2113    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable precisol','','')
2114
2115    ALLOCATE (precisol_ns(kjpindex,nstm),stat=ier) 
2116    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable precisol_nc','','')
2117
2118    ALLOCATE (free_drain_coef(kjpindex,nstm),stat=ier) 
2119    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable free_drain_coef','','')
2120
2121    ALLOCATE (zwt_force(kjpindex,nstm),stat=ier) 
2122    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zwt_force','','')
2123
2124    ALLOCATE (frac_bare_ns(kjpindex,nstm),stat=ier) 
2125    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable frac_bare_ns','','')
2126
2127    ALLOCATE (water2infilt(kjpindex,nstm),stat=ier)
2128    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable water2infilt','','')
2129
2130    ALLOCATE (ae_ns(kjpindex,nstm),stat=ier) 
2131    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ae_ns','','')
2132
2133    ALLOCATE (evap_bare_lim_ns(kjpindex,nstm),stat=ier) 
2134    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable evap_bare_lim_ns','','')
2135
2136    ALLOCATE (rootsink(kjpindex,nslm,nstm),stat=ier) 
2137    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable rootsink','','')
2138
2139    ALLOCATE (subsnowveg(kjpindex),stat=ier) 
2140    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsnowveg','','')
2141
2142    ALLOCATE (subsnownobio(kjpindex,nnobio),stat=ier) 
2143    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsnownobio','','')
2144
2145    ALLOCATE (snowmelt(kjpindex),stat=ier)
2146    IF (ier.NE.0) THEN
2147        WRITE (numout,*) ' error in snowmelt allocation. We stop. We need kjpindex words = ',kjpindex
2148        STOP 'hydrol_init'
2149    END IF
2150
2151    ALLOCATE (icemelt(kjpindex),stat=ier) 
2152    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable icemelt','','')
2153
2154    ALLOCATE (subsinksoil(kjpindex),stat=ier) 
2155    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable subsinksoil','','')
2156
2157    ALLOCATE (mx_eau_var(kjpindex),stat=ier)
2158    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mx_eau_var','','')
2159
2160    ALLOCATE (vegtot(kjpindex),stat=ier) 
2161    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegtot','','')
2162
2163    ALLOCATE (vegtot_old(kjpindex),stat=ier) 
2164    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegtot_old','','')
2165
2166    ALLOCATE (resdist(kjpindex,nstm),stat=ier)
2167    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable resdist','','')
2168
2169    ALLOCATE (humtot(kjpindex),stat=ier)
2170    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable humtot','','')
2171
2172    ALLOCATE (resolv(kjpindex),stat=ier) 
2173    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable resolv','','')
2174
2175    ALLOCATE (k(kjpindex,nslm),stat=ier) 
2176    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable k','','')
2177
2178    IF (ok_freeze_cwrr) THEN
2179       ALLOCATE (kk_moy(kjpindex,nslm),stat=ier) 
2180       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kk_moy','','')
2181       kk_moy(:,:) = 276.48
2182
2183       ALLOCATE (kk(kjpindex,nslm,nstm),stat=ier) 
2184       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kk','','')
2185       kk(:,:,:) = 276.48
2186    ENDIF
2187
2188    ALLOCATE (a(kjpindex,nslm),stat=ier) 
2189    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable a','','')
2190
2191    ALLOCATE (b(kjpindex,nslm),stat=ier)
2192    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable b','','')
2193
2194    ALLOCATE (d(kjpindex,nslm),stat=ier)
2195    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable d','','')
2196
2197    ALLOCATE (e(kjpindex,nslm),stat=ier) 
2198    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable e','','')
2199
2200    ALLOCATE (f(kjpindex,nslm),stat=ier) 
2201    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable f','','')
2202
2203    ALLOCATE (g1(kjpindex,nslm),stat=ier) 
2204    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable g1','','')
2205
2206    ALLOCATE (ep(kjpindex,nslm),stat=ier)
2207    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ep','','')
2208
2209    ALLOCATE (fp(kjpindex,nslm),stat=ier)
2210    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fp','','')
2211
2212    ALLOCATE (gp(kjpindex,nslm),stat=ier)
2213    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable gp','','')
2214
2215    ALLOCATE (rhs(kjpindex,nslm),stat=ier)
2216    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable rhs','','')
2217
2218    ALLOCATE (srhs(kjpindex,nslm),stat=ier)
2219    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable srhs','','')
2220
2221    ALLOCATE (tmc(kjpindex,nstm),stat=ier)
2222    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc','','')
2223
2224    ALLOCATE (tmcs(kjpindex,nstm),stat=ier)
2225    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcs','','')
2226
2227    ALLOCATE (tmcr(kjpindex,nstm),stat=ier)
2228    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmcr','','')
2229
2230    ALLOCATE (tmc_litter(kjpindex,nstm),stat=ier)
2231    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter','','')
2232!gmjc top 5 layer mc for grazing
2233    ALLOCATE (tmc_trampling(kjpindex,nstm),stat=ier)
2234    IF (ier.NE.0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_trampling','','')
2235!end gmjc
2236    ALLOCATE (tmc_litt_mea(kjpindex),stat=ier)
2237    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_mea','','')
2238
2239    ALLOCATE (tmc_litter_res(kjpindex,nstm),stat=ier)
2240    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_res','','')
2241
2242    ALLOCATE (tmc_litter_wilt(kjpindex,nstm),stat=ier)
2243    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_wilt','','')
2244
2245    ALLOCATE (tmc_litter_field(kjpindex,nstm),stat=ier)
2246    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_field','','')
2247
2248    ALLOCATE (tmc_litter_sat(kjpindex,nstm),stat=ier)
2249    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_sat','','')
2250
2251    ALLOCATE (tmc_litter_awet(kjpindex,nstm),stat=ier)
2252    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_awet','','')
2253
2254    ALLOCATE (tmc_litter_adry(kjpindex,nstm),stat=ier)
2255    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litter_adry','','')
2256
2257    ALLOCATE (tmc_litt_wet_mea(kjpindex),stat=ier)
2258    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_wet_mea','','')
2259
2260    ALLOCATE (tmc_litt_dry_mea(kjpindex),stat=ier)
2261    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmc_litt_dry_mea','','')
2262
2263    ALLOCATE (v1(kjpindex,nstm),stat=ier)
2264    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable v1','','')
2265
2266    ALLOCATE (ru_ns(kjpindex,nstm),stat=ier)
2267    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ru_ns','','')
2268    ru_ns(:,:) = zero
2269
2270    ALLOCATE (dr_ns(kjpindex,nstm),stat=ier)
2271    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dr_ns','','')
2272    dr_ns(:,:) = zero
2273
2274    ALLOCATE (tr_ns(kjpindex,nstm),stat=ier)
2275    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tr_ns','','')
2276
2277    ALLOCATE (vegetmax_soil(kjpindex,nvm,nstm),stat=ier)
2278    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable vegetmax_soil','','')
2279
2280    ALLOCATE (mc(kjpindex,nslm,nstm),stat=ier)
2281    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc','','')
2282   
2283    ALLOCATE (frac_hydro_diag(nslm, nbdl),stat=ier)
2284    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable frac_hydro_diag','','')
2285
2286    ALLOCATE (soilmoist(kjpindex,nslm),stat=ier)
2287    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soilmoist','','')
2288
2289    ALLOCATE (soil_wet(kjpindex,nslm,nstm),stat=ier)
2290    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soil_wet','','')
2291
2292    ALLOCATE (soil_wet_litter(kjpindex,nstm),stat=ier)
2293    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable soil_wet_litter','','')
2294
2295    ALLOCATE (qflux(kjpindex,nslm,nstm),stat=ier) 
2296    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable qflux','','')
2297
2298    ALLOCATE (tmat(kjpindex,nslm,3),stat=ier)
2299    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tmat','','')
2300
2301    ALLOCATE (stmat(kjpindex,nslm,3),stat=ier)
2302    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable stmat','','')
2303
2304    ALLOCATE (nroot(kjpindex,nvm, nslm),stat=ier)
2305    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable nroot','','')
2306
2307    ALLOCATE (kfact_root(kjpindex, nslm, nstm), stat=ier)
2308    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kfact_root','','')
2309
2310    ALLOCATE (kfact(nslm, nscm),stat=ier)
2311    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable kfact','','')
2312
2313    ALLOCATE (zz(nslm),stat=ier)
2314    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zz','','')
2315
2316    ALLOCATE (dz(nslm),stat=ier)
2317    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dz','','')
2318   
2319    ALLOCATE (dh(nslm),stat=ier)
2320    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable dh','','')
2321
2322    ALLOCATE (mc_lin(imin:imax, kjpindex),stat=ier)
2323    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mc_lin','','')
2324
2325    ALLOCATE (k_lin(imin:imax, nslm, kjpindex),stat=ier)
2326    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable k_lin','','')
2327
2328    ALLOCATE (d_lin(imin:imax, nslm, kjpindex),stat=ier)
2329    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable d_lin','','')
2330
2331    ALLOCATE (a_lin(imin:imax, nslm, kjpindex),stat=ier)
2332    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable a_lin','','')
2333
2334    ALLOCATE (b_lin(imin:imax, nslm, kjpindex),stat=ier)
2335    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable b_lin','','')
2336
2337!pss+ ! WETALND variables allocation
2338!pss:+
2339   
2340    ALLOCATE (fsat(kjpindex),stat=ier)
2341       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fsat','','')
2342
2343    ALLOCATE (fwet(kjpindex),stat=ier)
2344       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fwet','','')
2345
2346    ALLOCATE (fwt1(kjpindex),stat=ier)
2347       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fwt1','','')
2348   
2349    ALLOCATE (fwt2(kjpindex),stat=ier)
2350       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fwt2','','')
2351   
2352    ALLOCATE (fwt3(kjpindex),stat=ier)
2353       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fwt3','','')
2354
2355    ALLOCATE (fwt4(kjpindex),stat=ier)
2356       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable fwt4','','')
2357
2358    ALLOCATE (drunoff(kjpindex,nvm),stat=ier)
2359       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable drunoff','','')
2360       
2361    ALLOCATE (ZMEAN(kjpindex),stat=ier)
2362       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZMEAN','','')
2363!    ALLOCATE (NB_PIXE(kjpindex),stat=ier)
2364!    IF (ier.NE.0) THEN
2365!        WRITE (numout,*) ' error in mx_eau_var allocation. We stop. We need kjpindex words = ',kjpindex
2366!        STOP 'hydrolc_init'
2367!    END IF
2368    ALLOCATE (ZSTDT(kjpindex),stat=ier)
2369    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZSTDT','','')
2370   
2371    ALLOCATE (ZSKEW(kjpindex),stat=ier)
2372    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZSKEW','','')
2373
2374    ALLOCATE (ZMIN(kjpindex),stat=ier)
2375    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZMIN','','')
2376   
2377    ALLOCATE (ZMAX(kjpindex),stat=ier)
2378    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZMAX','','')
2379   
2380    ALLOCATE (ZM(kjpindex),stat=ier)
2381    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZM','','')
2382
2383    ALLOCATE (ZZPAS(kjpindex),stat=ier)
2384    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZZPAS','','')
2385
2386    ALLOCATE (ZTAB_FSAT(kjpindex,1000),stat=ier)
2387    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZTAB_FSAT','','')
2388
2389    ALLOCATE (ZTAB_WTOP(kjpindex,1000),stat=ier)
2390    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZTAB_WTOP','','')
2391
2392    ALLOCATE (ZTAB_FWET(kjpindex,1000),stat=ier)
2393    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZTAB_FWET','','')
2394
2395    ALLOCATE (ZTAB_WTOP_WET(kjpindex,1000),stat=ier)
2396    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable ZTAB_WTOP_WET','','')
2397
2398!pss+
2399    ALLOCATE (mcw_grid(kjpindex),stat=ier)
2400    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcw_grid','','')
2401
2402    ALLOCATE (mcs_grid(kjpindex),stat=ier)
2403    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcs_grid','','')
2404!pss-
2405
2406!!! xuhui: this has to be defined even if not ok_freeze_cwrr
2407       ALLOCATE (profil_froz_hydro_ns(kjpindex, nslm, nstm),stat=ier)
2408       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydro_ns','','')
2409       profil_froz_hydro_ns(:,:,:) = zero
2410
2411
2412    IF (ok_freeze_cwrr) THEN
2413       ALLOCATE (profil_froz_hydro(kjpindex, nslm),stat=ier)
2414       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable profil_froz_hydrol','','')
2415       profil_froz_hydro(:,:) = zero
2416
2417       ALLOCATE (temp_hydro(kjpindex, nslm),stat=ier)
2418       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable temp_hydro','','')
2419       temp_hydro(:,:) = 280.
2420    ENDIF
2421
2422    ALLOCATE (mcl(kjpindex, nslm, nstm),stat=ier)
2423    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable mcl','','')
2424
2425    !  If we check the water balance we need two more variables
2426    IF ( check_waterbal ) THEN
2427       ALLOCATE (tot_water_beg(kjpindex),stat=ier)
2428       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_water_beg','','')
2429
2430       ALLOCATE (tot_water_end(kjpindex),stat=ier)
2431       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_water_end','','')
2432
2433       ALLOCATE (tot_flux(kjpindex),stat=ier)
2434       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_flux','','')
2435    ENDIF
2436
2437    ALLOCATE (undermcr(kjpindex),stat=ier)
2438    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable undermcr','','')
2439
2440    ALLOCATE (tot_watveg_beg(kjpindex),stat=ier)
2441    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watveg_beg','','')
2442   
2443    ALLOCATE (tot_watveg_end(kjpindex),stat=ier)
2444    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watvag_end','','')
2445   
2446    ALLOCATE (tot_watsoil_beg(kjpindex),stat=ier)
2447    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watsoil_beg','','')
2448   
2449    ALLOCATE (tot_watsoil_end(kjpindex),stat=ier)
2450    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable tot_watsoil_end','','')
2451   
2452    ALLOCATE (delsoilmoist(kjpindex),stat=ier)
2453    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delsoilmoist','','')
2454   
2455    ALLOCATE (delintercept(kjpindex),stat=ier)
2456    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delintercept','','')
2457   
2458    ALLOCATE (delswe(kjpindex),stat=ier)
2459    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable delswe','','')
2460   
2461    ALLOCATE (snow_beg(kjpindex),stat=ier)
2462    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snow_beg','','')
2463   
2464    ALLOCATE (snow_end(kjpindex),stat=ier)
2465    IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable snow_end','','')
2466   
2467    !! 4 Open restart input file and read data for HYDROLOGIC process
2468       IF (printlev>=3) WRITE (numout,*) ' we have to read a restart file for HYDROLOGIC variables'
2469
2470       CALL ioconf_setatt_p('UNITS', '-')
2471       CALL restget_p (rest_id, 'moistc', nbp_glo, nslm , nstm, kjit, .TRUE., mc, "gather", nbp_glo, index_g)
2472       !
2473       CALL ioconf_setatt_p('UNITS', '-')
2474       CALL restget_p (rest_id, 'moistcl', nbp_glo, nslm , nstm, kjit, .TRUE., mcl, "gather", nbp_glo, index_g)
2475
2476       CALL ioconf_setatt_p('UNITS', '-')
2477       CALL ioconf_setatt_p('LONG_NAME','us')
2478       CALL restget_p (rest_id, 'us', nbp_glo, nvm, nstm, nslm, kjit, .TRUE., us, "gather", nbp_glo, index_g)
2479       !
2480       var_name= 'free_drain_coef'
2481       CALL ioconf_setatt_p('UNITS', '-')
2482       CALL ioconf_setatt_p('LONG_NAME','Coefficient for free drainage at bottom of soil')
2483       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., free_drain_coef, "gather", nbp_glo, index_g)
2484       !
2485       var_name= 'zwt_force'
2486       CALL ioconf_setatt_p('UNITS', 'm')
2487       CALL ioconf_setatt_p('LONG_NAME','Prescribed water table depth')
2488       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., zwt_force, "gather", nbp_glo, index_g)
2489       !
2490       var_name= 'water2infilt'
2491       CALL ioconf_setatt_p('UNITS', '-')
2492       CALL ioconf_setatt_p('LONG_NAME','Remaining water to be infiltrated on top of the soil')
2493       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., water2infilt, "gather", nbp_glo, index_g)
2494       !
2495       var_name= 'ae_ns'
2496       CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2497       CALL ioconf_setatt_p('LONG_NAME','Bare soil evap on each soil type')
2498       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., ae_ns, "gather", nbp_glo, index_g)
2499       !
2500       var_name= 'snow'       
2501       CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2502       CALL ioconf_setatt_p('LONG_NAME','Snow mass')
2503       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., snow, "gather", nbp_glo, index_g)
2504       !
2505       var_name= 'snow_age'
2506          CALL ioconf_setatt_p('UNITS', 'd')
2507          CALL ioconf_setatt_p('LONG_NAME','Snow age')
2508       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., snow_age, "gather", nbp_glo, index_g)
2509       !
2510       var_name= 'snow_nobio'
2511          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2512          CALL ioconf_setatt_p('LONG_NAME','Snow on other surface types')
2513       CALL restget_p (rest_id, var_name, nbp_glo, nnobio  , 1, kjit, .TRUE., snow_nobio, "gather", nbp_glo, index_g)
2514       !
2515       var_name= 'snow_nobio_age'
2516          CALL ioconf_setatt_p('UNITS', 'd')
2517          CALL ioconf_setatt_p('LONG_NAME','Snow age on other surface types')
2518       CALL restget_p (rest_id, var_name, nbp_glo, nnobio  , 1, kjit, .TRUE., snow_nobio_age, "gather", nbp_glo, index_g)
2519       !
2520       var_name= 'qsintveg'
2521          CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2522          CALL ioconf_setatt_p('LONG_NAME','Intercepted moisture')
2523       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., qsintveg, "gather", nbp_glo, index_g)
2524
2525!pss:+ !         
2526       var_name= 'fwet_out'     
2527          CALL ioconf_setatt('UNITS', '-')
2528          CALL ioconf_setatt('LONG_NAME','fwet pr autres routines')
2529       CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE.,fwet_out , "gather", nbp_glo, index_g)
2530!pss:-
2531       var_name= 'evap_bare_lim_ns'
2532          CALL ioconf_setatt_p('UNITS', '?')
2533          CALL ioconf_setatt_p('LONG_NAME','?')
2534       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., evap_bare_lim_ns, "gather", nbp_glo, index_g)
2535       CALL setvar_p (evap_bare_lim_ns, val_exp, 'NO_KEYWORD', 0.0)
2536!       DO jv = 1,nvm
2537!           evap_bare_lim_pft(:,jv) = evap_bare_lim_ns(:,pref_soil_veg(jv))
2538!       ENDDO
2539
2540       var_name= 'resdist'
2541          CALL ioconf_setatt_p('UNITS', '-')
2542          CALL ioconf_setatt_p('LONG_NAME','soiltile values from previous time-step')
2543       CALL restget_p (rest_id, var_name, nbp_glo, nstm, 1, kjit, .TRUE., resdist, "gather", nbp_glo, index_g)
2544
2545       var_name= 'vegtot_old'
2546          CALL ioconf_setatt_p('UNITS', '-')
2547          CALL ioconf_setatt_p('LONG_NAME','vegtot from previous time-step')
2548       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., vegtot_old, "gather", nbp_glo, index_g)       
2549       
2550       IF ( check_waterbal ) THEN
2551          var_name= 'tot_water_beg'
2552             CALL ioconf_setatt_p('UNITS', 'kg/m^2')
2553             CALL ioconf_setatt_p('LONG_NAME','Previous Total water')
2554          CALL restget_p (rest_id, var_name, nbp_glo, 1  , 1, kjit, .TRUE., tot_water_beg, "gather", nbp_glo, index_g)
2555       ENDIF
2556
2557       ! Read drysoil_frac. It will be initalized later in hydrol_var_init if the varaible is not find in restart file.
2558          CALL ioconf_setatt_p('UNITS', '')
2559          CALL ioconf_setatt_p('LONG_NAME','Function of litter wetness')
2560       CALL restget_p (rest_id, 'drysoil_frac', nbp_glo, 1  , 1, kjit, .TRUE., drysoil_frac, "gather", nbp_glo, index_g)
2561
2562
2563    !! 5 get restart values if none were found in the restart file
2564       !
2565       !Config Key   = HYDROL_MOISTURE_CONTENT
2566       !Config Desc  = Soil moisture on each soil tile and levels
2567       !Config If    = HYDROL_CWRR       
2568       !Config Def   = 0.3
2569       !Config Help  = The initial value of mc if its value is not found
2570       !Config         in the restart file. This should only be used if the model is
2571       !Config         started without a restart file.
2572       !Config Units = [m3/m3]
2573       !
2574       CALL setvar_p (mc, val_exp, 'HYDROL_MOISTURE_CONTENT', 0.3_r_std)
2575
2576       ! Initialize mcl as mc if it is not found in the restart file
2577!      IF (minval(mc) .LT. zero) THEN
2578!       WRITE (numout,*) 'BOOM mc LT zero L2578 val =', mc
2579!      END IF
2580       IF ( ALL(mcl(:,:,:)==val_exp) ) THEN
2581          mcl(:,:,:) = mc(:,:,:)
2582       END IF
2583
2584       
2585       !Config Key   = US_INIT
2586       !Config Desc  = US_NVM_NSTM_NSLM
2587       !Config If    = HYDROL_CWRR       
2588       !Config Def   = 0.0
2589       !Config Help  = The initial value of us (relative moisture) if its value is not found
2590       !Config         in the restart file. This should only be used if the model is
2591       !Config         started without a restart file.
2592       !Config Units = [-]
2593       !
2594       DO jsl=1,nslm
2595          CALL setvar_p (us(:,:,:,jsl), val_exp, 'US_INIT', zero)
2596       ENDDO
2597       !
2598       !Config Key   = ZWT_FORCE
2599       !Config Desc  = Prescribed water depth, dimension nstm
2600       !Config If    = HYDROL_CWRR       
2601       !Config Def   = undef undef undef
2602       !Config Help  = The initial value of zwt_force if its value is not found
2603       !Config         in the restart file. undef corresponds to a case whith no forced WT.
2604       !Config         This should only be used if the model is started without a restart file.
2605       !Config Units = [m]
2606       
2607       ALLOCATE (zwt_default(nstm),stat=ier)
2608       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable zwt_default','','')
2609       zwt_default(:) = undef_sechiba
2610       CALL setvar_p (zwt_force, val_exp, 'ZWT_FORCE', zwt_default )
2611
2612       zforce = .FALSE.
2613       DO jst=1,nstm
2614          IF (zwt_force(1,jst) <= zmaxh) zforce = .TRUE. ! AD16*** check if OK with vertical_soil
2615       ENDDO
2616       !
2617       !Config Key   = FREE_DRAIN_COEF
2618       !Config Desc  = Coefficient for free drainage at bottom, dimension nstm
2619       !Config If    = HYDROL_CWRR       
2620       !Config Def   = 1.0 1.0 1.0
2621       !Config Help  = The initial value of free drainage coefficient if its value is not found
2622       !Config         in the restart file. This should only be used if the model is
2623       !Config         started without a restart file.
2624       !Config Units = [-]
2625             
2626       ALLOCATE (free_drain_max(nstm),stat=ier)
2627       IF (ier /= 0) CALL ipslerr_p(3,'hydrol_init','Problem in allocate of variable free_drain_max','','')
2628       free_drain_max(:)=1.0
2629
2630       CALL setvar_p (free_drain_coef, val_exp, 'FREE_DRAIN_COEF', free_drain_max)
2631       DEALLOCATE(free_drain_max)
2632
2633       !
2634       !Config Key   = WATER_TO_INFILT
2635       !Config Desc  = Water to be infiltrated on top of the soil
2636       !Config If    = HYDROL_CWRR   
2637       !Config Def   = 0.0
2638       !Config Help  = The initial value of free drainage if its value is not found
2639       !Config         in the restart file. This should only be used if the model is
2640       !Config         started without a restart file.
2641       !Config Units = [mm]
2642       !
2643       CALL setvar_p (water2infilt, val_exp, 'WATER_TO_INFILT', zero)
2644       !
2645       !Config Key   = EVAPNU_SOIL
2646       !Config Desc  = Bare soil evap on each soil if not found in restart
2647       !Config If    = HYDROL_CWRR 
2648       !Config Def   = 0.0
2649       !Config Help  = The initial value of bare soils evap if its value is not found
2650       !Config         in the restart file. This should only be used if the model is
2651       !Config         started without a restart file.
2652       !Config Units = [mm]
2653       !
2654       CALL setvar_p (ae_ns, val_exp, 'EVAPNU_SOIL', zero)
2655       !
2656       !Config Key  = HYDROL_SNOW
2657       !Config Desc  = Initial snow mass if not found in restart
2658       !Config If    = OK_SECHIBA
2659       !Config Def   = 0.0
2660       !Config Help  = The initial value of snow mass if its value is not found
2661       !Config         in the restart file. This should only be used if the model is
2662       !Config         started without a restart file.
2663       !Config Units =
2664       !
2665       CALL setvar_p (snow, val_exp, 'HYDROL_SNOW', zero)
2666       !
2667       !Config Key   = HYDROL_SNOWAGE
2668       !Config Desc  = Initial snow age if not found in restart
2669       !Config If    = OK_SECHIBA
2670       !Config Def   = 0.0
2671       !Config Help  = The initial value of snow age if its value is not found
2672       !Config         in the restart file. This should only be used if the model is
2673       !Config         started without a restart file.
2674       !Config Units = ***
2675       !
2676       CALL setvar_p (snow_age, val_exp, 'HYDROL_SNOWAGE', zero)
2677       !
2678       !Config Key   = HYDROL_SNOW_NOBIO
2679       !Config Desc  = Initial snow amount on ice, lakes, etc. if not found in restart
2680       !Config If    = OK_SECHIBA
2681       !Config Def   = 0.0
2682       !Config Help  = The initial value of snow if its value is not found
2683       !Config         in the restart file. This should only be used if the model is
2684       !Config         started without a restart file.
2685       !Config Units = [mm]
2686       !
2687       CALL setvar_p (snow_nobio, val_exp, 'HYDROL_SNOW_NOBIO', zero)
2688       !
2689       !Config Key   = HYDROL_SNOW_NOBIO_AGE
2690       !Config Desc  = Initial snow age on ice, lakes, etc. if not found in restart
2691       !Config If    = OK_SECHIBA
2692       !Config Def   = 0.0
2693       !Config Help  = The initial value of snow age if its value is not found
2694       !Config         in the restart file. This should only be used if the model is
2695       !Config         started without a restart file.
2696       !Config Units = ***
2697       !
2698       CALL setvar_p (snow_nobio_age, val_exp, 'HYDROL_SNOW_NOBIO_AGE', zero)
2699       !
2700       !Config Key   = HYDROL_QSV
2701       !Config Desc  = Initial water on canopy if not found in restart
2702       !Config If    = OK_SECHIBA
2703       !Config Def   = 0.0
2704       !Config Help  = The initial value of moisture on canopy if its value
2705       !Config         is not found in the restart file. This should only be used if
2706       !Config         the model is started without a restart file.
2707       !Config Units = [mm]
2708       !
2709       CALL setvar_p (qsintveg, val_exp, 'HYDROL_QSV', zero)
2710
2711       IF (ok_freeze_cwrr) THEN 
2712          CALL setvar_p (profil_froz_hydro, val_exp, 'NO_KEYWORD', zero)
2713          CALL setvar_p (profil_froz_hydro_ns, val_exp, 'NO_KEYWORD', zero)
2714          CALL setvar_p (kk, val_exp, 'NO_KEYWORD', 276.48)
2715          CALL setvar_p (kk_moy, val_exp, 'NO_KEYWORD', 276.48)
2716          CALL setvar_p (temp_hydro, val_exp, 'NO_KEYWORD', 280.)
2717       ENDIF
2718       
2719!pss:+
2720       !
2721       !Config Key   = HYDROL_FWET
2722       !Config Desc  = Initial fwet_out if not found in restart
2723       !Config If    = TOPM_calcul
2724       !Config Def   = 0.0
2725       !Config Help  = The initial value of fwet_out if its value
2726       !Config         is not found in the restart file. This should only be used if
2727       !Config         the model is started without a restart file.
2728       !Config Units =
2729       CALL setvar_p (fwet_out, val_exp,'HYDROL_FWET', zero)
2730
2731!pss:-
2732
2733    !! 6 Vegetation array     
2734       !
2735       ! If resdist is not in restart file, initialize with soiltile
2736       IF ( MINVAL(resdist) .EQ.  MAXVAL(resdist) .AND. MINVAL(resdist) .EQ. val_exp) THEN
2737          resdist(:,:) = soiltile(:,:)
2738       ENDIF
2739       
2740       !
2741       !  Remember that it is only frac_nobio + SUM(veget_max(,:)) that is equal to 1. Thus we need vegtot
2742       !
2743       IF ( ALL(vegtot_old(:) == val_exp) ) THEN
2744          ! vegtot_old was not found in restart file
2745          DO ji = 1, kjpindex
2746             vegtot_old(ji) = SUM(veget_max(ji,:))
2747          ENDDO
2748       ENDIF
2749       
2750       ! In the initialization phase, vegtot must take the value from previous time-step.
2751       ! This is because hydrol_main is done before veget_max is updated in the end of the time step.
2752       vegtot(:) = vegtot_old(:)
2753       
2754       !
2755       !
2756       ! compute the masks for veget
2757
2758       mask_veget(:,:) = 0
2759       mask_soiltile(:,:) = 0
2760
2761       DO jst=1,nstm
2762          DO ji = 1, kjpindex
2763             IF(soiltile(ji,jst) .GT. min_sechiba) THEN
2764                mask_soiltile(ji,jst) = 1
2765             ENDIF
2766          END DO
2767       ENDDO
2768         
2769       DO jv = 1, nvm
2770          DO ji = 1, kjpindex
2771             IF(veget_max(ji,jv) .GT. min_sechiba) THEN
2772                mask_veget(ji,jv) = 1
2773             ENDIF
2774          END DO
2775       END DO
2776
2777       humrelv(:,:,:) = SUM(us,dim=4)
2778
2779         
2780       !! 7a. Set vegstress
2781     
2782       var_name= 'vegstress'
2783          CALL ioconf_setatt_p('UNITS', '-')
2784          CALL ioconf_setatt_p('LONG_NAME','Vegetation growth moisture stress')
2785       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., vegstress, "gather", nbp_glo, index_g)
2786
2787       vegstressv(:,:,:) = humrelv(:,:,:)
2788       ! Calculate vegstress if it is not found in restart file
2789       IF (ALL(vegstress(:,:)==val_exp)) THEN
2790          DO jv=1,nvm
2791             DO ji=1,kjpindex
2792                vegstress(ji,jv)=vegstress(ji,jv) + vegstressv(ji,jv,pref_soil_veg(jv))
2793             END DO
2794          END DO
2795       END IF
2796       !! 7b. Set humrel   
2797       ! Read humrel from restart file
2798       var_name= 'humrel'
2799          CALL ioconf_setatt_p('UNITS', '')
2800          CALL ioconf_setatt_p('LONG_NAME','Relative humidity')
2801       CALL restget_p (rest_id, var_name, nbp_glo, nvm, 1, kjit, .TRUE., humrel, "gather", nbp_glo, index_g)
2802
2803       ! Calculate humrel if it is not found in restart file
2804       IF (ALL(humrel(:,:)==val_exp)) THEN
2805          ! set humrel from humrelv, assuming equi-repartition for the first time step
2806          humrel(:,:) = zero
2807          DO jv=1,nvm
2808             DO ji=1,kjpindex
2809                humrel(ji,jv)=humrel(ji,jv) + humrelv(ji,jv,pref_soil_veg(jv))     
2810             END DO
2811          END DO
2812       END IF
2813
2814       ! Read evap_bare_lim from restart file
2815       var_name= 'evap_bare_lim'
2816          CALL ioconf_setatt_p('UNITS', '')
2817          CALL ioconf_setatt_p('LONG_NAME','Limitation factor for bare soil evaporation')
2818       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., evap_bare_lim, "gather", nbp_glo, index_g)
2819
2820       ! Calculate evap_bare_lim if it was not found in the restart file.
2821       IF ( ALL(evap_bare_lim(:) == val_exp) ) THEN
2822          DO ji = 1, kjpindex
2823             evap_bare_lim(ji) =  SUM(evap_bare_lim_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
2824          ENDDO
2825       END IF
2826
2827
2828    ! Read from restart file       
2829    ! The variables tot_watsoil_beg, tot_watsoil_beg and snwo_beg will be initialized in the end of
2830    ! hydrol_initialize if they were not found in the restart file.
2831       
2832    var_name= 'tot_watveg_beg'
2833       CALL ioconf_setatt_p('UNITS', '?')
2834       CALL ioconf_setatt_p('LONG_NAME','?')
2835    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., tot_watveg_beg, "gather", nbp_glo, index_g)
2836   
2837    var_name= 'tot_watsoil_beg'
2838       CALL ioconf_setatt_p('UNITS', '?')
2839       CALL ioconf_setatt_p('LONG_NAME','?')
2840    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., tot_watsoil_beg, "gather", nbp_glo, index_g)
2841   
2842    var_name= 'snow_beg'
2843       CALL ioconf_setatt_p('UNITS', '?')
2844       CALL ioconf_setatt_p('LONG_NAME','?')
2845    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., snow_beg, "gather", nbp_glo, index_g)
2846       
2847 
2848    ! Initialize variables for explictsnow module by reading restart file
2849    IF (ok_explicitsnow) THEN
2850       CALL explicitsnow_initialize( kjit,     kjpindex, rest_id,    snowrho,   &
2851                                     snowtemp, snowdz,   snowheat,   snowgrain)
2852    END IF
2853
2854   
2855    IF (printlev>=3) WRITE (numout,*) ' hydrol_init done '
2856   
2857  END SUBROUTINE hydrol_init
2858
2859
2860!! ================================================================================================================================
2861!! SUBROUTINE   : hydrol_clear
2862!!
2863!>\BRIEF        Deallocate arrays
2864!!
2865!_ ================================================================================================================================
2866!_ hydrol_clear
2867
2868  SUBROUTINE hydrol_clear()
2869
2870    ! Allocation for soiltile related parameters
2871    IF ( ALLOCATED (nvan)) DEALLOCATE (nvan)
2872    IF ( ALLOCATED (avan)) DEALLOCATE (avan)
2873    IF ( ALLOCATED (mcr)) DEALLOCATE (mcr)
2874    IF ( ALLOCATED (mcs_mineral)) DEALLOCATE (mcs_mineral)
2875    IF ( ALLOCATED (ks)) DEALLOCATE (ks)
2876    IF ( ALLOCATED (pcent)) DEALLOCATE (pcent)
2877    IF ( ALLOCATED (mcf_mineral)) DEALLOCATE (mcf_mineral)
2878    IF ( ALLOCATED (mcw_mineral)) DEALLOCATE (mcw_mineral)
2879    IF ( ALLOCATED (mcs)) DEALLOCATE (mcs)
2880    IF ( ALLOCATED (mcf)) DEALLOCATE (mcf)
2881    IF ( ALLOCATED (mcw)) DEALLOCATE (mcw)
2882    IF ( ALLOCATED (VG_m)) DEALLOCATE (VG_m)
2883    IF ( ALLOCATED (VG_n)) DEALLOCATE (VG_n)
2884    IF ( ALLOCATED (VG_alpha)) DEALLOCATE (VG_alpha)
2885    IF ( ALLOCATED (VG_psi_fc)) DEALLOCATE (VG_psi_fc)
2886    IF ( ALLOCATED (VG_psi_wp)) DEALLOCATE (VG_psi_wp)
2887    IF ( ALLOCATED (mc_awet)) DEALLOCATE (mc_awet)
2888    IF ( ALLOCATED (mc_adry)) DEALLOCATE (mc_adry)
2889!pss+
2890    IF ( ALLOCATED (mcs_grid)) DEALLOCATE (mcs_grid)
2891    IF ( ALLOCATED (mcw_grid)) DEALLOCATE (mcw_grid)
2892!pss-
2893    ! Other arrays
2894    IF (ALLOCATED (mask_veget)) DEALLOCATE (mask_veget)
2895    IF (ALLOCATED (irrig_fin)) DEALLOCATE (irrig_fin)
2896    IF (ALLOCATED (mask_soiltile)) DEALLOCATE (mask_soiltile)
2897    IF (ALLOCATED (humrelv)) DEALLOCATE (humrelv)
2898    IF (ALLOCATED (vegstressv)) DEALLOCATE (vegstressv)
2899    IF (ALLOCATED (us)) DEALLOCATE (us)
2900    IF (ALLOCATED  (precisol)) DEALLOCATE (precisol)
2901    IF (ALLOCATED  (precisol_ns)) DEALLOCATE (precisol_ns)
2902    IF (ALLOCATED  (free_drain_coef)) DEALLOCATE (free_drain_coef)
2903    IF (ALLOCATED  (frac_bare_ns)) DEALLOCATE (frac_bare_ns)
2904    IF (ALLOCATED  (water2infilt)) DEALLOCATE (water2infilt)
2905    IF (ALLOCATED  (ae_ns)) DEALLOCATE (ae_ns)
2906    IF (ALLOCATED  (evap_bare_lim_ns)) DEALLOCATE (evap_bare_lim_ns)
2907    IF (ALLOCATED  (rootsink)) DEALLOCATE (rootsink)
2908    IF (ALLOCATED  (subsnowveg)) DEALLOCATE (subsnowveg)
2909    IF (ALLOCATED  (subsnownobio)) DEALLOCATE (subsnownobio)
2910    IF (ALLOCATED  (snowmelt)) DEALLOCATE (snowmelt)
2911    IF (ALLOCATED  (icemelt)) DEALLOCATE (icemelt)
2912    IF (ALLOCATED  (subsinksoil)) DEALLOCATE (subsinksoil)
2913    IF (ALLOCATED  (mx_eau_var)) DEALLOCATE (mx_eau_var)
2914    IF (ALLOCATED  (vegtot)) DEALLOCATE (vegtot)
2915    IF (ALLOCATED  (vegtot_old)) DEALLOCATE (vegtot_old)
2916    IF (ALLOCATED  (resdist)) DEALLOCATE (resdist)
2917    IF (ALLOCATED  (tot_water_beg)) DEALLOCATE (tot_water_beg)
2918    IF (ALLOCATED  (tot_water_end)) DEALLOCATE (tot_water_end)
2919    IF (ALLOCATED  (tot_flux)) DEALLOCATE (tot_flux)
2920    IF (ALLOCATED  (tot_watveg_beg)) DEALLOCATE (tot_watveg_beg)
2921    IF (ALLOCATED  (tot_watveg_end)) DEALLOCATE (tot_watveg_end)
2922    IF (ALLOCATED  (tot_watsoil_beg)) DEALLOCATE (tot_watsoil_beg)
2923    IF (ALLOCATED  (tot_watsoil_end)) DEALLOCATE (tot_watsoil_end)
2924    IF (ALLOCATED  (delsoilmoist)) DEALLOCATE (delsoilmoist)
2925    IF (ALLOCATED  (delintercept)) DEALLOCATE (delintercept)
2926    IF (ALLOCATED  (snow_beg)) DEALLOCATE (snow_beg)
2927    IF (ALLOCATED  (snow_end)) DEALLOCATE (snow_end)
2928    IF (ALLOCATED  (delswe)) DEALLOCATE (delswe)
2929    IF (ALLOCATED  (undermcr)) DEALLOCATE (undermcr)
2930    IF (ALLOCATED  (v1)) DEALLOCATE (v1)
2931    IF (ALLOCATED  (humtot)) DEALLOCATE (humtot)
2932    IF (ALLOCATED  (resolv)) DEALLOCATE (resolv)
2933    IF (ALLOCATED  (k)) DEALLOCATE (k)
2934    IF (ALLOCATED  (kk)) DEALLOCATE (kk)
2935    IF (ALLOCATED  (kk_moy)) DEALLOCATE (kk_moy)
2936    IF (ALLOCATED  (a)) DEALLOCATE (a)
2937    IF (ALLOCATED  (b)) DEALLOCATE (b)
2938    IF (ALLOCATED  (d)) DEALLOCATE (d)
2939    IF (ALLOCATED  (e)) DEALLOCATE (e)
2940    IF (ALLOCATED  (f)) DEALLOCATE (f)
2941    IF (ALLOCATED  (g1)) DEALLOCATE (g1)
2942    IF (ALLOCATED  (ep)) DEALLOCATE (ep)
2943    IF (ALLOCATED  (fp)) DEALLOCATE (fp)
2944    IF (ALLOCATED  (gp)) DEALLOCATE (gp)
2945    IF (ALLOCATED  (rhs)) DEALLOCATE (rhs)
2946    IF (ALLOCATED  (srhs)) DEALLOCATE (srhs)
2947    IF (ALLOCATED  (tmc)) DEALLOCATE (tmc)
2948    IF (ALLOCATED  (tmcs)) DEALLOCATE (tmcs)
2949    IF (ALLOCATED  (tmcr)) DEALLOCATE (tmcr)
2950    IF (ALLOCATED  (tmc_litter)) DEALLOCATE (tmc_litter)
2951!gmjc top 5 layer mc for grazing
2952    IF (ALLOCATED  (tmc_trampling)) DEALLOCATE (tmc_trampling)
2953!end gmjc
2954    IF (ALLOCATED  (tmc_litt_mea)) DEALLOCATE (tmc_litt_mea)
2955    IF (ALLOCATED  (tmc_litter_res)) DEALLOCATE (tmc_litter_res)
2956    IF (ALLOCATED  (tmc_litter_wilt)) DEALLOCATE (tmc_litter_wilt)
2957    IF (ALLOCATED  (tmc_litter_field)) DEALLOCATE (tmc_litter_field)
2958    IF (ALLOCATED  (tmc_litter_sat)) DEALLOCATE (tmc_litter_sat)
2959    IF (ALLOCATED  (tmc_litter_awet)) DEALLOCATE (tmc_litter_awet)
2960    IF (ALLOCATED  (tmc_litter_adry)) DEALLOCATE (tmc_litter_adry)
2961    IF (ALLOCATED  (tmc_litt_wet_mea)) DEALLOCATE (tmc_litt_wet_mea)
2962    IF (ALLOCATED  (tmc_litt_dry_mea)) DEALLOCATE (tmc_litt_dry_mea)
2963    IF (ALLOCATED  (ru_ns)) DEALLOCATE (ru_ns)
2964    IF (ALLOCATED  (dr_ns)) DEALLOCATE (dr_ns)
2965    IF (ALLOCATED  (tr_ns)) DEALLOCATE (tr_ns)
2966    IF (ALLOCATED  (vegetmax_soil)) DEALLOCATE (vegetmax_soil)
2967    IF (ALLOCATED  (mc)) DEALLOCATE (mc)
2968    IF (ALLOCATED  (soilmoist)) DEALLOCATE (soilmoist)
2969    IF (ALLOCATED  (soil_wet)) DEALLOCATE (soil_wet)
2970    IF (ALLOCATED  (soil_wet_litter)) DEALLOCATE (soil_wet_litter)
2971    IF (ALLOCATED  (qflux)) DEALLOCATE (qflux)
2972    IF (ALLOCATED  (tmat)) DEALLOCATE (tmat)
2973    IF (ALLOCATED  (stmat)) DEALLOCATE (stmat)
2974    IF (ALLOCATED  (nroot)) DEALLOCATE (nroot)
2975    IF (ALLOCATED  (kfact_root)) DEALLOCATE (kfact_root)
2976    IF (ALLOCATED  (kfact)) DEALLOCATE (kfact)
2977    IF (ALLOCATED  (zz)) DEALLOCATE (zz)
2978    IF (ALLOCATED  (dz)) DEALLOCATE (dz)
2979    IF (ALLOCATED  (dh)) DEALLOCATE (dh)
2980    IF (ALLOCATED  (mc_lin)) DEALLOCATE (mc_lin)
2981    IF (ALLOCATED  (k_lin)) DEALLOCATE (k_lin)
2982    IF (ALLOCATED  (d_lin)) DEALLOCATE (d_lin)
2983    IF (ALLOCATED  (a_lin)) DEALLOCATE (a_lin)
2984    IF (ALLOCATED  (b_lin)) DEALLOCATE (b_lin)
2985    IF (ALLOCATED  (frac_hydro_diag)) DEALLOCATE (frac_hydro_diag)
2986   
2987!pss:+ !WETLAND variables
2988    IF (ALLOCATED  (fsat))  DEALLOCATE (fsat)
2989    IF (ALLOCATED  (fwet))  DEALLOCATE (fwet)
2990    IF (ALLOCATED  (fwt1))  DEALLOCATE (fwt1)
2991    IF (ALLOCATED  (fwt2))  DEALLOCATE (fwt2)
2992    IF (ALLOCATED  (fwt3))  DEALLOCATE (fwt3)
2993    IF (ALLOCATED  (fwt4))  DEALLOCATE (fwt4)
2994    IF (ALLOCATED  (drunoff))  DEALLOCATE (drunoff)
2995    IF (ALLOCATED  (ZMEAN)) DEALLOCATE (ZMEAN)
2996!    IF (ALLOCATED  (NB_PIXE)) DEALLOCATE (NB_PIXE)
2997    IF (ALLOCATED  (ZSTDT)) DEALLOCATE (ZSTDT)
2998    IF (ALLOCATED  (ZSKEW)) DEALLOCATE (ZSKEW)
2999    IF (ALLOCATED  (ZMIN)) DEALLOCATE (ZMIN)
3000    IF (ALLOCATED  (ZMAX)) DEALLOCATE (ZMAX)
3001    IF (ALLOCATED  (ZM)) DEALLOCATE (ZM)
3002    IF (ALLOCATED  (ZZPAS)) DEALLOCATE (ZZPAS)
3003    IF (ALLOCATED  (ZTAB_FSAT)) DEALLOCATE (ZTAB_FSAT)
3004    IF (ALLOCATED  (ZTAB_WTOP)) DEALLOCATE (ZTAB_WTOP)
3005    IF (ALLOCATED  (ZTAB_FWET)) DEALLOCATE (ZTAB_FWET)
3006    IF (ALLOCATED  (ZTAB_WTOP_WET)) DEALLOCATE (ZTAB_WTOP_WET)
3007!pss:-
3008    IF ( ALLOCATED (refSOC_1d)) DEALLOCATE (refSOC_1d)
3009
3010  END SUBROUTINE hydrol_clear
3011
3012!! ================================================================================================================================
3013!! SUBROUTINE   : hydrol_tmc_update
3014!!
3015!>\BRIEF        This routine updates the soil moisture profiles when the vegetation fraction have changed.
3016!!
3017!! DESCRIPTION  :
3018!!
3019!!    This routine update tmc and mc with variation of veget_max (LAND_USE or DGVM activated)
3020!!
3021!!
3022!!
3023!!
3024!! RECENT CHANGE(S) : Adaptation to excluding nobio from soiltile(1)
3025!!
3026!! MAIN OUTPUT VARIABLE(S) :
3027!!
3028!! REFERENCE(S) :
3029!!
3030!! FLOWCHART    : None
3031!! \n
3032!_ ================================================================================================================================
3033!_ hydrol_tmc_update
3034  SUBROUTINE hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg, drain_upd, runoff_upd)
3035
3036    !! 0.1 Input variables
3037    INTEGER(i_std), INTENT(in)                            :: kjpindex      !! domain size
3038    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)     :: veget_max     !! max fraction of vegetation type
3039    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)   :: soiltile      !! Fraction of each soil tile (0-1, unitless)
3040
3041    !! 0.2 Output variables
3042    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: drain_upd        !! Change in drainage due to decrease in vegtot
3043                                                                              !! on mc [kg/m2/dt]
3044    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: runoff_upd       !! Change in runoff due to decrease in vegtot
3045                                                                              !! on water2infilt[kg/m2/dt]
3046   
3047    !! 0.3 Modified variables
3048    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg   !! Amount of water in the canopy interception
3049
3050    !! 0.4 Local variables
3051    INTEGER(i_std)                           :: ji, jv, jst,jsl
3052    LOGICAL                                  :: soil_upd        !! True if soiltile changed since last time step
3053    LOGICAL                                  :: vegtot_upd      !! True if vegtot changed since last time step
3054    LOGICAL                                  :: error=.FALSE.   !! If true, exit in the end of subroutine
3055    REAL(r_std), DIMENSION(kjpindex,nstm)    :: vmr             !! Change in soiltile (within vegtot)
3056    REAL(r_std), DIMENSION(kjpindex)         :: vmr_sum
3057    REAL(r_std), DIMENSION(kjpindex)         :: delvegtot   
3058    REAL(r_std), DIMENSION(kjpindex,nslm)    :: mc_dilu         !! Total loss of moisture content
3059    REAL(r_std), DIMENSION(kjpindex)         :: infil_dilu      !! Total loss for water2infilt
3060    REAL(r_std), DIMENSION(kjpindex,nstm)    :: tmc_old         !! tmc before calculations
3061    REAL(r_std), DIMENSION(kjpindex,nstm)    :: water2infilt_old!! water2infilt before calculations
3062    REAL(r_std), DIMENSION (kjpindex,nvm)    :: qsintveg_old    !! qsintveg before calculations
3063    REAL(r_std), DIMENSION(kjpindex)         :: test
3064    REAL(r_std), DIMENSION(kjpindex,nslm,nstm) :: mcaux        !! serves to hold the chnage in mc when vegtot decreases
3065
3066    !! 0. For checks
3067
3068    IF (check_cwrr) THEN
3069       ! Save soil moisture for later use
3070       tmc_old(:,:) = tmc(:,:) 
3071       water2infilt_old(:,:) = water2infilt(:,:)
3072       qsintveg_old(:,:) = qsintveg(:,:)
3073    ENDIF
3074   
3075    !! 1. If a PFT has disapperead as result from a veget_max change,
3076    !!    then add canopy water to surface water.
3077    !     Other adaptations of qsintveg are delt by the normal functioning of hydrol_canop
3078
3079!       WRITE(numout,*) '3079 minval water2infilt =', (minval(water2infilt))
3080!       WRITE(numout,*) '3079 maxval water2infilt =', (maxval(water2infilt))
3081!       WRITE(numout,*) '3079 minval qsingtveg_old =', (minval(qsintveg_old))
3082!       WRITE(numout,*) '3079 maxval qsintveg_old =', (maxval(qsintveg_old))
3083!       WRITE(numout,*) '3079 minval tmc =', (minval(tmc))
3084!       WRITE(numout,*) '3079 maxval tmc =', (maxval(tmc))
3085
3086       
3087!      IF (minval(mc) .LT. zero) THEN
3088!       WRITE (numout,*) 'BOOM mc LT zero 3079 tmc val =', tmc
3089!       WRITE (numout,*) 'BOOM mc LT zero 3079 water2infilt val =', water2infilt
3090!      END IF
3091    DO ji=1,kjpindex
3092       IF (vegtot_old(ji) .GT.min_sechiba) THEN
3093          DO jv=1,nvm
3094             IF ((veget_max(ji,jv).LT.min_sechiba).AND.(qsintveg(ji,jv).GT.0.)) THEN
3095                jst=pref_soil_veg(jv) ! soil tile index
3096                water2infilt(ji,jst) = water2infilt(ji,jst) + qsintveg(ji,jv)/(resdist(ji,jst)*vegtot_old(ji))
3097                qsintveg(ji,jv) = zero
3098             ENDIF
3099          ENDDO
3100       ENDIF
3101    ENDDO
3102
3103!       WRITE(numout,*) 'minval 3104 water2infilt =', (minval(water2infilt))
3104!       WRITE(numout,*) 'maxval 3104 water2infilt =', (maxval(water2infilt))
3105!       WRITE(numout,*) 'minval 3104 vegtot_old =', (minval(vegtot_old))
3106!       WRITE(numout,*) 'maxval 3104 vegtot_old =', (maxval(vegtot_old))
3107 
3108! IF (minval(precisol_ns) .LT. zero) THEN
3109! WRITE (numout,*) 'BOOM water2infilt LT zero, minval =', (minval(water2infilt))
3110! ENDIF
3111   
3112    !! 2. We now deal with the changes of soiltile and corresponding soil moistures
3113    !!    Because sum(soiltile)=1 whatever vegtot, we need to distinguish two cases:
3114    !!    - when vegtot changes (meaning that the nobio fraction changes too),
3115    !!    - and when vegtot does not changes (a priori the most frequent case)
3116
3117    vegtot_upd = SUM(ABS((vegtot(:)-vegtot_old(:)))) .GT. zero ! True if at least one land point with a vegtot change
3118!write(numout,*) 'hydrol.f90 3103  vegtot upd =', vegtot_upd
3119!write(numout,*) 'hydrol.f90 3103 maxval runoff upd =', (maxval(runoff_upd))
3120!write(numout,*) 'hydrol.f90 3103 minval runoff upd =', (maxval(runoff_upd))
3121!write(numout,*) 'hydrol.f90 3103 maxval drain upd =', (maxval(drain_upd))
3122!write(numout,*) 'hydrol.f90 3103 minval drain upd =', (maxval(drain_upd))
3123
3124    runoff_upd(:) = zero
3125    drain_upd(:) = zero
3126    IF (vegtot_upd) THEN
3127       ! We find here the processing specific to the chnages of nobio fraction and vegtot
3128
3129       delvegtot(:) = vegtot(:) - vegtot_old(:)
3130
3131       DO jst=1,nstm
3132          DO ji=1,kjpindex
3133
3134             IF (delvegtot(ji) .GT. min_sechiba) THEN
3135
3136                !! 2.1. If vegtot increases (nobio decreases), then the mc in each soiltile is decreased
3137                !!      assuming the same proportions for each soiltile, and each soil layer
3138               
3139                mc(ji,:,jst) = mc(ji,:,jst) * vegtot_old(ji)/vegtot(ji) ! vegtot cannot be zero as > vegtot_old
3140                water2infilt(ji,jst) = water2infilt(ji,jst) * vegtot_old(ji)/vegtot(ji)
3141
3142             ELSE
3143
3144                !! 2.2 If vegtot decreases (nobio increases), then the mc in each soiltile should increase,
3145                !!     but should not exceed mcs
3146                !!     For simplicity, we choose to send the corresponding water volume to drainage
3147                !!     We do the same for water2infilt but send the excess to surface runoff
3148
3149                IF (vegtot(ji) .GT.min_sechiba) THEN
3150                   mcaux(ji,:,jst) =  mc(ji,:,jst) * (vegtot_old(ji)-vegtot(ji))/vegtot(ji) ! mcaux is the delta mc
3151                ELSE ! we just have nobio in the grid-cell
3152                   mcaux(ji,:,jst) =  mc(ji,:,jst)
3153                ENDIF
3154               
3155                drain_upd(ji) = drain_upd(ji) + dz(2) * ( trois*mcaux(ji,1,jst) + mcaux(ji,2,jst) )/huit
3156                DO jsl = 2,nslm-1
3157                   drain_upd(ji) = drain_upd(ji) + dz(jsl) * (trois*mcaux(ji,jsl,jst)+mcaux(ji,jsl-1,jst))/huit &
3158                        + dz(jsl+1) * (trois*mcaux(ji,jsl,jst)+mcaux(ji,jsl+1,jst))/huit
3159                ENDDO
3160                drain_upd(ji) = drain_upd(ji) + dz(nslm) * (trois*mcaux(ji,nslm,jst) + mcaux(ji,nslm-1,jst))/huit
3161
3162                IF (vegtot(ji) .GT.min_sechiba) THEN
3163                   runoff_upd(ji) = runoff_upd(ji) + water2infilt(ji,jst) * (vegtot_old(ji)-vegtot(ji))/vegtot(ji)
3164                ELSE ! we just have nobio in the grid-cell
3165                   runoff_upd(ji) = runoff_upd(ji) + water2infilt(ji,jst)
3166                ENDIF
3167
3168             ENDIF
3169             
3170          ENDDO
3171       ENDDO
3172       
3173    ENDIF
3174   
3175!       WRITE(numout,*) '3175 minval water2infilt =', (minval(water2infilt))
3176!       WRITE(numout,*) '3175 maxval water2infilt =', (maxval(water2infilt))
3177!       WRITE(numout,*) '3175 minval vegtot =', (minval(vegtot))
3178!       WRITE(numout,*) '3175 maxval vegtot =', (maxval(vegtot))
3179!       WRITE(numout,*) '3175 minval vegtot_old =', (minval(vegtot_old))
3180!       WRITE(numout,*) '3175 maxval vegtot_old =', (maxval(vegtot_old))
3181!       WRITE(numout,*) '3175 minval mc =', (minval(mc))
3182!       WRITE(numout,*) '3175 maxval mc =', (maxval(mc))
3183!       WRITE(numout,*) '3175 minval mcaux =', (minval(mcaux))
3184!       WRITE(numout,*) '3175 maxval mcaux =', (maxval(mcaux))
3185!       WRITE(numout,*) '3175 minval drain_upd =', (minval(drain_upd))
3186!       WRITE(numout,*) '3175 maxval drain_upd =', (maxval(drain_upd))
3187   
3188    !! 3. At the end of step 2, we are back to a case where vegtot changes are treated, so we can use soiltile
3189    !!    as a fraction of vegtot to process the mc transfers between soil tiles due to the changes of vegetation map
3190   
3191    !! 3.1 Check if soiltiles changed since last time step
3192    soil_upd=SUM(ABS(soiltile(:,:)-resdist(:,:))) .GT. zero
3193    IF (printlev>=3) WRITE (numout,*) 'soil_upd ', soil_upd
3194       
3195    IF (soil_upd) THEN
3196     
3197       !! 3.2 Define the change in soiltile
3198       vmr(:,:) = soiltile(:,:) - resdist(:,:)  ! resdist is the previous values of soiltiles, previous timestep, so before new map
3199
3200       ! Total area loss by the three soil tiles
3201       DO ji=1,kjpindex
3202          vmr_sum(ji)=SUM(vmr(ji,:),MASK=vmr(ji,:).LT.zero)
3203       ENDDO
3204
3205       !! 3.3 Shrinking soil tiles
3206       !! 3.3.1 Total loss of moisture content from the shrinking soil tiles, expressed by soil layer
3207       mc_dilu(:,:)=zero
3208       DO jst=1,nstm
3209          DO jsl = 1, nslm
3210             DO ji=1,kjpindex
3211                IF ( vmr(ji,jst) < -min_sechiba ) THEN
3212                   mc_dilu(ji,jsl) = mc_dilu(ji,jsl) + mc(ji,jsl,jst) * vmr(ji,jst) / vmr_sum(ji)
3213                ENDIF
3214             ENDDO
3215          ENDDO
3216       ENDDO
3217
3218       !! 3.3.2 Total loss of water2inft from the shrinking soil tiles
3219       infil_dilu(:)=zero
3220       DO jst=1,nstm
3221          DO ji=1,kjpindex
3222             IF ( vmr(ji,jst) < -min_sechiba ) THEN
3223                infil_dilu(ji) = infil_dilu(ji) + water2infilt(ji,jst) * vmr(ji,jst) / vmr_sum(ji)
3224             ENDIF
3225          ENDDO
3226       ENDDO
3227
3228       !! 3.4 Each gaining soil tile gets moisture proportionally to both the total loss and its areal increase
3229
3230       ! As the original mc from each soil tile are in [mcr,mcs] and we do weighted avrage, the new mc are in [mcr,mcs]
3231       ! The case where the soiltile is created (soiltile_old=0) works as the other cases
3232
3233       ! 3.4.1 Update mc(kjpindex,nslm,nstm) !m3/m3
3234       DO jst=1,nstm
3235          DO jsl = 1, nslm
3236             DO ji=1,kjpindex
3237                IF ( vmr(ji,jst) > min_sechiba ) THEN
3238                   mc(ji,jsl,jst) = ( mc(ji,jsl,jst) * resdist(ji,jst) + mc_dilu(ji,jsl) * vmr(ji,jst) ) / soiltile(ji,jst)
3239                   ! NB : soiltile can not be zero for case vmr > zero, see slowproc_veget
3240                ENDIF
3241             ENDDO
3242          ENDDO
3243       ENDDO
3244!
3245!       DO jst=1,nstm
3246!          IF ( vmr(1,jst) > zero ) THEN
3247!             WRITE(numout,*) 'zdcheck2 jst=',jst,'soiltile,resdist,vmr',soiltile(1,jst),resdist(1,jst),vmr(1,jst)
3248!          ENDIF
3249!       ENDDO
3250       
3251       ! 3.4.2 Update water2inft
3252       DO jst=1,nstm
3253          DO ji=1,kjpindex
3254             IF ( vmr(ji,jst) > min_sechiba ) THEN !donc soiltile>0     
3255                water2infilt(ji,jst) = ( water2infilt(ji,jst) * resdist(ji,jst) + infil_dilu(ji) * vmr(ji,jst) ) / soiltile(ji,jst)
3256             ENDIF !donc resdist>0
3257          ENDDO
3258       ENDDO
3259!  WRITE(numout,*) '3259 minval water2infilt =', (minval(water2infilt))
3260!  WRITE(numout,*) '3259 maxval water2infilt =', (maxval(water2infilt))
3261!  WRITE(numout,*) '3175 minval resdist =', (minval(resdist))
3262!  WRITE(numout,*) '3175 maxval resdist =', (maxval(resdist))
3263!  WRITE(numout,*) '3175 minval infil_dilu =', (minval(infil_dilu))
3264!  WRITE(numout,*) '3175 maxval infil_dilu =', (maxval(infil_dilu))
3265       ! 3.4.3 Case where soiltile < min_sechiba
3266       DO jst=1,nstm
3267          DO ji=1,kjpindex
3268             IF ( soiltile(ji,jst) .LT. min_sechiba ) THEN
3269                water2infilt(ji,jst) = zero
3270                mc(ji,:,jst) = zero
3271             ENDIF
3272          ENDDO
3273       ENDDO
3274!      IF (minval(mc) .LT. zero) THEN
3275!       WRITE (numout,*) 'BOOM mc LT zero 3233'
3276!      END IF
3277
3278    ENDIF ! soil_upd
3279
3280    !! 4. Update tmc and humtot
3281   
3282    DO jst=1,nstm
3283       DO ji=1,kjpindex
3284             tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
3285             DO jsl = 2,nslm-1
3286                tmc(ji,jst) = tmc(ji,jst) + dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
3287                     + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
3288             ENDDO
3289             tmc(ji,jst) = tmc(ji,jst) + dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
3290             tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
3291             ! WARNING tmc is increased by includes water2infilt(ji,jst)
3292       ENDDO
3293    ENDDO
3294
3295    humtot(:) = zero
3296    DO jst=1,nstm
3297       DO ji=1,kjpindex
3298          humtot(ji) = humtot(ji) + vegtot(ji) * soiltile(ji,jst) * tmc(ji,jst) ! average over grid-cell
3299       ENDDO
3300    ENDDO
3301
3302    !! 5. Check
3303    IF (check_cwrr) THEN
3304       DO ji=1,kjpindex
3305          test(ji) = SUM(tmc(ji,:)*soiltile(ji,:)*vegtot(ji)) - SUM(tmc_old(ji,:)*resdist(ji,:)*vegtot_old(ji)) + &
3306               SUM(qsintveg(ji,:)) - SUM(qsintveg_old(ji,:)) + (drain_upd(ji) + runoff_upd(ji))   
3307          IF ( ABS(test(ji)) .GT.  10.*allowed_err ) THEN
3308             WRITE(numout,*) 'tmc update WRONG: ji',ji
3309             WRITE(numout,*) 'tot water avant:',SUM(tmc_old(ji,:)*resdist(ji,:)*vegtot_old(ji)) + SUM(qsintveg_old(ji,:))
3310             WRITE(numout,*) 'tot water apres:',SUM(tmc(ji,:)*soiltile(ji,:)*vegtot(ji)) + SUM(qsintveg(ji,:))
3311             WRITE(numout,*) 'err:',test(ji)
3312             WRITE(numout,*) 'allowed_err:',allowed_err
3313             WRITE(numout,*) 'tmc:',tmc(ji,:)
3314             WRITE(numout,*) 'tmc_old:',tmc_old(ji,:)
3315             WRITE(numout,*) 'qsintveg:',qsintveg(ji,:)
3316             WRITE(numout,*) 'qsintveg_old:',qsintveg_old(ji,:)
3317             WRITE(numout,*) 'SUMqsintveg:',SUM(qsintveg(ji,:))
3318             WRITE(numout,*) 'SUMqsintveg_old:',SUM(qsintveg_old(ji,:))
3319             WRITE(numout,*) 'veget_max:',veget_max(ji,:)
3320             WRITE(numout,*) 'soiltile:',soiltile(ji,:)
3321             WRITE(numout,*) 'resdist:',resdist(ji,:)
3322             WRITE(numout,*) 'vegtot:',vegtot(ji)
3323             WRITE(numout,*) 'vegtot_old:',vegtot_old(ji)
3324             WRITE(numout,*) 'drain_upd:',drain_upd(ji)
3325             WRITE(numout,*) 'runoff_upd:',runoff_upd(ji)
3326             WRITE(numout,*) 'vmr:',vmr(ji,:)
3327             WRITE(numout,*) 'vmr_sum:',vmr_sum(ji)
3328             DO jst=1,nstm
3329                WRITE(numout,*) 'mc(',jst,'):',mc(ji,:,jst)
3330             ENDDO
3331             WRITE(numout,*) 'water2infilt:',water2infilt(ji,:)
3332             WRITE(numout,*) 'water2infilt_old:',water2infilt_old(ji,:)
3333             WRITE(numout,*) 'infil_dilu:',infil_dilu(ji)
3334             WRITE(numout,*) 'mc_dilu:',mc_dilu(ji,:)
3335
3336             error=.TRUE.
3337             CALL ipslerr_p(2, 'hydrol_tmc_update', 'Error in water balance', 'We STOP in the end of this subroutine','')
3338          ENDIF
3339       ENDDO
3340    ENDIF
3341
3342    !! Now that the work is done, update resdist
3343    resdist(:,:) = soiltile(:,:)
3344
3345    !
3346    !!  Exit if error was found previously in this subroutine
3347    !
3348    IF ( error ) THEN
3349       WRITE(numout,*) 'One or more errors have been detected in hydrol_tmc_update. Model stops.'
3350       CALL ipslerr_p(3, 'hydrol_tmc_update', 'We will STOP now.',&
3351                  & 'One or several fatal errors were found previously.','')
3352    END IF
3353
3354    IF (printlev>=3) WRITE (numout,*) ' hydrol_tmc_update done '
3355
3356  END SUBROUTINE hydrol_tmc_update
3357
3358
3359  SUBROUTINE hydrol_rotation_update( ip, kjpindex, rot_matrix, old_veget_max, veget_max, soiltile, qsintveg )
3360
3361    !! 0.1 Input variables
3362    INTEGER(i_std), INTENT(in)                          :: ip, kjpindex      !! domain size
3363    REAL(r_std),DIMENSION (nvm), INTENT (in)            :: old_veget_max     !! max fraction of vegetation type
3364    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max     !! max fraction of vegetation type
3365    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile      !! Fraction of each soil tile (0-1, unitless)
3366    REAL(r_std), DIMENSION (nvm, nvm), INTENT(in)       :: rot_matrix    !! rotation matrix
3367
3368    !! 0.3 Modified variables
3369    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)   :: qsintveg   !! Amount of water in the canopy interception
3370!    REAL(r_std), DIMENSION (kjpindex, nstm), INTENT(inout) :: resdist    !! Soiltile from previous time-step
3371!  resdist is defined in MODULE hydrol, no need to be put in the argument list
3372
3373    !! 0.4 Local variables
3374    INTEGER(i_std)                           :: ji, jv, jst, jst1, jst2, jsl, jsrc, jtar
3375    LOGICAL                                  :: soil_upd        !! True if soiltile changed since last time step
3376    LOGICAL                                  :: error=.FALSE.   !! If true, exit in the end of subroutine
3377!!    REAL(r_std), DIMENSION(kjpindex,nstm)    :: vmr             !! Change in soiltile
3378!!    REAL(r_std), DIMENSION(kjpindex)         :: vmr_sum
3379!!    REAL(r_std), DIMENSION(kjpindex,nslm)    :: mc_dilu         !! Total loss of moisture content
3380!!    REAL(r_std), DIMENSION(kjpindex)         :: infil_dilu      !! Total loss for water2infilt
3381!!    REAL(r_std), DIMENSION(kjpindex,nstm)    :: tmc_old         !! tmc before calculations
3382!!    REAL(r_std), DIMENSION(kjpindex,nstm)    :: water2infilt_old!! water2infilt before calculations
3383!!    REAL(r_std), DIMENSION (kjpindex,nvm)    :: qsintveg_old    !! qsintveg before calculations
3384!!    REAL(r_std), DIMENSION(kjpindex)         :: test
3385
3386    REAL(r_std), DIMENSION(nslm,nstm)    :: mc_dilu         !! Total loss of moisture content
3387    REAL(r_std), DIMENSION(nslm,nstm)    :: mc_old          !! temporary file to store mc
3388    REAL(r_std), DIMENSION(nstm)         :: infil_dilu      !! Total loss for water2infilt
3389    REAL(r_std), DIMENSION(nstm)    :: tmc_old         !! tmc before calculations
3390    REAL(r_std), DIMENSION(nstm)    :: water2infilt_old!! water2infilt before calculations
3391    REAL(r_std), DIMENSION(nvm)     :: qsintveg_old    !! qsintveg before calculations
3392    REAL(r_std), DIMENSION(nvm)     :: maxfrac, maxfrac_new
3393    REAL(r_std), DIMENSION(nstm,nstm) :: rot_matrix_tile !! relative portion of soil tile to be transferred
3394    REAL(r_std)                     :: test
3395
3396    !! 0. Check if soiltiles changed since last time step
3397!    soil_upd=SUM(ABS(soiltile(:,:)-resdist(:,:))) .GT. zero
3398    maxfrac = old_veget_max(:)
3399    maxfrac_new = old_veget_max(:)
3400    rot_matrix_tile(:,:) = 0.0
3401    DO jsrc = 1,nvm
3402        DO jtar = 1,nvm
3403            IF (rot_matrix(jsrc,jtar) .GT. 0.0) THEN
3404                maxfrac_new(jtar) = maxfrac_new(jtar) + maxfrac(jsrc) * rot_matrix(jsrc,jtar)
3405                maxfrac_new(jsrc) = maxfrac_new(jsrc) - maxfrac(jsrc) * rot_matrix(jsrc,jtar)
3406                jst1 = pref_soil_veg(jsrc)
3407                jst2 = pref_soil_veg(jtar)
3408                rot_matrix_tile(jst1,jst2) = rot_matrix_tile(jst1,jst2) + &
3409                    rot_matrix(jsrc,jtar) * maxfrac(jsrc) / resdist(ip, jst1 )
3410                IF ( (rot_matrix_tile(jst1,jst2) .GT. 1.0) .OR. &
3411                     (rot_matrix_tile(jst1,jst2) .LE. 0.0) ) THEN
3412                    !!!! make sure the fraction is in (0,1)
3413                    WRITE(numout,*) 'pref_soil_veg',pref_soil_veg
3414                    WRITE(numout,*) 'jsrc, jtar,', jsrc, jtar
3415                    WRITE(numout,*) 'jst1, jst2,', jst1, jst2
3416                    WRITE(numout,*) 'maxfrac(jsrc), rot_matrix(jsrc,jtar)', maxfrac(jsrc), rot_matrix(jsrc,jtar)
3417                    WRITE(numout,*) 'pref_soil_veg(jsrc), resdist(ip,pref_soil_veg(jsrc))', pref_soil_veg(jsrc), resdist(ip,pref_soil_veg(jsrc))
3418                    STOP 'soiltile error in hydrol_rotation'
3419                ENDIF
3420            ENDIF
3421        ENDDO
3422    ENDDO
3423
3424    !!!! check if the vegetation conversion is successful
3425    IF ( SUM(ABS(maxfrac_new - veget_max(ip,:))) .GT. min_sechiba ) THEN
3426        WRITE(numout,*) 'maxfrac',maxfrac
3427        WRITE(numout,*) 'maxfrac_new', maxfrac_new
3428        WRITE(numout,*) 'veget_max(ip,:)', veget_max(ip,:)
3429        STOP 'hydrol_rotation: fraction conversion error'
3430    ENDIF
3431    IF (printlev>=4) THEN
3432        WRITE(numout,*) 'xuhui: hydrol_rotation' 
3433        WRITE(numout,*) 'resdist(ip,:)', resdist(ip,:)
3434        WRITE(numout,*) 'soiltile(ip,:)', soiltile(ip,:)
3435        DO jsrc = 1,nstm 
3436            WRITE(numout,*) 'jsrc, rot_matrix_tile(jsrc,:)', jsrc, rot_matrix_tile(jsrc,:)
3437        ENDDO
3438    ENDIF
3439
3440    IF (SUM(rot_matrix) .GT. 0) THEN
3441        soil_upd = .TRUE.
3442    ENDIF
3443    IF (printlev>=3) WRITE (numout,*) 'soil_upd ', soil_upd
3444
3445    IF (check_cwrr) THEN
3446       ! Save soil moisture for later use
3447       tmc_old(:) = tmc(ip,:) 
3448       water2infilt_old(:) = water2infilt(ip,:)
3449       qsintveg_old(:) = qsintveg(ip,:)
3450    ENDIF
3451
3452    !! 1. If a PFT has disapperead as result from a veget_max change,
3453    !!    then add canopy water to surface water.
3454     DO jv=1,nvm
3455        IF ( (maxfrac_new(jv) .LT. min_sechiba) .AND.  (qsintveg(ip, jv) .GT. 0.0) )  THEN
3456            jst = pref_soil_veg(jv)
3457            water2infilt(ip,jst) = water2infilt(ip,jst) + qsintveg(ip,jv)/maxfrac(jv)
3458            qsintveg(ip,jv) = zero
3459        ENDIF
3460     ENDDO
3461! WRITE(numout,*) '3461 minval water2infilt =', (minval(water2infilt))
3462! WRITE(numout,*) '3461 maxval water2infilt =', (maxval(water2infilt))   
3463    mc_old = mc(ip,:,:)
3464    water2infilt_old(:) = water2infilt(ip,:)
3465    !! 2. Compute new soil moisture if soiltile changed
3466    IF (soil_upd) THEN
3467        DO jtar = 1,nstm
3468          mc_dilu(:,:) = zero
3469          infil_dilu(:) = zero
3470          IF ( SUM(rot_matrix_tile(:,jtar)) .GT. min_sechiba ) THEN
3471            DO jsrc = 1,nstm
3472              IF ( rot_matrix_tile(jsrc,jtar) .GT. min_sechiba ) THEN
3473                mc_dilu(:,jsrc) = mc_old(:,jsrc)
3474                infil_dilu(jsrc) = water2infilt_old(jsrc)
3475              ENDIF ! rot_matrix_tile(jsrc,jtar) > 0
3476            ENDDO
3477            !!! actually do the rotation
3478            mc(ip,:,jtar) = mc_old(:,jtar) * resdist(ip,jtar) * (1.0 - SUM(rot_matrix_tile(jtar,:)))
3479            water2infilt(ip,jtar) = water2infilt_old(jtar) * resdist(ip,jtar) * (1.0 - SUM(rot_matrix_tile(jtar,:)))
3480            DO jsrc = 1,nstm
3481                mc(ip,:,jtar) = mc(ip,:,jtar) + resdist(ip,jsrc) * rot_matrix_tile(jsrc,jtar) * mc_dilu(:,jsrc)
3482                water2infilt(ip,jtar) = water2infilt(ip,jtar) + resdist(ip,jsrc) * rot_matrix_tile(jsrc,jtar) * infil_dilu(jsrc)
3483            ENDDO
3484            IF ( soiltile(ip,jtar) .LE. 0. ) THEN
3485                WRITE(numout,*) 'jtar, soiltile(ip,jtar)',jtar, soiltile(ip,jtar)
3486                STOP 'hydrol_rotation_update: target tile has no proportion'
3487            ENDIF
3488            mc(ip,:,jtar) = mc(ip,:,jtar) / soiltile(ip,jtar)
3489            water2infilt(ip,jtar) = water2infilt(ip,jtar) / soiltile(ip,jtar)
3490          ENDIF ! SUM(rot_matrix_tile(:,jtar)) > 0
3491        ENDDO
3492
3493!        WRITE(numout,*) '3493 minval water2infilt =', (minval(water2infilt))
3494!       WRITE(numout,*) '3493 maxval water2infilt =', (maxval(water2infilt))
3495       
3496!      IF (minval(mc) .LT. zero) THEN
3497!       WRITE (numout,*) 'BOOM mc LT zero 3450'
3498!      END IF
3499     
3500       ! 2.3.3 Case where soiltile < min_sechiba
3501       DO jst=1,nstm
3502          IF ( soiltile(ip,jst) .LT. min_sechiba ) THEN
3503             water2infilt(ip,jst) = zero
3504             mc(ip,:,jst) = zero
3505          ENDIF
3506       ENDDO
3507!      IF (minval(mc) .LT. zero) THEN
3508!       WRITE (numout,*) 'BOOM mc LT zero 3461'
3509!      END IF
3510       IF (printlev>=4) THEN
3511            WRITE(numout,*) 'mc_old(1,:)',mc_old(1,:)
3512            WRITE(numout,*) 'mc(ip,1,:)',mc(ip,1,:)
3513            WRITE(numout,*) 'water2infilt_old(:)', water2infilt_old(:)
3514            WRITE(numout,*) 'water2infilt(ip,:)', water2infilt(ip,:)
3515       ENDIF
3516
3517
3518    ENDIF ! soil_upd
3519
3520
3521    !2.3.3 we compute tmc(kjpindex,nstm) and humtot!
3522    DO jst=1,nstm
3523         tmc(ip,jst) = dz(2) * ( trois*mc(ip,1,jst) + mc(ip,2,jst) )/huit
3524         DO jsl = 2,nslm-1
3525            tmc(ip,jst) = tmc(ip,jst) + dz(jsl) * (trois*mc(ip,jsl,jst)+mc(ip,jsl-1,jst))/huit &
3526                 + dz(jsl+1) * (trois*mc(ip,jsl,jst)+mc(ip,jsl+1,jst))/huit
3527         ENDDO
3528         tmc(ip,jst) = tmc(ip,jst) + dz(nslm) * (trois*mc(ip,nslm,jst) + mc(ip,nslm-1,jst))/huit
3529         tmc(ip,jst) = tmc(ip,jst) + water2infilt(ip,jst)
3530         ! WARNING tmc is increased by water2infilt(ip,jst), but mc is not modified !
3531    ENDDO
3532
3533    humtot(ip) = zero
3534    DO jst=1,nstm
3535        humtot(ip) = humtot(ip) + soiltile(ip,jst) * tmc(ip,jst)
3536    ENDDO
3537
3538    !! 4 check
3539    IF (check_cwrr) THEN
3540!       DO ji=1,kjpindex
3541        ji = ip
3542          test = ABS(SUM(tmc(ji,:)*soiltile(ji,:)) - SUM(tmc_old(:)*resdist(ji,:)) + &
3543               SUM(qsintveg(ji,:)) - SUM(qsintveg_old(:))) ! sum(soiltile)=1
3544          IF ( test .GT.  allowed_err ) THEN
3545             WRITE(numout,*) 'hydrol_rotation_update WRONG: ji',ji
3546             WRITE(numout,*) 'tot water before:',SUM(tmc_old(:)*resdist(ji,:)) + SUM(qsintveg_old(:))
3547             WRITE(numout,*) 'tot water after:',SUM(tmc(ji,:)*soiltile(ji,:)) + SUM(qsintveg(ji,:))
3548             WRITE(numout,*) 'err:',test
3549             WRITE(numout,*) 'allowed_err:',allowed_err
3550             WRITE(numout,*) 'tmc:',tmc(ji,:)
3551             WRITE(numout,*) 'tmc_old:',tmc_old(:)
3552             WRITE(numout,*) 'qsintveg:',qsintveg(ji,:)
3553             WRITE(numout,*) 'qsintveg_old:',qsintveg_old(:)
3554             WRITE(numout,*) 'SUMqsintveg:',SUM(qsintveg(ji,:))
3555             WRITE(numout,*) 'SUMqsintveg_old:',SUM(qsintveg_old(:))
3556             WRITE(numout,*) 'veget_max:',veget_max(ji,:)
3557             WRITE(numout,*) 'soiltile:',soiltile(ji,:)
3558             WRITE(numout,*) 'resdist:',resdist(ji,:)
3559             DO jst=1,nstm
3560                WRITE(numout,*) 'mc(',jst,'):',mc(ji,:,jst)
3561             ENDDO
3562             WRITE(numout,*) 'water2infilt:',water2infilt(ji,:)
3563             WRITE(numout,*) 'water2infilt_old:',water2infilt_old(:)
3564
3565             error=.TRUE.
3566             CALL ipslerr_p(2, 'hydrol_rotation_update', 'Error in water balance', 'We STOP in the end of this subroutine','')
3567          ENDIF
3568!       ENDDO
3569    ENDIF
3570
3571    !! Now that the work is done, update resdist
3572    resdist(:,:) = soiltile(:,:)
3573
3574    !
3575    !!  Exit if error was found previously in this subroutine
3576    !
3577    IF ( error ) THEN
3578       WRITE(numout,*) 'One or more errors have been detected in hydrol_tmc_update. Model stops.'
3579       CALL ipslerr_p(3, 'hydrol_tmc_update', 'We will STOP now.',&
3580                  & 'One or several fatal errors were found previously.','')
3581    END IF
3582
3583    IF (printlev>=3) WRITE (numout,*) ' hydrol_rotation_update done '
3584
3585  END SUBROUTINE hydrol_rotation_update
3586
3587!! ================================================================================================================================
3588!! SUBROUTINE   : hydrol_var_init
3589!!
3590!>\BRIEF        This routine initializes hydrologic parameters to define K and D, and diagnostic hydrologic variables. 
3591!!
3592!! DESCRIPTION  :
3593!! - 1 compute the depths
3594!! - 2 compute the profile for roots
3595!! - 3 compute the profile for ksat, a and n Van Genuchten parameter
3596!! - 4 compute the linearized values of k, a, b and d for the resolution of Fokker Planck equation
3597!! - 5 water reservoirs initialisation
3598!!
3599!! RECENT CHANGE(S) : None
3600!!
3601!! MAIN OUTPUT VARIABLE(S) :
3602!!
3603!! REFERENCE(S) :
3604!!
3605!! FLOWCHART    : None
3606!! \n
3607!_ ================================================================================================================================
3608!_ hydrol_var_init
3609
3610  SUBROUTINE hydrol_var_init (kjpindex, veget, veget_max, soiltile, njsc, &
3611       mx_eau_var, shumdiag_perma, &
3612       drysoil_frac, qsintveg, mc_layh, mcl_layh, tmc_layh, mc_layh_s, mcl_layh_s, tmc_layh_s, &
3613!gmjc
3614       tmc_topgrass, humcste_use, altmax)
3615!end gmjc
3616
3617    ! interface description
3618
3619    !! 0. Variable and parameter declaration
3620
3621    !! 0.1 Input variables
3622
3623    ! input scalar
3624    INTEGER(i_std), INTENT(in)                          :: kjpindex      !! Domain size (number of grid cells) (1)
3625    ! input fields
3626    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget_max     !! PFT fractions within grid-cells (1; 1)
3627    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: veget         !! Effective fraction of vegetation by PFT (1; 1)
3628    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)    :: njsc          !! Index of the dominant soil textural class
3629                                                                         !! in the grid cell (1-nscm, unitless)
3630    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in) :: soiltile      !! Fraction of each soil tile within vegtot (0-1, unitless)
3631
3632    !! 0.2 Output variables
3633
3634    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: mx_eau_var    !! Maximum water content of the soil
3635                                                                         !! @tex $(kg m^{-2})$ @endtex
3636    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out) :: shumdiag_perma!! Percent of porosity filled with water (mc/mcs)
3637                                                                         !! used for the thermal computations
3638    REAL(r_std),DIMENSION (kjpindex), INTENT (inout)    :: drysoil_frac  !! function of litter humidity
3639    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: mc_layh       !! Volumetric soil moisture content for each layer in hydrol(liquid+ice) [m3/m3]
3640    REAL(r_std), DIMENSION (kjpindex,nslm,nstm), INTENT (out):: mc_layh_s   !! Volumetric soil moisture content for each layer in hydrol(liquid+ice) [m3/m3]
3641    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: mcl_layh      !! Volumetric soil moisture content for each layer in hydrol(liquid) [m3/m3]
3642    REAL(r_std), DIMENSION (kjpindex,nslm,nstm), INTENT (out):: mcl_layh_s  !! Volumetric soil moisture content for each layer in hydrol(liquid) [m3/m3]
3643    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out):: tmc_layh      !! Total soil moisture content for each layer in hydrol(liquid+ice) [mm]
3644    REAL(r_std), DIMENSION (kjpindex,nslm,nstm), INTENT(out)  :: tmc_layh_s  !! total soil moisture content for each layer in hydrol and for each soiltile (mm)
3645
3646    !! 0.3 Modified variables
3647    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg    !! Water on vegetation due to interception
3648                                                                         !! @tex $(kg m^{-2})$ @endtex 
3649!gmjc top 5 layer grassland soil moisture for grazing
3650    REAL(r_std),DIMENSION (kjpindex), INTENT(out)       :: tmc_topgrass
3651!end gmjc
3652    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)  :: humcste_use
3653    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)   :: altmax
3654    !! 0.4 Local variables
3655
3656    INTEGER(i_std)                                      :: ji, jv, jp    !! Grid-cell and PFT indices (1)
3657    INTEGER(i_std)                                      :: jst, jsc, jsl !! Soiltile, Soil Texture, and Soil layer indices (1)
3658    INTEGER(i_std)                                      :: i, jd         !! Index (1)
3659    REAL(r_std)                                         :: m             !! m=1-1/n (unitless)
3660    REAL(r_std)                                         :: frac          !! Relative linearized VWC (unitless)
3661    REAL(r_std)                                         :: avan_mod      !! VG parameter a modified from  exponantial profile
3662                                                                         !! @tex $(mm^{-1})$ @endtex
3663    REAL(r_std)                                         :: nvan_mod      !! VG parameter n  modified from  exponantial profile
3664                                                                         !! (unitless)
3665    REAL(r_std), DIMENSION(nslm,nscm)                   :: afact, nfact  !! Multiplicative factor for decay of a and n with depth
3666                                                                         !! (unitless)
3667    ! parameters for "soil densification" with depth
3668    REAL(r_std)                                         :: dp_comp       !! Depth at which the 'compacted' value of ksat
3669                                                                         !! is reached (m)
3670    REAL(r_std)                                         :: f_ks          !! Exponential factor for decay of ksat with depth
3671                                                                         !! @tex $(m^{-1})$ @endtex
3672    ! Fixed parameters from fitted relationships
3673    REAL(r_std)                                         :: n0            !! fitted value for relation log((n-n0)/(n_ref-n0)) =
3674                                                                         !! nk_rel * log(k/k_ref)
3675                                                                         !! (unitless)
3676    REAL(r_std)                                         :: nk_rel        !! fitted value for relation log((n-n0)/(n_ref-n0)) =
3677                                                                         !! nk_rel * log(k/k_ref)
3678                                                                         !! (unitless)
3679    REAL(r_std)                                         :: a0            !! fitted value for relation log((a-a0)/(a_ref-a0)) =
3680                                                                         !! ak_rel * log(k/k_ref)
3681                                                                         !! @tex $(mm^{-1})$ @endtex
3682    REAL(r_std)                                         :: ak_rel        !! fitted value for relation log((a-a0)/(a_ref-a0)) =
3683                                                                         !! ak_rel * log(k/k_ref)
3684                                                                         !! (unitless)
3685    REAL(r_std)                                         :: kfact_max     !! Maximum factor for Ks decay with depth (unitless)
3686    REAL(r_std)                                         :: k_tmp, tmc_litter_ratio
3687    INTEGER(i_std), PARAMETER                           :: error_level = 3 !! Error level for consistency check
3688                                                                           !! Switch to 2 tu turn fatal errors into warnings
3689    INTEGER(i_std)                                      :: jiref           !! To identify the mc_lins where k_lin and d_lin
3690                                                                           !! need special treatment
3691    REAL(r_std)                                         :: nroot_tmp
3692    REAL(r_std)               :: zx1
3693
3694!_ ================================================================================================================================
3695
3696!!??Aurelien: Les 3 parametres qui suivent pourait peut-être mis dans hydrol_init?
3697    !
3698    !
3699    !Config Key   = CWRR_NKS_N0
3700    !Config Desc  = fitted value for relation log((n-n0)/(n_ref-n0)) = nk_rel * log(k/k_ref)
3701    !Config Def   = 0.95
3702    !Config If    = HYDROL_CWRR
3703    !Config Help  =
3704    !Config Units = [-]
3705    n0 = 0.95
3706    CALL getin_p("CWRR_NKS_N0",n0)
3707
3708    !! Check parameter value (correct range)
3709    IF ( n0 < zero ) THEN
3710       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3711            &     "Wrong parameter value for CWRR_NKS_N0.", &
3712            &     "This parameter should be non-negative. ", &
3713            &     "Please, check parameter value in run.def. ")
3714    END IF
3715
3716
3717    !Config Key   = CWRR_NKS_POWER
3718    !Config Desc  = fitted value for relation log((n-n0)/(n_ref-n0)) = nk_rel * log(k/k_ref)
3719    !Config Def   = 0.34
3720    !Config If    = HYDROL_CWRR
3721    !Config Help  =
3722    !Config Units = [-]
3723    nk_rel = 0.34
3724    CALL getin_p("CWRR_NKS_POWER",nk_rel)
3725
3726    !! Check parameter value (correct range)
3727    IF ( nk_rel < zero ) THEN
3728       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3729            &     "Wrong parameter value for CWRR_NKS_POWER.", &
3730            &     "This parameter should be non-negative. ", &
3731            &     "Please, check parameter value in run.def. ")
3732    END IF
3733
3734
3735    !Config Key   = CWRR_AKS_A0
3736    !Config Desc  = fitted value for relation log((a-a0)/(a_ref-a0)) = ak_rel * log(k/k_ref)
3737    !Config Def   = 0.00012
3738    !Config If    = HYDROL_CWRR
3739    !Config Help  =
3740    !Config Units = [1/mm]
3741    a0 = 0.00012
3742    CALL getin_p("CWRR_AKS_A0",a0)
3743
3744    !! Check parameter value (correct range)
3745    IF ( a0 < zero ) THEN
3746       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3747            &     "Wrong parameter value for CWRR_AKS_A0.", &
3748            &     "This parameter should be non-negative. ", &
3749            &     "Please, check parameter value in run.def. ")
3750    END IF
3751
3752
3753    !Config Key   = CWRR_AKS_POWER
3754    !Config Desc  = fitted value for relation log((a-a0)/(a_ref-a0)) = ak_rel * log(k/k_ref)
3755    !Config Def   = 0.53
3756    !Config If    = HYDROL_CWRR
3757    !Config Help  =
3758    !Config Units = [-]
3759    ak_rel = 0.53
3760    CALL getin_p("CWRR_AKS_POWER",ak_rel)
3761
3762    !! Check parameter value (correct range)
3763    IF ( nk_rel < zero ) THEN
3764       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3765            &     "Wrong parameter value for CWRR_AKS_POWER.", &
3766            &     "This parameter should be non-negative. ", &
3767            &     "Please, check parameter value in run.def. ")
3768    END IF
3769
3770
3771    !Config Key   = KFACT_DECAY_RATE
3772    !Config Desc  = Factor for Ks decay with depth
3773    !Config Def   = 2.0
3774    !Config If    = HYDROL_CWRR
3775    !Config Help  = 
3776    !Config Units = [1/m]
3777    f_ks = 2.0
3778    CALL getin_p ("KFACT_DECAY_RATE", f_ks)
3779
3780    !! Check parameter value (correct range)
3781    IF ( f_ks < zero ) THEN
3782       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3783            &     "Wrong parameter value for KFACT_DECAY_RATE.", &
3784            &     "This parameter should be positive. ", &
3785            &     "Please, check parameter value in run.def. ")
3786    END IF
3787
3788
3789    !Config Key   = KFACT_STARTING_DEPTH
3790    !Config Desc  = Depth for compacted value of Ks
3791    !Config Def   = 0.3
3792    !Config If    = HYDROL_CWRR
3793    !Config Help  = 
3794    !Config Units = [m]
3795    dp_comp = 0.3
3796    CALL getin_p ("KFACT_STARTING_DEPTH", dp_comp)
3797
3798    !! Check parameter value (correct range)
3799    IF ( dp_comp <= zero ) THEN
3800       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3801            &     "Wrong parameter value for KFACT_STARTING_DEPTH.", &
3802            &     "This parameter should be positive. ", &
3803            &     "Please, check parameter value in run.def. ")
3804    END IF
3805
3806
3807    !Config Key   = KFACT_MAX
3808    !Config Desc  = Maximum Factor for Ks increase due to vegetation
3809    !Config Def   = 10.0
3810    !Config If    = HYDROL_CWRR
3811    !Config Help  =
3812    !Config Units = [-]
3813    kfact_max = 10.0
3814    CALL getin_p ("KFACT_MAX", kfact_max)
3815
3816    !! Check parameter value (correct range)
3817    IF ( kfact_max < 10. ) THEN
3818       CALL ipslerr_p(error_level, "hydrol_var_init.", &
3819            &     "Wrong parameter value for KFACT_MAX.", &
3820            &     "This parameter should be greater than 10. ", &
3821            &     "Please, check parameter value in run.def. ")
3822    END IF
3823
3824   
3825    !-
3826    !! 1 Create local variables in mm for the vertical depths
3827    !!   Vertical depth variables (znh, dnh, dlh) are stored in module vertical_soil_var in m.
3828    DO jsl=1,nslm
3829       zz(jsl) = znh(jsl)*mille
3830       dz(jsl) = dnh(jsl)*mille
3831       dh(jsl) = dlh(jsl)*mille
3832    ENDDO
3833
3834    !! consider impacts of SOC on mcs,mcw,mcf
3835    mcs(:)=mcs_mineral(njsc(:))
3836    mcw(:)=mcw_mineral(njsc(:))
3837    mcf(:)=mcf_mineral(njsc(:))
3838
3839    IF (use_refSOC_hydrol) THEN
3840     IF (nscm .NE. 12) THEN
3841          CALL ipslerr_p(3, 'hydrol_var_init', 'Error: use_refSOC_hydrol=true only apply to USDA','','')
3842     ELSE
3843       zx1 = 0.
3844       DO ji = 1, kjpindex
3845          zx1 = MIN((refSOC_1d(ji)/soilc_max),1.) 
3846          mcs(ji) = zx1 * poros_org + (1.-zx1 )  * mcs_mineral(njsc(ji))
3847
3848          !! use Van Genuchten equation to calculate mcw and mcf
3849          mcw(ji) = mcr(njsc(ji)) + (mcs(ji)-mcr(njsc(ji)))/(1.+(VG_alpha(njsc(ji))*VG_psi_wp(njsc(ji)))**VG_n(njsc(ji)))**VG_m(njsc(ji))
3850          mcf(ji) = mcr(njsc(ji)) + (mcs(ji)-mcr(njsc(ji)))/(1.+(VG_alpha(njsc(ji))*VG_psi_fc(njsc(ji)))**VG_n(njsc(ji)))**VG_m(njsc(ji))
3851       ENDDO
3852     ENDIF
3853    ENDIF
3854
3855    !-
3856    !! 2 Compute the root density profile
3857    !! Note: if ok_dynroot, nroot is modified at each time step in hydrol_soil
3858    DO ji=1, kjpindex
3859      !-
3860      !! The three following equations concerning nroot computation are derived from the integrals
3861      !! of equations C9 to C11 of De Rosnay's (1999) PhD thesis (page 158).
3862      !! The occasional absence of minus sign before humcste parameter is correct.
3863      DO jv = 1,nvm
3864         nroot(ji,jv,1) = zero
3865
3866         humcste_use(ji,jv)=humcste(jv)
3867
3868         DO jsl = 2, nslm-1
3869            nroot(ji,jv,jsl) = (EXP(-humcste_use(ji,jv)*zz(jsl)/mille)) * &
3870                    & (EXP(humcste_use(ji,jv)*dz(jsl)/mille/deux) - &
3871                    & EXP(-humcste_use(ji,jv)*dz(jsl+1)/mille/deux))/ &
3872                    & (EXP(-humcste_use(ji,jv)*dz(2)/mille/deux) &
3873                    & -EXP(-humcste_use(ji,jv)*zz(nslm)/mille))
3874         ENDDO ! jsl = 2, nslm-1
3875
3876         nroot(ji,jv,nslm) = (EXP(humcste_use(ji,jv)*dz(nslm)/mille/deux) -un) * &
3877              & EXP(-humcste_use(ji,jv)*zz(nslm)/mille) / &
3878              & (EXP(-humcste_use(ji,jv)*dz(2)/mille/deux) &
3879              & -EXP(-humcste_use(ji,jv)*zz(nslm)/mille))
3880
3881         !! if ok_pc: nroot is set zero below ALT, and then re-normalized to 1 along the depth
3882!!SIMON commented ok_pc condition
3883!!         IF ( ok_pc ) THEN
3884           nroot_tmp=zero
3885           DO jsl = 1, nslm
3886             IF (znh(jsl) .LT. altmax(ji,jv)) THEN
3887               nroot_tmp =nroot_tmp+nroot(ji,jv,jsl)
3888             ELSEIF (altmax(ji,jv) .GT. zero) THEN
3889               nroot(ji,jv,jsl)=zero
3890             ENDIF
3891           ENDDO ! jsl = 1, nslm
3892           IF (nroot_tmp .GT. zero) nroot(ji,jv,:)=nroot(ji,jv,:)/nroot_tmp
3893!!         ENDIF ! ok_pc
3894
3895      ENDDO ! jv = 1,nvm
3896    ENDDO ! DO ji=1, kjpindex
3897
3898    !! for check
3899    IF ( ANY(ABS(SUM(nroot(:,:,:),DIM=3)-un) > min_sechiba) ) THEN
3900      WRITE(numout,*) 'WARNING in hydrol_var_init: nroot: vertical summation does not equal to 1'
3901    ENDIF
3902
3903    !-
3904    !! 3 Compute the profile for ksat, a and n
3905    !-
3906
3907    ! For every soil texture
3908    DO jsc = 1, nscm 
3909       DO jsl=1,nslm
3910          ! PhD thesis of d'Orgeval, 2006, p81, Eq. 4.38; d'Orgeval et al. 2008, Eq. 2
3911          ! Calibrated against Hapex-Sahel measurements
3912          kfact(jsl,jsc) = MIN(MAX(EXP(- f_ks * (zz(jsl)/mille - dp_comp)), un/kfact_max),un)
3913          ! PhD thesis of d'Orgeval, 2006, p81, Eqs. 4.39; 4.42, and Fig 4.14
3914         
3915          nfact(jsl,jsc) = ( kfact(jsl,jsc) )**nk_rel
3916          afact(jsl,jsc) = ( kfact(jsl,jsc) )**ak_rel
3917       ENDDO
3918    ENDDO
3919
3920    ! For every pixel
3921    DO jp = 1, kjpindex
3922       !-
3923       !! 4 compute the linearized values of k, a, b and d
3924       !-
3925       ! Calculate the matrix coef for Dublin model (de Rosnay, 1999; p149)
3926       ! piece-wise linearised hydraulic conductivity k_lin=alin * mc_lin + b_lin
3927       ! and diffusivity d_lin in each interval of mc, called mc_lin,
3928       ! between imin, for residual mcr, and imax for saturation mcs.
3929
3930       ! We define 51 bounds for 50 bins of mc between mcr and mcs
3931       mc_lin(imin,jp)=mcr(njsc(jp))
3932       mc_lin(imax,jp)=mcs(jp)
3933       DO ji= imin+1, imax-1 ! ji=2,50
3934          mc_lin(ji,jp) = mcr(njsc(jp)) + (ji-imin)*(mcs(jp)-mcr(njsc(jp)))/(imax-imin)
3935       ENDDO
3936
3937       DO jsl = 1, nslm
3938          ! From PhD thesis of d'Orgeval, 2006, p81, Eq. 4.42
3939          nvan_mod = n0 + (nvan(njsc(jp))-n0) * nfact(jsl,njsc(jp))
3940          avan_mod = a0 + (avan(njsc(jp))-a0) * afact(jsl,njsc(jp))
3941          m = un - un / nvan_mod
3942          ! We apply Van Genuchten equation for K(theta) based on Ks(z)=ks(jsc) * kfact(jsl,jsc)
3943          DO ji = imax,imin,-1 
3944             frac=MIN(un,(mc_lin(ji,jp)-mcr(njsc(jp)))/(mcs(jp)-mcr(njsc(jp))))
3945             k_lin(ji,jsl,jp) = ks(njsc(jp)) * kfact(jsl,njsc(jp)) * (frac**0.5) * ( un - ( un - frac ** (un/m)) ** m )**2
3946          ENDDO
3947
3948          ! k_lin should not be zero, nor too small
3949          ! We track jiref, the bin under which mc is too small and we may get zero k_lin     
3950          ji=imax-1
3951          DO WHILE ((k_lin(ji,jsl,jp) > 1.e-32) .and. (ji>0))
3952             jiref=ji
3953             ji=ji-1
3954          ENDDO
3955          DO ji=jiref-1,imin,-1
3956             k_lin(ji,jsl,jp)=k_lin(ji+1,jsl,jp)/10.
3957          ENDDO
3958         
3959          DO ji = imin,imax-1 ! ji=1,50
3960             ! We deduce a_lin and b_lin based on continuity between segments k_lin = a_lin*mc-lin+b_lin
3961             a_lin(ji,jsl,jp) = (k_lin(ji+1,jsl,jp)-k_lin(ji,jsl,jp)) / (mc_lin(ji+1,jp)-mc_lin(ji,jp))
3962             b_lin(ji,jsl,jp)  = k_lin(ji,jsl,jp) - a_lin(ji,jsl,jp)*mc_lin(ji,jp)
3963
3964             ! We calculate the d_lin for each mc bin, from Van Genuchten equation for D(theta)
3965             ! d_lin is constant and taken as the arithmetic mean between the values at the bounds of each bin
3966             IF (ji.NE.imin .AND. ji.NE.imax-1) THEN
3967                frac=MIN(un,(mc_lin(ji,jp)-mcr(njsc(jp)))/(mcs(jp)-mcr(njsc(jp))))
3968                d_lin(ji,jsl,jp) =(k_lin(ji,jsl,jp) / (avan_mod*m*nvan_mod)) *  &
3969                     ( (frac**(-un/m))/(mc_lin(ji,jp)-mcr(njsc(jp))) ) * &
3970                     (  frac**(-un/m) -un ) ** (-m)
3971                frac=MIN(un,(mc_lin(ji+1,jp)-mcr(njsc(jp)))/(mcs(jp)-mcr(njsc(jp))))
3972                d_lin(ji+1,jsl,jp) =(k_lin(ji+1,jsl,jp) / (avan_mod*m*nvan_mod))*&
3973                     ( (frac**(-un/m))/(mc_lin(ji+1,jp)-mcr(njsc(jp))) ) * &
3974                     (  frac**(-un/m) -un ) ** (-m)
3975                d_lin(ji,jsl,jp) = undemi * (d_lin(ji,jsl,jp)+d_lin(ji+1,jsl,jp))
3976             ELSE IF(ji.EQ.imax-1) THEN
3977                d_lin(ji,jsl,jp) =(k_lin(ji,jsl,jp) / (avan_mod*m*nvan_mod)) * &
3978                     ( (frac**(-un/m))/(mc_lin(ji,jp)-mcr(njsc(jp))) ) *  &
3979                     (  frac**(-un/m) -un ) ** (-m)
3980             ENDIF
3981          ENDDO
3982
3983          ! Special case for ji=imin
3984          d_lin(imin,jsl,jp) = d_lin(imin+1,jsl,jp)/1000.
3985
3986          ! We adjust d_lin where k_lin was previously adjusted otherwise we might get non-monotonous variations
3987          ! We don't want d_lin = zero
3988          DO ji=jiref-1,imin,-1
3989             d_lin(ji,jsl,jp)=d_lin(ji+1,jsl,jp)/10.
3990          ENDDO
3991
3992       ENDDO
3993    ENDDO
3994   
3995
3996    !! 5 Water reservoir initialisation
3997    !
3998!!$    DO jst = 1,nstm
3999!!$       DO ji = 1, kjpindex
4000!!$          mx_eau_var(ji) = mx_eau_var(ji) + soiltile(ji,jst)*&
4001!!$               &   zmaxh*mille*mcs(njsc(ji))
4002!!$       END DO
4003!!$    END DO
4004!!$    IF (check_CWRR) THEN
4005!!$       IF ( ANY ( ABS( mx_eau_var(:) - zmaxh*mille*mcs(njsc(:)) ) > min_sechiba ) ) THEN
4006!!$          ji=MAXLOC ( ABS( mx_eau_var(:) - zmaxh*mille*mcs(njsc(:)) ) , 1)
4007!!$          WRITE(numout, *) "Erreur formule simplifiée mx_eau_var ! ", mx_eau_var(ji), zmaxh*mille*mcs(njsc(ji))
4008!!$          WRITE(numout, *) "err = ",ABS(mx_eau_var(ji) - zmaxh*mille*mcs(njsc(ji)))
4009!!$          STOP 1
4010!!$       ENDIF
4011!!$    ENDIF
4012
4013    mx_eau_var(:) = zero
4014    mx_eau_var(:) = zmaxh*mille*mcs(:) 
4015
4016    DO ji = 1,kjpindex 
4017       IF (vegtot(ji) .LE. zero) THEN
4018          mx_eau_var(ji) = mx_eau_nobio*zmaxh
4019          ! Aurelien: what does vegtot=0 mean? is it like frac_nobio=1? But if 0<frac_nobio<1 ???
4020       ENDIF
4021
4022    END DO
4023
4024    ! Compute the litter humidity, shumdiag and fry
4025    shumdiag_perma(:,:) = zero
4026    humtot(:) = zero
4027    tmc(:,:) = zero
4028!gmjc top 5 layer grassland soil moisture for grazing
4029    tmc_topgrass(:) = zero
4030!end gmjc
4031
4032    ! Loop on soiltiles to compute the variables (ji,jst)
4033    DO jst=1,nstm 
4034       DO ji = 1, kjpindex
4035          tmcs(ji,jst)=zmaxh* mille*mcs(ji)
4036          tmcr(ji,jst)=zmaxh* mille*mcr(njsc(ji))
4037       ENDDO
4038    ENDDO
4039       
4040    ! The total soil moisture for each soiltile:
4041    DO jst=1,nstm
4042       DO ji=1,kjpindex
4043          tmc(ji,jst)= dz(2) * ( trois*mc(ji,1,jst)+ mc(ji,2,jst))/huit
4044       END DO
4045    ENDDO
4046
4047    DO jst=1,nstm 
4048       DO jsl=2,nslm-1
4049          DO ji=1,kjpindex
4050             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) * ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
4051                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
4052          END DO
4053       END DO
4054    ENDDO
4055
4056    DO jst=1,nstm 
4057       DO ji=1,kjpindex
4058          tmc(ji,jst) = tmc(ji,jst) +  dz(nslm) * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
4059          tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
4060       ENDDO
4061    END DO
4062
4063!JG: hydrol_tmc_update should not be called in the initialization phase. Call of hydrol_tmc_update makes the model restart differenlty.   
4064!    ! If veget has been updated before restart (with LAND USE or DGVM),
4065!    ! tmc and mc must be modified with respect to humtot conservation.
4066!   CALL hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg)
4067
4068    ! The litter variables:
4069    ! level 1
4070    DO jst=1,nstm 
4071       DO ji=1,kjpindex
4072          tmc_litter(ji,jst) = dz(2) * (trois*mc(ji,1,jst)+mc(ji,2,jst))/huit
4073!gmjc top 5 layer mc for grazing
4074          tmc_trampling(ji,jst) = dz(2) *(trois*mc(ji,1,jst)+mc(ji,2,jst))/huit
4075!end gmjc
4076          tmc_litter_wilt(ji,jst) = dz(2) * mcw(ji) / deux
4077          tmc_litter_res(ji,jst) = dz(2) * mcr(njsc(ji)) / deux
4078          tmc_litter_field(ji,jst) = dz(2) * mcf(ji) / deux
4079          tmc_litter_sat(ji,jst) = dz(2) * mcs(ji) / deux
4080          tmc_litter_awet(ji,jst) = dz(2) * mc_awet(njsc(ji)) / deux
4081          tmc_litter_adry(ji,jst) = dz(2) * mc_adry(njsc(ji)) / deux
4082       ENDDO
4083    END DO
4084!gmjc top 5 layer mc for grazing
4085    ! sum from level 2 to 5
4086    DO jst=1,nstm
4087       DO jsl=2,6
4088          DO ji=1,kjpindex
4089             tmc_trampling(ji,jst) = tmc_trampling(ji,jst) + dz(jsl) * &
4090                  & ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
4091                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
4092          END DO
4093       END DO
4094    END DO
4095!end gmjc
4096    ! sum from level 2 to 4
4097    DO jst=1,nstm 
4098       DO jsl=2,4
4099          DO ji=1,kjpindex
4100             tmc_litter(ji,jst) = tmc_litter(ji,jst) + dz(jsl) * & 
4101                  & ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
4102                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
4103             tmc_litter_wilt(ji,jst) = tmc_litter_wilt(ji,jst) + &
4104                  &(dz(jsl)+ dz(jsl+1))*& 
4105                  & mcw(ji)/deux
4106             tmc_litter_res(ji,jst) = tmc_litter_res(ji,jst) + &
4107                  &(dz(jsl)+ dz(jsl+1))*& 
4108                  & mcr(njsc(ji))/deux
4109             tmc_litter_sat(ji,jst) = tmc_litter_sat(ji,jst) + &
4110                  &(dz(jsl)+ dz(jsl+1))* & 
4111                  & mcs(ji)/deux
4112             tmc_litter_field(ji,jst) = tmc_litter_field(ji,jst) + &
4113                  & (dz(jsl)+ dz(jsl+1))* & 
4114                  & mcf(ji)/deux
4115             tmc_litter_awet(ji,jst) = tmc_litter_awet(ji,jst) + &
4116                  &(dz(jsl)+ dz(jsl+1))* & 
4117                  & mc_awet(njsc(ji))/deux
4118             tmc_litter_adry(ji,jst) = tmc_litter_adry(ji,jst) + &
4119                  & (dz(jsl)+ dz(jsl+1))* & 
4120                  & mc_adry(njsc(ji))/deux
4121          END DO
4122       END DO
4123    END DO
4124
4125    ! Soil wetness profiles (W-Ww)/(Ws-Ww)
4126    DO jst=1,nstm 
4127       DO ji=1,kjpindex
4128          soil_wet(ji,1,jst) = MIN(un, MAX(zero,&
4129               &(trois*mc(ji,1,jst) + mc(ji,2,jst) - quatre*mcw(ji))&
4130               & /(quatre*(mcs(ji)-mcw(ji))) ))
4131          ! here we set that humrelv=0 in PFT1
4132          humrelv(ji,1,jst) = zero
4133       ENDDO
4134    END DO
4135
4136    DO jst=1,nstm 
4137       DO jsl=2,nslm-1
4138          DO ji=1,kjpindex
4139             soil_wet(ji,jsl,jst) = MIN(un, MAX(zero,&
4140                  & (trois*mc(ji,jsl,jst) + & 
4141                  & mc(ji,jsl-1,jst) *(dz(jsl)/(dz(jsl)+dz(jsl+1))) &
4142                  & + mc(ji,jsl+1,jst)*(dz(jsl+1)/(dz(jsl)+dz(jsl+1))) &
4143                  & - quatre*mcw(ji)) / (quatre*(mcs(ji)-mcw(ji))) ))
4144          END DO
4145       END DO
4146    END DO
4147
4148    DO jst=1,nstm 
4149       DO ji=1,kjpindex
4150          soil_wet(ji,nslm,jst) = MIN(un, MAX(zero,&
4151               & (trois*mc(ji,nslm,jst) &
4152               & + mc(ji,nslm-1,jst)-quatre*mcw(ji))/(quatre*(mcs(ji)-mcw(ji))) ))
4153       ENDDO
4154    END DO
4155
4156!gmjc top 5 layer grassland soil moisture for grazing
4157    tmc_topgrass(:) = tmc_trampling(:,3)/(SUM(dz(1:6))+dz(7)/2)
4158!WRITE (numout,*) 'sechiba inittmc_topgrass',tmc_topgrass
4159!end gmjc
4160    ! Calculate frac_hydro_diag for interpolation between hydrological and diagnostic axes
4161    CALL hydrol_calculate_frac_hydro_diag
4162
4163    ! Calculate shumdiag_perma (at diagnostic levels)
4164    ! Use resdist instead of soiltile because we here need to have
4165    ! shumdiag_perma at the value from previous time step.
4166    ! Here, soilmoist is only used as a temporary variable to calculate shumdiag_perma
4167    ! (based on resdist=soiltile from previous timestep, but normally equal to soiltile)
4168    ! For consistency with hydrol_soil, we want to calculate a grid-cell average
4169    soilmoist(:,:) = zero
4170    DO jst=1,nstm
4171       DO ji=1,kjpindex
4172          soilmoist(ji,1) = soilmoist(ji,1) + resdist(ji,jst) * &
4173               dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
4174          DO jsl = 2,nslm-1
4175             soilmoist(ji,jsl) = soilmoist(ji,jsl) + resdist(ji,jst) * &
4176                  ( dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
4177                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit )
4178          END DO
4179          soilmoist(ji,nslm) = soilmoist(ji,nslm) + resdist(ji,jst) * &
4180               dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
4181       ENDDO
4182    ENDDO
4183    DO ji=1,kjpindex
4184        soilmoist(ji,:) = soilmoist(ji,:) * vegtot_old(ji) ! grid cell average
4185    ENDDO
4186   
4187    ! -- shumdiag_perma for restart
4188    !  For consistency with hydrol_soil, we want to calculate a grid-cell average
4189    DO jd=1,nbdl
4190       DO ji=1,kjpindex       
4191          DO jsl = 1, nslm
4192             shumdiag_perma(ji,jd) = soilmoist(ji,jsl)*frac_hydro_diag(jsl,jd) &
4193                  /(dh(jsl)*mcs(ji))
4194          ENDDO
4195          shumdiag_perma(ji,jd) = MAX(MIN(shumdiag_perma(ji,jd), un), zero) 
4196       ENDDO
4197    ENDDO
4198               
4199    ! Calculate drysoil_frac if it was not found in the restart file
4200    ! For simplicity, we set drysoil_frac to 0.5 in this case
4201    IF (ALL(drysoil_frac(:) == val_exp)) THEN
4202       DO ji=1,kjpindex
4203          drysoil_frac(ji) = 0.5
4204       END DO
4205    END IF
4206
4207    profil_froz_hydro_ns(:,:,:) = 0.0
4208    IF (ok_freeze_cwrr) THEN
4209       profil_froz_hydro(:,:) = 0.0
4210       temp_hydro(:,:) = 0.0
4211    ENDIF
4212   
4213    !! Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in
4214    !! thermosoil for the thermal conductivity. Calculate also total soil moisture content(tmc_layh)
4215    !! needed in thermosoil for the heat capacity.
4216    ! These values are only used in thermosoil_init in absence of a restart file
4217    ! For this case, we calculate them based on mc and mcl from the restart files,
4218    ! and vegtot and soiltile which correspond to the new vegetation map
4219    ! This creates a little inconsistency (since mc corresponds to the previous vegetation map)
4220    ! but it's not important since it's just when we start from scratch
4221    !! The multiplication by vegtot creates grid-cell average values *** to be checked for consistency with thermosoil
4222    mc_layh(:,:) = zero
4223    mcl_layh(:,:) = zero
4224    tmc_layh(:,:) = zero
4225    mc_layh_s(:,:,:) = zero
4226    mcl_layh_s(:,:,:) = zero
4227    tmc_layh_s(:,:,:) = zero
4228   
4229    mc_layh_s = mc
4230    mcl_layh_s = mc
4231    DO jst=1,nstm
4232      DO ji=1,kjpindex
4233         DO jsl=1,nslm
4234            mc_layh(ji,jsl) = mc_layh(ji,jsl) + mc(ji,jsl,jst) * soiltile(ji,jst)  * vegtot(ji)
4235            mcl_layh(ji,jsl) = mcl_layh(ji,jsl) + mcl(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji)
4236         ENDDO
4237         tmc_layh_s(ji,1,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit 
4238         DO jsl = 2,nslm-1
4239            tmc_layh_s(ji,jsl,jst) = dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
4240                + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit 
4241         ENDDO
4242         tmc_layh_s(ji,nslm,jst) = dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
4243         DO jsl = 1,nslm
4244            tmc_layh(ji,jsl) = tmc_layh(ji,jsl) + tmc_layh_s(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji)
4245         ENDDO
4246      END DO
4247    END DO
4248
4249!      IF (minval(tmc_layh_s) .LT. zero) THEN
4250!       WRITE (numout,*) 'BOOM tmc_layh_s LT zero!!'
4251!       ENDIF
4252
4253    IF (printlev>=3) WRITE (numout,*) ' hydrol_var_init done '
4254
4255  END SUBROUTINE hydrol_var_init
4256
4257
4258!! ================================================================================================================================
4259!! SUBROUTINE   : hydrol_snow
4260!!
4261!>\BRIEF        This routine computes snow processes.
4262!!
4263!! DESCRIPTION  :
4264!! - 0 initialisation
4265!! - 1 On vegetation
4266!! - 1.1 Compute snow masse
4267!! - 1.2 Sublimation
4268!! - 1.2.1 Check that sublimation on the vegetated fraction is possible.
4269!! - 1.3. snow melt only if temperature positive
4270!! - 1.3.1 enough snow for melting or not
4271!! - 1.3.2 not enough snow
4272!! - 1.3.3 negative snow - now snow melt
4273!! - 1.4 Snow melts only on weight glaciers
4274!! - 2 On Land ice
4275!! - 2.1 Compute snow
4276!! - 2.2 Sublimation
4277!! - 2.3 Snow melt only for continental ice fraction
4278!! - 2.3.1 If there is snow on the ice-fraction it can melt
4279!! - 2.4 Snow melts only on weight glaciers
4280!! - 3 On other surface types - not done yet
4281!! - 4 computes total melt (snow and ice)
4282!! - 5 computes snow age on veg and ice (for albedo)
4283!! - 5.1 Snow age on vegetation
4284!! - 5.2 Snow age on ice
4285!! - 6 Diagnose the depth of the snow layer
4286!!
4287!! RECENT CHANGE(S) : None
4288!!
4289!! MAIN OUTPUT VARIABLE(S) :
4290!!
4291!! REFERENCE(S) :
4292!!
4293!! FLOWCHART    : None
4294!! \n
4295!_ ================================================================================================================================
4296!_ hydrol_snow
4297
4298  SUBROUTINE hydrol_snow (kjpindex, precip_rain, precip_snow , temp_sol_new, soilcap,&
4299       & frac_nobio, totfrac_nobio, vevapsno, snow, snow_age, snow_nobio, snow_nobio_age, &
4300       & tot_melt, snowdepth,snowmelt)
4301
4302    !
4303    ! interface description
4304
4305    !! 0. Variable and parameter declaration
4306
4307    !! 0.1 Input variables
4308
4309    ! input scalar
4310    INTEGER(i_std), INTENT(in)                               :: kjpindex      !! Domain size
4311    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_rain   !! Rainfall
4312    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_snow   !! Snow precipitation
4313    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: temp_sol_new  !! New soil temperature
4314    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: soilcap       !! Soil capacity
4315    REAL(r_std), DIMENSION (kjpindex,nnobio), INTENT(in)     :: frac_nobio    !! Fraction of continental ice, lakes, ...
4316    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: totfrac_nobio !! Total fraction of continental ice+lakes+ ...
4317
4318    !! 0.2 Output variables
4319
4320    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: tot_melt      !! Total melt from snow and ice 
4321    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: snowmelt      !! Snow melt
4322    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: snowdepth     !! Snow depth
4323
4324    !! 0.3 Modified variables
4325
4326    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapsno      !! Snow evaporation
4327    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: snow          !! Snow mass [Kg/m^2]
4328    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: snow_age      !! Snow age
4329    REAL(r_std), DIMENSION (kjpindex,nnobio), INTENT(inout)  :: snow_nobio    !! Ice water balance
4330    REAL(r_std), DIMENSION (kjpindex,nnobio), INTENT(inout)  :: snow_nobio_age!! Snow age on ice, lakes, ...
4331
4332    !! 0.4 Local variables
4333
4334    INTEGER(i_std)                               :: ji, jv
4335    REAL(r_std), DIMENSION (kjpindex)             :: d_age  !! Snow age change
4336    REAL(r_std), DIMENSION (kjpindex)             :: xx     !! temporary
4337    REAL(r_std)                                   :: snowmelt_tmp !! The name says it all !
4338    REAL(r_std)                                   :: snow_d1k !! The amount of snow that corresponds to a 1K cooling
4339
4340!_ ================================================================================================================================
4341
4342    !
4343    ! for continental points
4344    !
4345
4346    !
4347    !!_0 initialisation
4348    !
4349    DO jv = 1, nnobio
4350       DO ji=1,kjpindex
4351          subsnownobio(ji,jv) = zero
4352       ENDDO
4353    ENDDO
4354    DO ji=1,kjpindex
4355       subsnowveg(ji) = zero
4356       snowmelt(ji) = zero
4357       icemelt(ji) = zero
4358       subsinksoil(ji) = zero
4359       tot_melt(ji) = zero
4360    ENDDO
4361    !
4362    !! 1 On vegetation
4363    IF (ANY(vevapsno < -10e+30)) CALL ipslerr_p(3, 'hydrol_snow', 'vevapsno is too big', '', '')
4364    !
4365    DO ji=1,kjpindex
4366       !
4367    !! 1.1 Compute snow masse
4368       !
4369       snow(ji) = snow(ji) + (un - totfrac_nobio(ji))*precip_snow(ji)
4370       !
4371       !
4372    !! 1.2 Sublimation
4373       !      Separate between vegetated and no-veget fractions
4374       !      Care has to be taken as we might have sublimation from the
4375       !      the frac_nobio while there is no snow on the rest of the grid.
4376       !
4377       IF ( snow(ji) > snowcri ) THEN
4378          subsnownobio(ji,iice) = frac_nobio(ji,iice)*vevapsno(ji)
4379          subsnowveg(ji) = vevapsno(ji) - subsnownobio(ji,iice)
4380       ELSE
4381          ! Correction Nathalie - Juillet 2006.
4382          ! On doit d'abord tester s'il existe un frac_nobio!
4383          ! Pour le moment je ne regarde que le iice
4384          IF ( frac_nobio(ji,iice) .GT. min_sechiba) THEN
4385             subsnownobio(ji,iice) = vevapsno(ji)
4386             subsnowveg(ji) = zero
4387          ELSE
4388             subsnownobio(ji,iice) = zero
4389             subsnowveg(ji) = vevapsno(ji)
4390          ENDIF
4391       ENDIF
4392       ! here vevapsno bas been separated into a bio and nobio fractions, without changing the total
4393       !
4394       !
4395    !! 1.2.1 Check that sublimation on the vegetated fraction is possible.
4396       !
4397       IF (subsnowveg(ji) .GT. snow(ji)) THEN
4398          ! What could not be sublimated goes into subsinksoil
4399          IF( (un - totfrac_nobio(ji)).GT.min_sechiba) THEN
4400             subsinksoil (ji) = (subsnowveg(ji) - snow(ji))/ (un - totfrac_nobio(ji))
4401          END IF
4402          ! Sublimation is thus limited to what is available
4403          ! Then, evavpsnow is reduced, of subsinksoil
4404          subsnowveg(ji) = snow(ji)
4405          snow(ji) = zero
4406          vevapsno(ji) = subsnowveg(ji) + subsnownobio(ji,iice)
4407       ELSE
4408          snow(ji) = snow(ji) - subsnowveg(ji)
4409       ENDIF
4410       !
4411    !! 1.3. snow melt only if temperature positive
4412       !
4413       IF (temp_sol_new(ji).GT.tp_00) THEN
4414          !
4415          IF (snow(ji).GT.sneige) THEN
4416             !
4417             snowmelt(ji) = (un - frac_nobio(ji,iice))*(temp_sol_new(ji) - tp_00) * soilcap(ji) / chalfu0
4418             !
4419    !! 1.3.1 enough snow for melting or not
4420             !
4421             IF (snowmelt(ji).LT.snow(ji)) THEN
4422                snow(ji) = snow(ji) - snowmelt(ji)
4423             ELSE
4424                snowmelt(ji) = snow(ji)
4425                snow(ji) = zero
4426             END IF
4427             !
4428          ELSEIF (snow(ji).GE.zero) THEN
4429             !
4430    !! 1.3.2 not enough snow
4431             !
4432             snowmelt(ji) = snow(ji)
4433             snow(ji) = zero
4434          ELSE
4435             !
4436    !! 1.3.3 negative snow - now snow melt
4437             !
4438             snow(ji) = zero
4439             snowmelt(ji) = zero
4440             WRITE(numout,*) 'hydrol_snow: WARNING! snow was negative and was reset to zero. '
4441             !
4442          END IF
4443
4444       ENDIF
4445    !! 1.4 Snow melts above a threshold
4446       ! Ice melt only if there is more than a given mass : maxmass_snow,
4447       ! But the snow cannot melt more in one time step to what corresponds to
4448       ! a 1K cooling. This will lead to a progressive melting of snow above
4449       ! maxmass_snow but it is needed as a too strong cooling can destabilise the model.
4450       IF ( snow(ji) .GT. maxmass_snow ) THEN
4451          snow_d1k = un * soilcap(ji) / chalfu0
4452          snowmelt(ji) = snowmelt(ji) + MIN((snow(ji) - maxmass_snow),snow_d1k)
4453          snow(ji) = snow(ji) - snowmelt(ji)
4454          IF ( printlev >= 3 ) WRITE (numout,*) "Snow was above maxmass_snow (", maxmass_snow,") and we melted ", snowmelt(ji)
4455       ENDIF
4456       
4457    END DO
4458    IF (ANY(vevapsno < -10e+30)) CALL ipslerr_p(3, 'hydrol_snow', 'vevapsno is too big', '', '')
4459    !
4460    !! 2 On Land ice
4461    !
4462    DO ji=1,kjpindex
4463       !
4464    !! 2.1 Compute snow
4465       !
4466       !!??Aurelien: pkoi mettre precip_rain en dessous? We considere liquid precipitations becomes instantly snow? 
4467       snow_nobio(ji,iice) = snow_nobio(ji,iice) + frac_nobio(ji,iice)*precip_snow(ji) + &
4468            & frac_nobio(ji,iice)*precip_rain(ji)
4469       !
4470    !! 2.2 Sublimation
4471       !      Was calculated before it can give us negative snow_nobio but that is OK
4472       !      Once it goes below a certain values (-maxmass_snow for instance) we should kill
4473       !      the frac_nobio(ji,iice) !
4474       !
4475       snow_nobio(ji,iice) = snow_nobio(ji,iice) - subsnownobio(ji,iice)
4476       !
4477    !! 2.3 Snow melt only for continental ice fraction
4478       !
4479       snowmelt_tmp = zero
4480       IF (temp_sol_new(ji) .GT. tp_00) THEN
4481          !
4482    !! 2.3.1 If there is snow on the ice-fraction it can melt
4483          !
4484          snowmelt_tmp = frac_nobio(ji,iice)*(temp_sol_new(ji) - tp_00) * soilcap(ji) / chalfu0
4485          !
4486          IF ( snowmelt_tmp .GT. snow_nobio(ji,iice) ) THEN
4487             snowmelt_tmp = MAX( zero, snow_nobio(ji,iice))
4488          ENDIF
4489          snowmelt(ji) = snowmelt(ji) + snowmelt_tmp
4490          snow_nobio(ji,iice) = snow_nobio(ji,iice) - snowmelt_tmp
4491          !
4492       ENDIF
4493       !
4494    !! 2.4 Snow melts over a threshold
4495       !   Ice melt only if there is more than a given mass : maxmass_snow,
4496       !   But the snow cannot melt more in one time step to what corresponds to
4497       !   a 1K cooling. This will lead to a progressive melting of snow above
4498       !   maxmass_snow but it is needed as a too strong cooling can destabilise the model.
4499       !
4500       IF ( snow_nobio(ji,iice) .GT. maxmass_snow ) THEN
4501          snow_d1k = un * soilcap(ji) / chalfu0
4502          icemelt(ji) = MIN((snow_nobio(ji,iice) - maxmass_snow),snow_d1k)
4503          snow_nobio(ji,iice) = snow_nobio(ji,iice) - icemelt(ji)
4504
4505          IF ( printlev >= 3 ) WRITE (numout,*) "Snow was above maxmass_snow ON ICE (", maxmass_snow,") and we melted ", icemelt(ji)
4506       ENDIF
4507
4508    END DO
4509
4510    !
4511    !! 3 On other surface types - not done yet
4512    !
4513    IF ( nnobio .GT. 1 ) THEN
4514       WRITE(numout,*) 'WE HAVE',nnobio-1,' SURFACE TYPES I DO NOT KNOW'
4515       WRITE(numout,*) 'CANNOT TREAT SNOW ON THESE SURFACE TYPES'
4516       CALL ipslerr_p(3,'hydrol_snow','nnobio > 1 not allowded','Cannot treat snow on these surface types.','')
4517    ENDIF
4518
4519    !
4520    !! 4 computes total melt (snow and ice)
4521    !
4522    DO ji = 1, kjpindex
4523       tot_melt(ji) = icemelt(ji) + snowmelt(ji)
4524    ENDDO
4525
4526    !
4527    !! 5 computes snow age on veg and ice (for albedo)
4528    !
4529    DO ji = 1, kjpindex
4530       !
4531    !! 5.1 Snow age on vegetation
4532       !
4533       IF (snow(ji) .LE. zero) THEN
4534          snow_age(ji) = zero
4535       ELSE
4536          snow_age(ji) =(snow_age(ji) + (un - snow_age(ji)/max_snow_age) * dt_sechiba/one_day) &
4537               & * EXP(-precip_snow(ji) / snow_trans)
4538       ENDIF
4539       !
4540    !! 5.2 Snow age on ice
4541       !
4542       ! age of snow on ice: a little bit different because in cold regions, we really
4543       ! cannot negect the effect of cold temperatures on snow metamorphism any more.
4544       !
4545       IF (snow_nobio(ji,iice) .LE. zero) THEN
4546          snow_nobio_age(ji,iice) = zero
4547       ELSE
4548          !
4549          d_age(ji) = ( snow_nobio_age(ji,iice) + &
4550               &  (un - snow_nobio_age(ji,iice)/max_snow_age) * dt_sechiba/one_day ) * &
4551               &  EXP(-precip_snow(ji) / snow_trans) - snow_nobio_age(ji,iice)
4552          IF (d_age(ji) .GT. min_sechiba ) THEN
4553             xx(ji) = MAX( tp_00 - temp_sol_new(ji), zero )
4554             xx(ji) = ( xx(ji) / 7._r_std ) ** 4._r_std
4555             d_age(ji) = d_age(ji) / (un+xx(ji))
4556          ENDIF
4557          snow_nobio_age(ji,iice) = MAX( snow_nobio_age(ji,iice) + d_age(ji), zero )
4558          !
4559       ENDIF
4560
4561    ENDDO
4562
4563    !
4564    !! 6 Diagnose the depth of the snow layer
4565    !
4566
4567    DO ji = 1, kjpindex
4568       snowdepth(ji) = snow(ji) /sn_dens
4569    ENDDO
4570
4571    IF (printlev>=3) WRITE (numout,*) ' hydrol_snow done '
4572
4573  END SUBROUTINE hydrol_snow
4574
4575   
4576!! ================================================================================================================================
4577!! SUBROUTINE   : hydrol_canop
4578!!
4579!>\BRIEF        This routine computes canopy processes.
4580!!
4581!! DESCRIPTION  :
4582!! - 1 evaporation off the continents
4583!! - 1.1 The interception loss is take off the canopy.
4584!! - 1.2 precip_rain is shared for each vegetation type
4585!! - 1.3 Limits the effect and sum what receives soil
4586!! - 1.4 swap qsintveg to the new value
4587!!
4588!! RECENT CHANGE(S) : None
4589!!
4590!! MAIN OUTPUT VARIABLE(S) :
4591!!
4592!! REFERENCE(S) :
4593!!
4594!! FLOWCHART    : None
4595!! \n
4596!_ ================================================================================================================================
4597!_ hydrol_canop
4598
4599  SUBROUTINE hydrol_canop (kjpindex, precip_rain, vevapwet, veget_max, veget, qsintmax, &
4600       & qsintveg,precisol,tot_melt, precip2canopy, precip2ground, canopy2ground)
4601
4602    !
4603    ! interface description
4604    !
4605
4606    !! 0. Variable and parameter declaration
4607
4608    !! 0.1 Input variables
4609
4610    INTEGER(i_std), INTENT(in)                               :: kjpindex    !! Domain size
4611    ! input fields
4612    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: precip_rain !! Rain precipitation
4613    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: vevapwet    !! Interception loss
4614    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: veget_max   !! max fraction of vegetation type
4615    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: veget       !! Fraction of vegetation type
4616    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: qsintmax    !! Maximum water on vegetation for interception
4617    REAL(r_std), DIMENSION  (kjpindex), INTENT (in)          :: tot_melt    !! Total melt
4618
4619    !! 0.2 Output variables
4620
4621    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: precisol    !! Water fallen onto the ground (throughfall)
4622    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: precip2canopy  !! Precipitation onto the canopy
4623    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: precip2ground  !! Precipitation not intercepted by canopy
4624    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: canopy2ground  !! Water flux from canopy to the ground
4625
4626    !! 0.3 Modified variables
4627
4628    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(inout)     :: qsintveg    !! Water on vegetation due to interception
4629
4630    !! 0.4 Local variables
4631
4632    INTEGER(i_std)                                           :: ji, jv
4633    REAL(r_std), DIMENSION (kjpindex,nvm)                    :: zqsintvegnew
4634
4635!_ ================================================================================================================================
4636
4637    ! boucle sur les points continentaux
4638    ! calcul de qsintveg au pas de temps suivant
4639    ! par ajout du flux interception loss
4640    ! calcule par enerbil en fonction
4641    ! des calculs faits dans diffuco
4642    ! calcul de ce qui tombe sur le sol
4643    ! avec accumulation dans precisol
4644    ! essayer d'harmoniser le traitement du sol nu
4645    ! avec celui des differents types de vegetation
4646    ! fait si on impose qsintmax ( ,1) = 0.0
4647    !
4648    ! loop for continental subdomain
4649    !
4650    !
4651    !! 1 evaporation off the continents
4652    !
4653    !! 1.1 The interception loss is take off the canopy.
4654    DO jv=2,nvm
4655       qsintveg(:,jv) = qsintveg(:,jv) - vevapwet(:,jv)
4656    END DO
4657
4658    !     It is raining :
4659    !! 1.2 precip_rain is shared for each vegetation type
4660    !
4661    precip2canopy(:,1)= zero      !! TF-DOC
4662    qsintveg(:,1) = zero
4663    DO jv=2,nvm
4664       qsintveg(:,jv) = qsintveg(:,jv) + veget(:,jv) * ((1-throughfall_by_pft(jv))*precip_rain(:))
4665       precip2canopy(:,jv) = veget(:,jv) * ((1-throughfall_by_pft(jv))*precip_rain(:))  !! TF-DOC
4666          ! should consider the veget_max(:,jv) to intercept rain
4667          ! xuhui 20151216
4668          !DO ji = 1,kjpindex
4669          !    IF (veget_max(ji,jv) .GT. zero) THEN ! otherwise, there will be no interception
4670          !        qsintveg(ji,jv) = qsintveg(ji,jv) + veget(ji,jv) / veget_max(ji,jv) * (1 - throughfall_by_pft(jv)) * precip_rain(ji)
4671          !    ENDIF
4672          !ENDDO
4673    END DO
4674
4675    !
4676    !! 1.3 Limits the effect and sum what receives soil
4677    !
4678    precisol(:,1)=veget_max(:,1)*precip_rain(:)
4679    precip2ground(:,1)= precisol(:,1)  !! amount of precipitation that goes to the ground, unitercepted by canopy. Used in stomate_soilcarbon.f90.
4680    DO jv=2,nvm
4681       DO ji = 1, kjpindex
4682          zqsintvegnew(ji,jv) = MIN (qsintveg(ji,jv),qsintmax(ji,jv)) 
4683          precisol(ji,jv) = (veget(ji,jv)*throughfall_by_pft(jv)*precip_rain(ji)) + &
4684               qsintveg(ji,jv) - zqsintvegnew (ji,jv) + &
4685               (veget_max(ji,jv) - veget(ji,jv))*precip_rain(ji)
4686          precip2ground(ji,jv) = (veget(ji,jv)*throughfall_by_pft(jv)*precip_rain(ji)) + &
4687               &                  (veget_max(ji,jv) - veget(ji,jv))*precip_rain(ji)  !! TF-DOC
4688          IF(precisol(ji,jv) .LT. zero) WRITE(numout,*) 'Precisol neg. L3561 ', precisol(ji,jv)
4689          IF(precip_rain(ji) .LT. zero) WRITE(numout,*) 'Precip neg. L3561 ', precip_rain(ji)
4690          IF(precisol(ji,jv) .LT. zero) WRITE(numout,*) 'qsintveg neg. L3561 ', qsintveg(ji,jv)
4691          IF(precisol(ji,jv) .LT. zero) WRITE(numout,*) 'zqsintvegnew neg. L3561 ', zqsintvegnew (ji,jv)
4692          IF(precisol(ji,jv) .LT. zero) WRITE(numout,*) '(veget_max(ji,jv) - veget(ji,jv)) neg. L3561 ', (veget_max(ji,jv) - veget(ji,jv))
4693          canopy2ground(ji,jv) = precisol(ji,jv) - precip2ground(ji,jv)  !! This is a variable used in stomate_soilcarbon.f90 to calculate DOC fluxes from canopy to ground
4694       ENDDO
4695    END DO
4696    !   
4697    DO jv=1,nvm
4698       DO ji = 1, kjpindex
4699          IF (vegtot(ji).GT.min_sechiba) THEN
4700             precisol(ji,jv) = precisol(ji,jv)+tot_melt(ji)*veget_max(ji,jv)/vegtot(ji)
4701             precip2ground(ji,jv) = precip2ground(ji,jv)+tot_melt(ji)*veget_max(ji,jv)/vegtot(ji)
4702          ENDIF
4703       ENDDO
4704    END DO
4705    !   
4706    !
4707    !! 1.4 swap qsintveg to the new value
4708    !
4709    DO jv=2,nvm
4710       qsintveg(:,jv) = zqsintvegnew (:,jv)
4711    END DO
4712
4713    IF (printlev>=3) WRITE (numout,*) ' hydrol_canop done '
4714
4715  END SUBROUTINE hydrol_canop
4716
4717
4718!! ================================================================================================================================
4719!! SUBROUTINE   : hydrol_vegupd
4720!!
4721!>\BRIEF        Vegetation update   
4722!!
4723!! DESCRIPTION  :
4724!!   The vegetation cover has changed and we need to adapt the reservoir distribution
4725!!   and the distribution of plants on different soil types.
4726!!   You may note that this occurs after evaporation and so on have been computed. It is
4727!!   not a problem as a new vegetation fraction will start with humrel=0 and thus will have no
4728!!   evaporation. If this is not the case it should have been caught above.
4729!!
4730!! - 1 Update of vegetation is it needed?
4731!! - 2 calculate water mass that we have to redistribute
4732!! - 3 put it into reservoir of plant whose surface area has grown
4733!! - 4 Soil tile gestion
4734!! - 5 update the corresponding masks
4735!!
4736!! RECENT CHANGE(S) : None
4737!!
4738!! MAIN OUTPUT VARIABLE(S) :
4739!!
4740!! REFERENCE(S) :
4741!!
4742!! FLOWCHART    : None
4743!! \n
4744!_ ================================================================================================================================
4745!_ hydrol_vegupd
4746
4747  SUBROUTINE hydrol_vegupd(kjpindex, veget, veget_max, soiltile, qsintveg, frac_bare, drain_upd, runoff_upd)
4748
4749
4750    !! 0. Variable and parameter declaration
4751
4752    !! 0.1 Input variables
4753
4754    ! input scalar
4755    INTEGER(i_std), INTENT(in)                            :: kjpindex 
4756    ! input fields
4757    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(in)    :: veget            !! New vegetation map
4758    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)     :: veget_max        !! Max. fraction of vegetation type
4759    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)   :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
4760
4761    !! 0.2 Output variables
4762    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)    :: frac_bare        !! Fraction(of veget_max) of bare soil
4763                                                                              !! in each vegetation type
4764    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: drain_upd        !! Change in drainage due to decrease in vegtot
4765                                                                              !! on mc [kg/m2/dt]
4766    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: runoff_upd       !! Change in runoff due to decrease in vegtot
4767                                                                              !! on water2infilt[kg/m2/dt]
4768   
4769
4770    !! 0.3 Modified variables
4771
4772    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (inout)  :: qsintveg         !! Water on old vegetation
4773
4774    !! 0.4 Local variables
4775
4776    INTEGER(i_std)                                 :: ji,jv,jst
4777
4778!_ ================================================================================================================================
4779
4780    !! 1 If veget has been updated at last time step (with LAND USE or DGVM),
4781    !! tmc and mc must be modified with respect to humtot conservation.
4782    CALL hydrol_tmc_update ( kjpindex, veget_max, soiltile, qsintveg, drain_upd, runoff_upd)
4783
4784
4785    ! Compute the masks for veget
4786   
4787    mask_veget(:,:) = 0
4788    mask_soiltile(:,:) = 0
4789   
4790    DO jst=1,nstm
4791       DO ji = 1, kjpindex
4792          IF(soiltile(ji,jst) .GT. min_sechiba) THEN
4793             mask_soiltile(ji,jst) = 1
4794          ENDIF
4795       END DO
4796    ENDDO
4797         
4798    DO jv = 1, nvm
4799       DO ji = 1, kjpindex
4800          IF(veget_max(ji,jv) .GT. min_sechiba) THEN
4801             mask_veget(ji,jv) = 1
4802          ENDIF
4803       END DO
4804    END DO
4805
4806    ! Compute vegetmax_soil
4807    vegetmax_soil(:,:,:) = zero
4808    DO jv = 1, nvm
4809       jst = pref_soil_veg(jv)
4810       DO ji=1,kjpindex
4811          ! for veget distribution used in sechiba via humrel
4812          IF (mask_soiltile(ji,jst).GT.0 .AND. vegtot(ji) > min_sechiba) THEN
4813             vegetmax_soil(ji,jv,jst)=veget_max(ji,jv)/soiltile(ji,jst)
4814          ENDIF
4815       ENDDO
4816    ENDDO
4817
4818    ! Calculate frac_bare (previosly done in slowproc_veget)
4819    DO ji =1, kjpindex
4820       IF( veget_max(ji,1) .GT. min_sechiba ) THEN
4821          frac_bare(ji,1) = un
4822       ELSE
4823          frac_bare(ji,1) = zero
4824       ENDIF
4825    ENDDO
4826    DO jv = 2, nvm
4827       DO ji =1, kjpindex
4828          IF( veget_max(ji,jv) .GT. min_sechiba ) THEN
4829             frac_bare(ji,jv) = un - veget(ji,jv)/veget_max(ji,jv)
4830          ELSE
4831             frac_bare(ji,jv) = zero
4832          ENDIF
4833       ENDDO
4834    ENDDO
4835
4836    ! Tout dans cette routine est maintenant certainement obsolete (veget_max etant constant) en dehors des lignes
4837    ! suivantes et le calcul de frac_bare:
4838    frac_bare_ns(:,:) = zero
4839    DO jst = 1, nstm
4840       DO jv = 1, nvm
4841          DO ji =1, kjpindex
4842             IF(vegtot(ji) .GT. min_sechiba) THEN
4843                frac_bare_ns(ji,jst) = frac_bare_ns(ji,jst) + vegetmax_soil(ji,jv,jst) * frac_bare(ji,jv) / vegtot(ji)
4844             ENDIF
4845          END DO
4846       ENDDO
4847    END DO
4848   
4849    IF (printlev>=3) WRITE (numout,*) ' hydrol_vegupd done '
4850
4851  END SUBROUTINE hydrol_vegupd
4852
4853
4854!! ================================================================================================================================
4855!! SUBROUTINE   : hydrol_flood
4856!!
4857!>\BRIEF        This routine computes the evolution of the surface reservoir (floodplain). 
4858!!
4859!! DESCRIPTION  :
4860!! - 1 Take out vevapflo from the reservoir and transfer the remaining to subsinksoil
4861!! - 2 Compute the total flux from floodplain floodout (transfered to routing)
4862!! - 3 Discriminate between precip over land and over floodplain
4863!!
4864!! RECENT CHANGE(S) : None
4865!!
4866!! MAIN OUTPUT VARIABLE(S) :
4867!!
4868!! REFERENCE(S) :
4869!!
4870!! FLOWCHART    : None
4871!! \n
4872!_ ================================================================================================================================
4873!_ hydrol_flood
4874
4875  SUBROUTINE hydrol_flood (kjpindex, vevapflo, flood_frac, flood_res, floodout)
4876
4877    !! 0. Variable and parameter declaration
4878
4879    !! 0.1 Input variables
4880
4881    ! input scalar
4882    INTEGER(i_std), INTENT(in)                               :: kjpindex         !!
4883    ! input fields
4884    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: flood_frac       !! Fraction of floodplains in grid box
4885
4886    !! 0.2 Output variables
4887
4888    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: floodout         !! Flux to take out from floodplains
4889
4890    !! 0.3 Modified variables
4891
4892    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: flood_res        !! Floodplains reservoir estimate
4893    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapflo         !! Evaporation over floodplains
4894
4895    !! 0.4 Local variables
4896
4897    INTEGER(i_std)                                           :: ji, jv           !! Indices
4898    REAL(r_std), DIMENSION (kjpindex)                        :: temp             !!
4899
4900!_ ================================================================================================================================
4901    !-
4902    !! 1 Take out vevapflo from the reservoir and transfer the remaining to subsinksoil
4903    !-
4904    DO ji = 1,kjpindex
4905       temp(ji) = MIN(flood_res(ji), vevapflo(ji))
4906    ENDDO
4907    DO ji = 1,kjpindex
4908       flood_res(ji) = flood_res(ji) - temp(ji)
4909       subsinksoil(ji) = subsinksoil(ji) + vevapflo(ji) - temp(ji)
4910       vevapflo(ji) = temp(ji)
4911    ENDDO
4912
4913    !-
4914    !! 2 Compute the total flux from floodplain floodout (transfered to routing)
4915    !-
4916    DO ji = 1,kjpindex
4917       floodout(ji) = vevapflo(ji) - flood_frac(ji) * SUM(precisol(ji,:))
4918    ENDDO
4919
4920    !-
4921    !! 3 Discriminate between precip over land and over floodplain
4922    !-
4923    DO jv=1, nvm
4924       DO ji = 1,kjpindex
4925          precisol(ji,jv) = precisol(ji,jv) * (1 - flood_frac(ji))
4926       ENDDO
4927    ENDDO 
4928
4929    IF (printlev>=3) WRITE (numout,*) ' hydrol_flood done'
4930
4931  END SUBROUTINE hydrol_flood
4932
4933
4934!! ================================================================================================================================
4935!! SUBROUTINE   : hydrol_soil
4936!!
4937!>\BRIEF        This routine computes soil processes with CWRR scheme (Richards equation solved by finite differences).
4938!! Note that the water fluxes are in kg/m2/dt_sechiba.
4939!!
4940!! DESCRIPTION  :
4941!! 0. Initialisation, and split 2d variables to 3d variables, per soil tile
4942!! -- START MAIN LOOP (prognostic loop to update mc and mcl) OVER SOILTILES
4943!! 1. FIRSTLY, WE CHANGE MC BASED ON EXTERNAL FLUXES, ALL APPLIED AT THE SOIL SURFACE
4944!! 1.1 Reduces water2infilt and water2extract to their difference
4945!! 1.2 To remove water2extract (including bare soilevaporation) from top layer
4946!! 1.3 Infiltration
4947!! 1.4 Reinfiltration of surface runoff : compute temporary surface water and extract from runoff
4948!! 2. SECONDLY, WE UPDATE MC FROM DIFFUSION, INCLUDING DRAINAGE AND ROOTSINK
4949!!    This will act on mcl (liquid water content) only
4950!! 2.1 K and D are recomputed after infiltration
4951!! 2.2 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
4952!! 2.3 We define mcl (liquid water content) based on mc and profil_froz_hydro_ns
4953!! 2.4 We calculate the total SM at the beginning of the routine tridiag for water conservation check
4954!! 2.5 Defining where diffusion is solved : everywhere
4955!! 2.6 We define the system of linear equations for mcl redistribution
4956!! 2.7 Solves diffusion equations
4957!! 2.8 Computes drainage = bottom boundary condition, consistent with rhs(ji,jsl=nslm)
4958!! 2.9 For water conservation check during redistribution, we calculate the total liquid SM
4959!!     at the end of the routine tridiag, and we compare the difference with the flux...
4960!! 3. AFTER DIFFUSION/REDISTRIBUTION
4961!! 3.1 Updating mc, as all the following checks against saturation will compare mc to mcs
4962!! 3.2 Correct here the possible over-saturation values (subroutine hydrol_soil_smooth_over_mcs2 acts on mc)
4963!!     Here hydrol_soil_smooth_over_mcs2 discard all excess as ru_corr_ns, oriented to either ru_ns or dr_ns
4964!! 3.3 Negative runoff is reported to drainage
4965!! 3.4 Optional block to force saturation below zwt_force
4966!! 3.5 Diagnosing the effective water table depth
4967!! 3.6 Diagnose under_mcr to adapt water stress calculation below
4968!! 4. At the end of the prognostic calculations, we recompute important moisture variables
4969!! 4.1 Total soil moisture content (water2infilt added below)
4970!! 4.2 mcl is a module variable; we update it here for calculating bare soil evaporation,
4971!! 5. Optional check of the water balance of soil column (if check_cwrr)
4972!! 5.1 Computation of the vertical water fluxes
4973!! 5.2 Total mc conservation
4974!! 5.3 Total mc should not reach zero, or the tridiag solver will have problems
4975!! 6. SM DIAGNOSTICS FOR OTHER ROUTINES, MODULES, OR NEXT STEP
4976!! 6.1 Total soil moisture, soil moisture at litter levels, soil wetness, us, humrelv, vesgtressv
4977!! 6.2 We need to turn off evaporation when is_under_mcr
4978!! 6.3 Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in thermosoil
4979!! 6.4 The hydraulic conductivities exported here are the ones used in the diffusion/redistribution
4980!! -- ENDING THE MAIN LOOP ON SOILTILES
4981!! 7. Summing 3d variables into 2d variables
4982!! 8. XIOS export of local variables, including water conservation checks
4983!! 9. COMPUTING EVAP_BARE_LIM_NS FOR NEXT TIME STEP, WITH A LOOP ON SOILTILES
4984!!    The principle is to run a dummy integration of the water redistribution scheme
4985!!    to check if the SM profile can sustain a potential evaporation.
4986!!    If not, the dummy integration is redone from the SM profile of the end of the normal integration,
4987!!    with a boundary condition leading to a very severe water limitation: mc(1)=mcr
4988!! 10. evap_bar_lim is the grid-cell scale beta
4989!! 11. Exit if error was found previously in this subroutine
4990!!
4991!! RECENT CHANGE(S) : 2016 by A. Ducharne
4992!!
4993!! MAIN OUTPUT VARIABLE(S) :
4994!!
4995!! REFERENCE(S) :
4996!!
4997!! FLOWCHART    : None
4998!! \n
4999!_ ================================================================================================================================
5000!_ hydrol_soil
5001
5002  SUBROUTINE hydrol_soil (kjpindex, veget_max, soiltile, njsc, reinf_slope, &
5003       & transpir, vevapnu, vevapnu_pft, evapot, evapot_penm, runoff, drainage, &
5004       & returnflow, reinfiltration, irrigation, irrig_demand_ratio, &
5005       & tot_melt, evap_bare_lim,  shumdiag, shumdiag_perma,&
5006!       & tot_melt, evap_bare_lim, evap_bare_lim_pft, shumdiag, shumdiag_perma,&
5007       & k_litt, litterhumdiag, humrel, vegstress, drysoil_frac, &
5008         irrig_fin, is_crop_soil, &
5009         stempdiag, snow, snowdz, tot_bare_soil, &
5010         u, v, tq_cdrag, &
5011         mc_layh, mcl_layh, tmc_layh, mc_layh_s, mcl_layh_s, &
5012         soil_mc, litter_mc,wat_flux0, wat_flux, drainage_per_soil, runoff_per_soil, &
5013         drunoff_tot, fsat, &
5014!gmjc
5015       & tmc_topgrass)
5016!end gmjc
5017    !
5018    ! interface description
5019
5020    !! 0. Variable and parameter declaration
5021
5022    !! 0.1 Input variables
5023
5024    INTEGER(i_std), INTENT(in)                               :: kjpindex 
5025    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: veget_max        !! Map of max vegetation types [-]
5026    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc             !! Index of the dominant soil textural class
5027                                                                                 !!   in the grid cell (1-nscm, unitless)
5028    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soil tile within vegtot (0-1, unitless)
5029    LOGICAL, DIMENSION (nstm), INTENT (in)                   :: is_crop_soil     !! Whether the tile is under cropland
5030    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: transpir         !! Transpiration 
5031                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5032    REAL(r_std), DIMENSION (kjpindex), INTENT (in)           :: reinf_slope      !! Fraction of surface runoff that reinfiltrates
5033                                                                                 !!  (unitless, [0-1])
5034    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow       !! Water returning to the soil from the bottom
5035                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5036    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: reinfiltration   !! Water returning to the top of the soil
5037                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5038    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: irrigation       !! Irrigation
5039                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5040    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(in)        :: irrig_demand_ratio  !! ratio of irrigation water [unitless,0-1]
5041    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot           !! Potential evaporation
5042                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5043    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot_penm      !! Potential evaporation "Penman" (Milly's correction)
5044                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5045    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_melt         !! Total melt from snow and ice
5046                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5047    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (in)       :: stempdiag        !! Diagnostic temp profile from thermosoil
5048    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: snow             !! Snow mass
5049                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5050    REAL(r_std), DIMENSION (kjpindex,nsnow),INTENT(in)       :: snowdz           !! Snow depth (m)
5051!pss:+
5052    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: fsat             !! fraction of saturation soil
5053!pss:-
5054    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_bare_soil    !! Total evaporating bare soil fraction
5055                                                                                 !!  (unitless, [0-1])
5056    REAL(r_std),DIMENSION (kjpindex), INTENT(in)             :: u,v              !! Horizontal wind speed
5057    REAL(r_std),DIMENSION (kjpindex), INTENT(in)             :: tq_cdrag         !! Surface drag coefficient
5058
5059    !! 0.2 Output variables
5060
5061    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: runoff           !! Surface runoff
5062                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5063    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drainage         !! Drainage
5064                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5065    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(out)      :: runoff_per_soil  !! runoff for each soil type[mm]
5066
5067    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(out)      :: drainage_per_soil!! drainage for each soil type [mm]
5068
5069    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: evap_bare_lim    !! Limitation factor (beta) for bare soil evaporation 
5070                                                                                 !! on each soil column (unitless, [0-1])
5071!    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)        :: evap_bare_lim_pft !! limitation factor (beta) for bare soil evaporation 
5072                                                                                 !! on each soil column [mm]
5073    REAL(r_std), DIMENSION (kjpindex,nbdl), INTENT (out)     :: shumdiag         !! Relative soil moisture in each diag soil layer
5074                                                                                 !! with respect to (mcf-mcw) (unitless, [0-1])
5075    REAL(r_std), DIMENSION (kjpindex,nbdl), INTENT (out)     :: shumdiag_perma   !! Percent of porosity filled with water (mc/mcs)
5076                                                                                 !! in each diag soil layer (for the thermal computations)
5077                                                                                 !! (unitless, [0-1])
5078    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: k_litt           !! Litter approximated hydraulic conductivity
5079                                                                                 !!  @tex $(mm d^{-1})$ @endtex
5080    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: litterhumdiag    !! Mean of soil_wet_litter across soil tiles
5081                                                                                 !! (unitless, [0-1])
5082    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(out)      :: vegstress        !! Veg. moisture stress (only for vegetation
5083                                                                                 !! growth) (unitless, [0-1])
5084    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: drysoil_frac     !! Function of the litter humidity
5085    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(out)       :: irrig_fin        !! final application of irrigation [mm]
5086!pss:+
5087    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drunoff_tot      !! Dunne runoff
5088!pss:-
5089    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: mc_layh          !! Volumetric water content (liquid + ice) for each soil layer
5090                                                                                 !! averaged over the mesh (for thermosoil)
5091                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
5092    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: mcl_layh         !! Volumetric liquid water content for each soil layer
5093                                                                                 !! averaged over the mesh (for thermosoil)
5094                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
5095    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT (out)     :: tmc_layh         !! Soil moisture (liquid + ice) for soil each layer
5096                                                                                 !! averaged over the mesh (for thermosoil)
5097                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
5098    REAL(r_std),DIMENSION (kjpindex,nbdl,nstm), INTENT(out)  :: soil_mc          !! soil moisture content \f($m^3 \times m^3$)\f
5099    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(out)       :: litter_mc        !! litter moisture content \f($m^3 \times m^3$)\f
5100    REAL(r_std),DIMENSION (kjpindex,nstm), INTENT(out)       :: wat_flux0        !! Water flux in the first soil layers exported for soil C calculations
5101    REAL(r_std),DIMENSION (kjpindex,nslm,nstm), INTENT(out)  :: wat_flux         !! Water flux in the soil layers exported for soil C calculations
5102   
5103                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
5104    REAL(r_std), DIMENSION (kjpindex,nslm,nstm), INTENT (out)  :: mc_layh_s          !! Volumetric soil moisture content for each layer in hydrol(liquid + ice) [m3/m3]
5105    REAL(r_std), DIMENSION (kjpindex,nslm,nstm), INTENT (out)  :: mcl_layh_s         !! Volumetric soil moisture content for each layer in hydrol(liquid) [m3/m3]
5106!gmjc
5107   REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: tmc_topgrass
5108!end gmjc
5109    !! 0.3 Modified variables
5110
5111    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapnu          !! Bare soil evaporation
5112                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5113    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT(inout)     :: vevapnu_pft          !! Bare soil evaporation
5114    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (inout)    :: humrel           !! Relative humidity (0-1, dimensionless)
5115
5116    !! 0.4 Local variables
5117
5118    INTEGER(i_std)                                 :: ji, jv, jsl, jst           !! Indices
5119    REAL(r_std), PARAMETER                         :: frac_mcs = 0.66            !! Temporary depth
5120    REAL(r_std)                                    :: tot_irrig_frac            !! temporary sum of irrigated fraction of vegetation
5121    REAL(r_std), DIMENSION(kjpindex)               :: temp                       !! Temporary value for fluxes
5122    REAL(r_std), DIMENSION(kjpindex)               :: tmcold                     !! Total SM at beginning of hydrol_soil (kg/m2)
5123    REAL(r_std), DIMENSION(kjpindex)               :: tmcint                     !! Ancillary total SM (kg/m2)
5124    REAL(r_std), DIMENSION(kjpindex,nslm)          :: mcint                      !! To save mc values for future use
5125    REAL(r_std), DIMENSION(kjpindex,nslm)          :: mclint                     !! To save mcl values for future use
5126    LOGICAL, DIMENSION(kjpindex,nstm)              :: is_under_mcr               !! Identifies under residual soil moisture points
5127    LOGICAL, DIMENSION(kjpindex)                   :: is_over_mcs                !! Identifies over saturated soil moisture points
5128    REAL(r_std), DIMENSION(kjpindex)               :: deltahum,diff              !!
5129    LOGICAL(r_std), DIMENSION(kjpindex)            :: test                       !!
5130    REAL(r_std), DIMENSION(kjpindex)               :: water2extract              !! Water flux to be extracted at the soil surface
5131                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5132    REAL(r_std), DIMENSION(kjpindex)               :: returnflow_soil            !! Water from the routing back to the bottom of
5133                                                                                 !! the soil @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5134    REAL(r_std), DIMENSION(kjpindex)               :: reinfiltration_soil        !! Water from the routing back to the top of the
5135                                                                                 !! soil @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5136    REAL(r_std), DIMENSION(kjpindex, nstm)         :: irrigation_soil            !! Water from irrigation returning to soil moisture
5137                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5138    REAL(r_std), DIMENSION(kjpindex)               :: flux_infilt                !! Water to infiltrate
5139                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5140    REAL(r_std), DIMENSION(kjpindex)               :: flux_bottom                !! Flux at bottom of the soil column
5141                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5142    REAL(r_std), DIMENSION(kjpindex)               :: flux_top                   !! Flux at top of the soil column (for bare soil evap)
5143                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5144    REAL(r_std), DIMENSION (kjpindex,nstm)         :: qinfilt_ns                 !! Effective infiltration flux per soil tile
5145                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
5146    REAL(r_std), DIMENSION (kjpindex)              :: qinfilt                    !! Effective infiltration flux 
5147                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5148    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_infilt_ns               !! Surface runoff from hydrol_soil_infilt per soil tile
5149                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
5150    REAL(r_std), DIMENSION (kjpindex)              :: ru_infilt                  !! Surface runoff from hydrol_soil_infilt
5151                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5152    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_corr_ns                 !! Surface runoff produced to correct excess per soil tile
5153                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5154    REAL(r_std), DIMENSION (kjpindex)              :: ru_corr                    !! Surface runoff produced to correct excess
5155                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex 
5156    REAL(r_std), DIMENSION (kjpindex,nstm)         :: ru_corr2_ns                !! Correction of negative surface runoff per soil tile
5157                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5158    REAL(r_std), DIMENSION (kjpindex)              :: ru_corr2                   !! Correction of negative surface runoff
5159                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5160    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_corr_ns                 !! Drainage produced to correct excess
5161                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5162    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_corrnum_ns              !! Drainage produced to correct numerical errors in tridiag
5163                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
5164    REAL(r_std), DIMENSION (kjpindex)              :: dr_corr                    !! Drainage produced to correct excess
5165                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5166    REAL(r_std), DIMENSION (kjpindex)              :: dr_corrnum                 !! Drainage produced to correct numerical errors in tridiag
5167                                                                                 !!  @tex $(kg m^{-2} dt\_sechiba^{-1})$ @endtex
5168    REAL(r_std), DIMENSION (kjpindex,nslm)         :: dmc                        !! Delta mc when forcing saturation (zwt_force)
5169                                                                                 !!  @tex $(m^{3} m^{-3})$ @endtex
5170    REAL(r_std), DIMENSION (kjpindex,nstm)         :: dr_force_ns                !! Delta drainage when forcing saturation (zwt_force)
5171                                                                                 !!  per soil tile  @tex $(kg m^{-2})$ @endtex
5172    REAL(r_std), DIMENSION (kjpindex)              :: dr_force                   !! Delta drainage when forcing saturation (zwt_force)
5173                                                                                 !!  @tex $(kg m^{-2})$ @endtex 
5174    REAL(r_std), DIMENSION (kjpindex,nstm)         :: wtd_ns                     !! Effective water table depth (m)
5175    REAL(r_std), DIMENSION (kjpindex)              :: wtd                        !! Mean water table depth in the grid-cell (m)
5176    REAL(r_std), DIMENSION (kjpindex,nslm,nstm)    :: tmc_layh_ns                !! Soil moisture content forin  each soil layer
5177                                                                                 !! and each soiltile
5178                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5179    LOGICAL                                        :: error=.FALSE.              !! If true, exit in the end of subroutine
5180
5181    ! For the calculation of soil_wet and us/humrel/vegstress
5182    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sm                         !! Soil moisture of each layer
5183                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5184    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smw                        !! Soil moisture of each layer at wilting point
5185                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5186    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smf                        !! Soil moisture of each layer at field capacity
5187                                                                                 !!  @tex $(kg m^{-2})$ @endtex   
5188    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sms                        !! Soil moisture of each layer at saturation
5189                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5190    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sms_tmp
5191    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smf_tmp
5192    REAL(r_std), DIMENSION (kjpindex,nslm)         :: smw_tmp
5193    REAL(r_std), DIMENSION (kjpindex,nslm)         :: sm_nostress                !! Soil moisture of each layer at which us reaches 1
5194                                                                                 !!  @tex $(kg m^{-2})$ @endtex
5195    ! For water conservation checks (in mm/dtstep unless otherwise mentioned)
5196    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_infilt_ns             !! Water conservation diagnostic at routine scale
5197    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check1_ns                   !! Water conservation diagnostic at routine scale
5198    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_tr_ns                 !! Water conservation diagnostic at routine scale
5199    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_over_ns               !! Water conservation diagnostic at routine scale
5200    REAL(r_std), DIMENSION (kjpindex,nstm)         :: check_under_ns              !! Water conservation diagnostic at routine scale
5201    REAL(r_std), DIMENSION(kjpindex)               :: tmci                        !! Total soil moisture at beginning of routine (kg/m2)
5202    REAL(r_std), DIMENSION(kjpindex)               :: tmcf                        !! Total soil moisture at end of routine (kg/m2)
5203    REAL(r_std), DIMENSION(kjpindex)               :: diag_tr                     !! Transpiration flux
5204    REAL(r_std), DIMENSION (kjpindex)              :: check_infilt                !! Water conservation diagnostic at routine scale
5205    REAL(r_std), DIMENSION (kjpindex)              :: check1                      !! Water conservation diagnostic at routine scale
5206    REAL(r_std), DIMENSION (kjpindex)              :: check_tr                    !! Water conservation diagnostic at routine scale
5207    REAL(r_std), DIMENSION (kjpindex)              :: check_over                  !! Water conservation diagnostic at routine scale
5208    REAL(r_std), DIMENSION (kjpindex)              :: check_under                 !! Water conservation diagnostic at routine scale
5209
5210    ! Variables for calculation of a soil resistance, option do_rsoil (following the formulation of Sellers et al 1992, implemented in Oleson et al. 2008)
5211    REAL(r_std)                                    :: speed                      !! magnitude of wind speed required for Aerodynamic resistance
5212    REAL(r_std)                                    :: ra                         !! diagnosed aerodynamic resistance
5213    REAL(r_std), DIMENSION(kjpindex)               :: mc_rel                     !! first layer relative soil moisture, required for rsoil
5214    REAL(r_std), DIMENSION(kjpindex)               :: evap_soil                  !! soil evaporation from Oleson et al 2008
5215    REAL(r_std), DIMENSION(kjpindex,nstm)          :: r_soil_ns                  !! soil resistance from Oleson et al 2008
5216    REAL(r_std), DIMENSION(kjpindex)               :: r_soil                     !! soil resistance from Oleson et al 2008
5217    REAL(r_std), DIMENSION(kjpindex)               :: tmcs_litter                !! Saturated soil moisture in the 4 "litter" soil layers
5218    REAL(r_std), DIMENSION (nslm)                  :: nroot_tmp                  !! Temporary variable to calculate the nroot
5219
5220!_ ================================================================================================================================
5221
5222    !! 0.1 Arrays with DIMENSION(kjpindex)
5223   
5224    returnflow_soil(:) = zero
5225    reinfiltration_soil(:) = zero
5226    irrigation_soil(:, :) = zero
5227    qflux(:,:,:) = zero
5228    mc_layh(:,:) = zero ! for thermosoil
5229    mcl_layh(:,:) = zero ! for thermosoil
5230    tmc_layh(:,:) = zero ! for thermosoil
5231!    mc_layh_s(:,:,:) = zero
5232!    mcl_layh_s(:,:,:) = zero
5233    tmc_layh_ns(:,:,:) = zero
5234    IF (ok_freeze_cwrr) THEN
5235       kk(:,:,:)=zero
5236       kk_moy(:,:)=zero
5237    ENDIF
5238    undermcr(:) = zero ! needs to be initialized outside from jst loop
5239
5240    IF (ok_freeze_cwrr) THEN
5241       
5242       ! 0.1 Calculate the temperature and fozen fraction at the hydrological levels
5243       
5244       ! AD16*** This subroutine could probably be simplified massively given
5245       ! that hydro and T share the same vertical discretization
5246       ! Here stempdiag is in from thermosoil and temp_hydro is out
5247       CALL hydrol_calculate_temp_hydro(kjpindex, stempdiag, snow,snowdz)
5248       
5249       ! Calculates profil_froz_hydro_ns as a function of temp_hydro, and mc if ok_thermodynamical_freezing
5250       ! These values will be kept till the end of the prognostic loop
5251       DO jst=1,nstm
5252          CALL hydrol_soil_froz(kjpindex,jst,njsc)
5253       ENDDO
5254
5255    ELSE
5256 
5257       profil_froz_hydro_ns(:,:,:) = zero
5258             
5259    ENDIF
5260   
5261    !! 0.2 Split 2d variables to 3d variables, per soil tile
5262    !  Here, the evaporative fluxes are distributed over the soiltiles as a function of the
5263    !    corresponding control factors; they are normalized to vegtot
5264    !  At step 7, the reverse transformation is used for the fluxes produced in hydrol_soil
5265    !    flux_cell(ji)=sum(flux_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji))
5266    CALL hydrol_split_soil (kjpindex, veget_max, soiltile, vevapnu, vevapnu_pft, transpir, humrel, evap_bare_lim, tot_bare_soil)
5267
5268    !! 0.3 Common variables related to routing, with all return flow applied to the soil surface
5269    ! The fluxes coming from the routing are uniformly splitted into the soiltiles,
5270    !    but are normalized to vegtot like the above fluxes:
5271    !            flux_ns(ji,jst)=flux_cell(ji)/vegtot(ji)
5272    ! It is the case for : irrigation_soil(ji) and reinfiltration_soil(ji) cf below
5273    ! It is also the case for subsinksoil(ji), which is divided by (1-tot_frac_nobio) at creation in hydrol_snow
5274    ! AD16*** The transformation in 0.2 and 0.3 is likely to induce conservation problems
5275    !         when tot_frac_nobio NE 0, since sum(soiltile) NE vegtot in this case
5276   
5277    DO ji=1,kjpindex
5278       IF(vegtot(ji).GT.min_sechiba) THEN
5279          ! returnflow_soil is assumed to enter from the bottom, but it is not possible with CWRR
5280          returnflow_soil(ji) = zero
5281          reinfiltration_soil(ji) = (returnflow(ji) + reinfiltration(ji))/vegtot(ji)
5282!          irrigation_soil(ji) = irrigation(ji)/vegtot(ji)
5283          ! only crop soil(nstm>=4) will be irrigated...
5284          tot_irrig_frac = zero
5285          DO jv=2,nvm
5286              IF ( ok_LAIdev(jv) .AND. ( irrig_demand_ratio(ji,jv) .GT. zero )) THEN
5287!                  IF (pref_soil_veg(jv) .LT. 4) THEN
5288                  IF (.NOT. is_crop_soil(pref_soil_veg(jv)) ) THEN 
5289                      ! the demanded irrigation is not in the crop soil column
5290                      WRITE(numout,*) "pft ", jv, " pref_soil_veg(jv) ", pref_soil_veg(jv), "is not crop soil"
5291                      STOP "hydrol irrig"
5292                  ENDIF
5293                  tot_irrig_frac = tot_irrig_frac + veget_max(ji,jv)
5294              ENDIF
5295          ENDDO         
5296!          IF (tot_irrig_frac .GT. zero) THEN
5297!              irrigation_soil(ji) = irrigation(ji)/tot_irrig_frac
5298!          ELSE
5299!              irrigation_soil(ji) = zero
5300!          ENDIF
5301          irrig_fin(:,:) = zero
5302          DO jv = 2,nvm
5303              ! old: since we only have one crop soil, we pour all irrigation water into
5304              ! this soil column
5305              !!!IF ( irrig_demand_ratio(ji,jv) .GT. zero ) THEN
5306              !!!    irrig_fin(ji,jv) = irrigation_soil(ji)
5307              !!!ENDIF
5308              ! now we have several crop soil tile
5309              ! we irrigate separately considering soil tiles
5310              ! assuming each crop has its own tile respectively
5311              IF ((irrig_demand_ratio(ji,jv) .GT. zero) .AND. (pref_soil_veg(jv) .GE. 4)) THEN
5312                  irrig_fin(ji,jv) = irrigation(ji) * irrig_demand_ratio(ji,jv) / veget_max(ji,jv)
5313                  irrigation_soil(ji,pref_soil_veg(jv)) = irrigation_soil(ji,pref_soil_veg(jv)) + &
5314                             & irrigation(ji) * irrig_demand_ratio(ji,jv) / soiltile(ji,pref_soil_veg(jv))
5315              ENDIF
5316          ENDDO
5317       ELSE
5318          returnflow_soil(ji) = zero
5319          reinfiltration_soil(ji) = zero
5320          irrigation_soil(ji,:) = zero
5321       ENDIF
5322    ENDDO     
5323
5324!!    WRITE(numout,*) "irrig xuhui: irrigation_soil(1,:): ", irrigation_soil(1,:)
5325   
5326    !! -- START MAIN LOOP (prognostic loop to update mc and mcl) OVER SOILTILES
5327    !!    The called subroutines work on arrays with DIMENSION(kjpindex),
5328    !!    recursively used for each soiltile jst
5329   
5330    DO jst = 1,nstm
5331
5332       is_under_mcr(:,jst) = .FALSE.
5333       is_over_mcs(:) = .FALSE.
5334       
5335       !! 0.4. Keep initial values for future check-up
5336       
5337       ! Total moisture content (including water2infilt) is saved for balance checks at the end
5338       ! In hydrol_tmc_update, tmc is increased by water2infilt(ji,jst), but mc is not modified !
5339       tmcold(:) = tmc(:,jst)
5340       
5341       ! The value of mc is kept in mcint (nstm dimension removed), in case needed for water balance checks
5342       DO jsl = 1, nslm
5343          DO ji = 1, kjpindex
5344             mcint(ji,jsl) = mask_soiltile(ji,jst) * mc(ji,jsl,jst)
5345          ENDDO
5346       ENDDO
5347       !
5348       ! Initial total moisture content : tmcint does not include water2infilt, contrarily to tmcold
5349       DO ji = 1, kjpindex
5350          tmcint(ji) = dz(2) * ( trois*mcint(ji,1) + mcint(ji,2) )/huit 
5351       ENDDO
5352       DO jsl = 2,nslm-1
5353          DO ji = 1, kjpindex
5354             tmcint(ji) = tmcint(ji) + dz(jsl) &
5355                  & * (trois*mcint(ji,jsl)+mcint(ji,jsl-1))/huit &
5356                  & + dz(jsl+1) * (trois*mcint(ji,jsl)+mcint(ji,jsl+1))/huit
5357          ENDDO
5358       ENDDO
5359       DO ji = 1, kjpindex
5360          tmcint(ji) = tmcint(ji) + dz(nslm) &
5361               & * (trois * mcint(ji,nslm) + mcint(ji,nslm-1))/huit
5362       ENDDO
5363
5364       !! 1. FIRSTLY, WE CHANGE MC BASED ON EXTERNAL FLUXES, ALL APPLIED AT THE SOIL SURFACE
5365       !!   Input = water2infilt(ji,jst) + irrigation_soil(ji) + reinfiltration_soil(ji) + precisol_ns(ji,jst)
5366       !!      - negative evaporation fluxes (MIN(ae_ns(ji,jst),zero)+ MIN(subsinksoil(ji),zero))
5367       !!   Output = MAX(ae_ns(ji,jst),zero) + subsinksoil(ji) = positive evaporation flux = water2extract
5368       ! In practice, negative subsinksoil(ji) is not possible
5369
5370       !! 1.1 Reduces water2infilt and water2extract to their difference
5371
5372       ! Compares water2infilt and water2extract to keep only difference
5373       ! Here, temp is used as a temporary variable to store the min of water to infiltrate vs evaporate
5374!write(numout,*) 'hydrol.f90 5335  maxval precisol_ns =', (maxval(precisol_ns))
5375!write(numout,*) 'hydrol.f90 5335  minval precisol_ns =', (minval(precisol_ns))
5376
5377       DO ji = 1, kjpindex
5378          IF ( is_crop_soil(jst) ) THEN ! crop soil
5379              temp(ji) = MIN(water2infilt(ji,jst) + irrigation_soil(ji, jst) + reinfiltration_soil(ji) &
5380                         - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst), &
5381                           MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) )
5382          ELSE
5383              temp(ji) = MIN(water2infilt(ji,jst) + reinfiltration_soil(ji) &
5384                         - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst), &
5385                           MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) )
5386          ENDIF
5387       ENDDO
5388
5389       ! The water to infiltrate at the soil surface is either 0, or the difference to what has to be evaporated
5390       !   - the initial water2infilt (right hand side) results from qsintveg changes with vegetation updates
5391       !   - irrigation_soil is the input flux to the soil surface from irrigation
5392       !   - reinfiltration_soil is the input flux to the soil surface from routing 'including returnflow)
5393       !   - eventually, water2infilt holds all fluxes to the soil surface except precisol (reduced by water2extract)
5394       DO ji = 1, kjpindex
5395          IF ( is_crop_soil(jst) ) THEN ! crop soil
5396               water2infilt(ji,jst) = water2infilt(ji,jst) + irrigation_soil(ji,jst) + reinfiltration_soil(ji) &
5397                    - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst) &
5398                    - temp(ji) 
5399          ELSE
5400                water2infilt(ji,jst) = water2infilt(ji,jst) + reinfiltration_soil(ji) &
5401                    - MIN(ae_ns(ji,jst),zero) - MIN(subsinksoil(ji),zero) + precisol_ns(ji,jst) &
5402                    - temp(ji) 
5403          ENDIF
5404       ENDDO       
5405!!       WRITE(numout,*) "irrig xuhui: water2infilt(1,4): ", water2infilt(1,4)
5406!!        WRITE(numout,*) '5405 minval water2infilt =', (minval(water2infilt))
5407!!       WRITE(numout,*) '5405 maxval water2infilt =', (maxval(water2infilt))
5408!!             
5409       ! The water to evaporate from the sol surface is either the difference to what has to be infiltrated, or 0
5410       !   - subsinksoil is the residual from sublimation is the snowpack is not sufficient
5411       !   - how are the negative values of ae_ns taken into account ???
5412       DO ji = 1, kjpindex
5413          water2extract(ji) =  MAX(ae_ns(ji,jst),zero) + MAX(subsinksoil(ji),zero) - temp(ji) 
5414       ENDDO
5415
5416       ! Here we acknowledge that subsinksoil is part of ae_ns, but ae_ns is not used further
5417       ae_ns(:,jst) = ae_ns(:,jst) + subsinksoil(:) 
5418
5419       !! 1.2 To remove water2extract (including bare soil) from top layer
5420       flux_top(:) = water2extract(:)
5421
5422       !! 1.3 Infiltration
5423!!write(numout,*) 'hydrol.f90 5382  maxval precisol_ns =', (maxval(precisol_ns))
5424!!write(numout,*) 'hydrol.f90 5382  minval precisol_ns =', (minval(precisol_ns))
5425       !! Definition of flux_infilt
5426       DO ji = 1, kjpindex
5427          ! Initialise the flux to be infiltrated 
5428          flux_infilt(ji) = water2infilt(ji,jst) !!!+ precisol_ns(ji,jst)  !!SIMON:: THIS PRECISOL_NS IS not used in latest MICT. WHY?
5429          ! This incoming flux is first dedicated to fill the soil up to mcr (in case needed, see 2.3)
5430       ENDDO
5431       
5432       !! K and D are computed for the profile of mc before infiltration
5433       !! They depend on the fraction of soil ice, given by profil_froz_hydro_ns
5434       CALL hydrol_soil_coef(kjpindex,jst,njsc)
5435
5436
5437       !! Infiltration and surface runoff are computed
5438       !! Infiltration stems from comparing liquid water2infilt to initial total mc (liquid+ice)
5439       !! The conductivity comes from hydrol_soil_coef and relates to the liquid phase only
5440       !  This seems consistent with ok_freeze
5441       CALL hydrol_soil_infilt(kjpindex, jst, njsc, flux_infilt, qinfilt_ns, ru_infilt_ns, &
5442            check_infilt_ns)
5443       ru_ns(:,jst) = ru_infilt_ns(:,jst) 
5444
5445
5446       !! 1.4 Reinfiltration of surface runoff : compute temporary surface water and extract from runoff
5447       ! Evrything here is liquid
5448       ! RK: water2infilt is both a volume for future reinfiltration (in mm) and a correction term for surface runoff (in mm/dt_sechiba)
5449       IF ( .NOT. doponds ) THEN ! this is the general case...
5450          DO ji = 1, kjpindex
5451             water2infilt(ji,jst) = reinf_slope(ji) * ru_ns(ji,jst)
5452          ENDDO
5453       ELSE
5454          DO ji = 1, kjpindex           
5455             water2infilt(ji,jst) = zero
5456          ENDDO
5457       ENDIF
5458!
5459!        WRITE(numout,*) '5457 minval water2infilt =', (minval(water2infilt))
5460!       WRITE(numout,*) '5457 maxval water2infilt =', (maxval(water2infilt))
5461       !
5462       DO ji = 1, kjpindex           
5463          ru_ns(ji,jst) = ru_ns(ji,jst) - water2infilt(ji,jst)
5464       END DO
5465
5466       !! 2. SECONDLY, WE UPDATE MC FROM DIFFUSION, INCLUDING DRAINAGE AND ROOTSINK
5467       !!    This will act on mcl only
5468       
5469       !! 2.1 K and D are recomputed after infiltration
5470       !! They depend on the fraction of soil ice, still given by profil_froz_hydro_ns
5471       CALL hydrol_soil_coef(kjpindex,jst,njsc)
5472 
5473       !! 2.2 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
5474       !! This process will further act on mcl only, based on a, b, d from hydrol_soil_coef
5475       CALL hydrol_soil_setup(kjpindex,jst)
5476
5477       !! 2.3 We define mcl (liquid water content) based on mc and profil_froz_hydro_ns
5478       DO jsl = 1, nslm
5479          DO ji =1, kjpindex
5480             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(njsc(ji)) + &
5481                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
5482             ! we always have mcl<=mc
5483             ! if mc>mcr, then mcl>mcr; if mc=mcr,mcl=mcr; if mc<mcr, then mcl<mcr
5484             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
5485          ENDDO
5486       ENDDO
5487
5488       ! The value of mcl is kept in mclint (nstm dimension removed), used in the flux computation after diffusion
5489       DO jsl = 1, nslm
5490          DO ji = 1, kjpindex
5491             mclint(ji,jsl) = mask_soiltile(ji,jst) * mcl(ji,jsl,jst)
5492          ENDDO
5493       ENDDO
5494
5495       !! 2.4 We calculate the total SM at the beginning of the routine tridiag for water conservation check
5496       !  (on mcl only, since the diffusion only modifies mcl)
5497       tmci(:) = dz(2) * ( trois*mcl(:,1,jst) + mcl(:,2,jst) )/huit
5498       DO jsl = 2,nslm-1
5499          tmci(:) = tmci(:) + dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
5500               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
5501       ENDDO
5502       tmci(:) = tmci(:) + dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit
5503
5504       IF (ok_freeze_cwrr) THEN
5505          CALL hydrol_soil_coef(kjpindex,jst,njsc)
5506          DO ji =1, kjpindex
5507             DO jsl = 1, nslm
5508                mcl(ji,jsl,jst)= MIN(mc(ji,jsl,jst),mcr(njsc(ji))+(1-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))))
5509             ENDDO
5510          ENDDO
5511       ELSE
5512          mcl(:,:,jst)=mc(:,:,jst)
5513       ENDIF
5514       !! 2.5 Defining where diffusion is solved : everywhere
5515       !! Since mc>mcs is not possible after infiltration, and we accept that mc<mcr
5516       !! (corrected later by shutting off all evaporative fluxes in this case)
5517       !  Nothing is done if resolv=F
5518       resolv(:) = (mask_soiltile(:,jst) .GT. 0)
5519
5520       !! 2.6 We define the system of linear equations for mcl redistribution,
5521       !! based on the matrix coefficients from hydrol_soil_setup
5522       !! following the PhD thesis of de Rosnay (1999), p155-157
5523       !! The bare soil evaporation (subtracted from infiltration) is used directly as flux_top
5524       ! rhs for right-hand side term; fp for f'; gp for g'; ep for e'; with flux=0 !
5525       
5526       !- First layer
5527       DO ji = 1, kjpindex
5528          tmat(ji,1,1) = zero
5529          tmat(ji,1,2) = f(ji,1)
5530          tmat(ji,1,3) = g1(ji,1)
5531          rhs(ji,1)    = fp(ji,1) * mcl(ji,1,jst) + gp(ji,1)*mcl(ji,2,jst) &
5532               &  - flux_top(ji) - (b(ji,1)+b(ji,2))/deux *(dt_sechiba/one_day) - rootsink(ji,1,jst)
5533       ENDDO
5534       !- soil body
5535       DO jsl=2, nslm-1
5536          DO ji = 1, kjpindex
5537             tmat(ji,jsl,1) = e(ji,jsl)
5538             tmat(ji,jsl,2) = f(ji,jsl)
5539             tmat(ji,jsl,3) = g1(ji,jsl)
5540             rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
5541                  & +  gp(ji,jsl) * mcl(ji,jsl+1,jst) & 
5542                  & + (b(ji,jsl-1) - b(ji,jsl+1)) * (dt_sechiba/one_day) / deux & 
5543                  & - rootsink(ji,jsl,jst) 
5544          ENDDO
5545       ENDDO       
5546       !- Last layer, including drainage
5547       DO ji = 1, kjpindex
5548          jsl=nslm
5549          tmat(ji,jsl,1) = e(ji,jsl)
5550          tmat(ji,jsl,2) = f(ji,jsl)
5551          tmat(ji,jsl,3) = zero
5552          rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
5553               & + (b(ji,jsl-1) + b(ji,jsl)*(un-deux*free_drain_coef(ji,jst))) * (dt_sechiba/one_day) / deux &
5554               & - rootsink(ji,jsl,jst)
5555       ENDDO
5556       !- Store the equations in case needed again
5557       DO jsl=1,nslm
5558          DO ji = 1, kjpindex
5559             srhs(ji,jsl) = rhs(ji,jsl)
5560             stmat(ji,jsl,1) = tmat(ji,jsl,1)
5561             stmat(ji,jsl,2) = tmat(ji,jsl,2)
5562             stmat(ji,jsl,3) = tmat(ji,jsl,3) 
5563          ENDDO
5564       ENDDO
5565
5566!       WRITE(numout,*) 'mcl step2 done'
5567       
5568       !! 2.7 Solves diffusion equations, but only in grid-cells where resolv is true, i.e. everywhere (cf 2.2)
5569       !!     The result is an updated mcl profile
5570
5571       CALL hydrol_soil_tridiag(kjpindex,jst)
5572
5573       !! 2.8 Computes drainage = bottom boundary condition, consistent with rhs(ji,jsl=nslm)
5574       ! dr_ns in mm/dt_sechiba, from k in mm/d
5575       ! This should be done where resolv=T, like tridiag (drainage is part of the linear system !)
5576       DO ji = 1, kjpindex
5577          IF (resolv(ji)) THEN
5578             dr_ns(ji,jst) = mask_soiltile(ji,jst)*k(ji,nslm)*free_drain_coef(ji,jst) * (dt_sechiba/one_day)
5579          ELSE
5580             dr_ns(ji,jst) = zero
5581          ENDIF
5582       ENDDO
5583
5584       !! 2.9 For water conservation check during redistribution AND CORRECTION,
5585       !!     we calculate the total liquid SM at the end of the routine tridiag
5586       tmcf(:) = dz(2) * ( trois*mcl(:,1,jst) + mcl(:,2,jst) )/huit
5587       DO jsl = 2,nslm-1
5588          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
5589               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
5590       ENDDO
5591       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit
5592         
5593       !! And we compare the difference with the flux...
5594       ! Normally, tcmf=tmci-flux_top(ji)-transpir-dr_ns
5595       DO ji=1,kjpindex
5596          diag_tr(ji)=SUM(rootsink(ji,:,jst))
5597       ENDDO
5598       ! Here, check_tr_ns holds the inaccuracy during the redistribution phase
5599       check_tr_ns(:,jst) = tmcf(:)-(tmci(:)-flux_top(:)-dr_ns(:,jst)-diag_tr(:))
5600
5601       !! We solve here the numerical errors that happen when the soil is close to saturation
5602       !! and drainage very high, and which lead to negative check_tr_ns: the soil dries more
5603       !! than what is demanded by the fluxes, so we need to increase the fluxes.
5604       !! This is done by increasing the drainage.
5605       !! There are also instances of positive check_tr_ns, larger when the drainage is high
5606       !! They are similarly corrected by a decrease of dr_ns, in the limit of keeping a positive drainage.
5607       DO ji=1,kjpindex
5608          IF ( check_tr_ns(ji,jst) .LT. zero ) THEN
5609              dr_corrnum_ns(ji,jst) = -check_tr_ns(ji,jst)
5610          ELSE
5611              dr_corrnum_ns(ji,jst) = -MIN(dr_ns(ji,jst),check_tr_ns(ji,jst))             
5612          ENDIF
5613          dr_ns(ji,jst) = dr_ns(ji,jst) + dr_corrnum_ns(ji,jst) ! dr_ns increases/decrease if check_tr negative/positive
5614       ENDDO
5615       !! For water conservation check during redistribution
5616       IF (check_cwrr2) THEN         
5617          check_tr_ns(:,jst) = tmcf(:)-(tmci(:)-flux_top(:)-dr_ns(:,jst)-diag_tr(:)) 
5618       ENDIF
5619
5620       !! 3. AFTER DIFFUSION/REDISTRIBUTION
5621
5622       !! 3.1 Updating mc, as all the following checks against saturation will compare mc to mcs
5623       !      The frozen fraction is constant, so that any water flux to/from a layer changes
5624       !      both mcl and the ice amount. The assumption behind this is that water entering/leaving
5625       !      a soil layer immediately freezes/melts with the proportion profil_froz_hydro_ns/(1-profil_...)
5626       DO jsl = 1, nslm
5627          DO ji =1, kjpindex
5628             mc(ji,jsl,jst) = MAX( mcl(ji,jsl,jst), mcl(ji,jsl,jst) + &
5629                  profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
5630             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we get mc=mcl
5631          ENDDO
5632       ENDDO
5633!      IF (minval(mc) .LT. zero) THEN
5634!       WRITE (numout,*) 'BOOM mc LT zero 5573'
5635!      END IF
5636       !! 3.2 Correct here the possible over-saturation values (subroutine hydrol_soil_smooth_over_mcs2 acts on mc)
5637       !    Oversaturation results from numerical inaccuracies and can be frequent if free_drain_coef=0
5638       !    Here hydrol_soil_smooth_over_mcs2 discard all excess as ru_corr_ns, oriented to either ru_ns or dr_ns
5639       !    The former routine hydrol_soil_smooth_over_mcs, which keeps most of the excess in the soiltile
5640       !    after smoothing, first downward then upward, is kept in the module but not used here
5641       dr_corr_ns(:,jst) = zero
5642       ru_corr_ns(:,jst) = zero
5643       call hydrol_soil_smooth_over_mcs2(kjpindex, jst, njsc, is_over_mcs, ru_corr_ns, check_over_ns)
5644       
5645       ! In absence of freezing, if F is large enough, the correction of oversaturation is sent to drainage       
5646       DO ji = 1, kjpindex
5647          IF ((free_drain_coef(ji,jst) .GE. 0.5) .AND. (.NOT. ok_freeze_cwrr) ) THEN
5648             dr_corr_ns(ji,jst) = ru_corr_ns(ji,jst) 
5649             ru_corr_ns(ji,jst) = zero
5650          ENDIF
5651       ENDDO
5652       dr_ns(:,jst) = dr_ns(:,jst) + dr_corr_ns(:,jst)
5653       ru_ns(:,jst) = ru_ns(:,jst) + ru_corr_ns(:,jst)
5654
5655       !! 3.3 Negative runoff is reported to drainage
5656       !  Since we computed ru_ns directly from hydrol_soil_infilt, ru_ns should not be negative
5657             
5658       ru_corr2_ns(:,jst) = zero
5659       DO ji = 1, kjpindex
5660          IF (ru_ns(ji,jst) .LT. zero) THEN
5661             IF (printlev>=3)  WRITE (numout,*) 'NEGATIVE RU_NS: runoff and drainage before correction',&
5662                  ru_ns(ji,jst),dr_ns(ji,jst)
5663             dr_ns(ji,jst)=dr_ns(ji,jst)+ru_ns(ji,jst)
5664             ru_corr2_ns(ji,jst) = -ru_ns(ji,jst)
5665             ru_ns(ji,jst)= 0.
5666          END IF         
5667       ENDDO
5668
5669       !! 3.4 Optional block to force saturation below zwt_force
5670       ! We test if zwt_force(1,jst) <= zmaxh, to avoid steps 1 and 2 if unnecessary
5671       
5672       IF (zwt_force(1,jst) <= zmaxh) THEN
5673
5674          !! We force the nodes below zwt_force to be saturated
5675          !  As above, we compare mc to mcs
5676          DO jsl = 1,nslm
5677             DO ji = 1, kjpindex
5678                dmc(ji,jsl) = zero
5679                IF ( ( zz(jsl) >= zwt_force(ji,jst)*mille ) ) THEN
5680                   dmc(ji,jsl) = mcs(ji) - mc(ji,jsl,jst) ! addition to reach mcs (m3/m3) = positive value
5681                   mc(ji,jsl,jst) = mcs(ji)
5682                ENDIF
5683             ENDDO
5684          ENDDO
5685!       IF (minval(mc) .LT. zero) THEN
5686!       WRITE (numout,*) 'BOOM mc LT zero 5625'
5687!      END IF         
5688          !! To ensure conservation, this needs to be balanced by a negative change in drainage (in kg/m2/dt)
5689          DO ji = 1, kjpindex
5690             dr_force_ns(ji,jst) = dz(2) * ( trois*dmc(ji,1) + dmc(ji,2) )/huit ! top layer = initialization
5691          ENDDO
5692          DO jsl = 2,nslm-1 ! intermediate layers
5693             DO ji = 1, kjpindex
5694                dr_force_ns(ji,jst) = dr_force_ns(ji,jst) + dz(jsl) &
5695                     & * (trois*dmc(ji,jsl)+dmc(ji,jsl-1))/huit &
5696                     & + dz(jsl+1) * (trois*dmc(ji,jsl)+dmc(ji,jsl+1))/huit
5697             ENDDO
5698          ENDDO
5699          DO ji = 1, kjpindex
5700             dr_force_ns(ji,jst) = dr_force_ns(ji,jst) + dz(nslm) & ! bottom layer
5701                  & * (trois * dmc(ji,nslm) + dmc(ji,nslm-1))/huit
5702             dr_ns(ji,jst) = dr_ns(ji,jst) - dr_force_ns(ji,jst) ! dr_force_ns is positive and dr_ns must be reduced
5703          END DO
5704
5705       ELSE         
5706
5707          dr_force_ns(:,jst) = zero 
5708
5709       ENDIF
5710
5711       !! 3.5 Diagnosing the effective water table depth:
5712       !!     Defined as as the smallest jsl value when mc(jsl) is no more at saturation (mcs), starting from the bottom
5713       !      If there is a part of the soil which is saturated but underlain with unsaturated nodes,
5714       !      this is not considered as a water table
5715       DO ji = 1, kjpindex
5716          wtd_ns(ji,jst) = undef_sechiba ! in meters
5717          jsl=nslm
5718          DO WHILE ( (mc(ji,jsl,jst) .EQ. mcs(ji)) .AND. (jsl > 1) )
5719             wtd_ns(ji,jst) = zz(jsl)/mille ! in meters
5720             jsl=jsl-1   
5721          ENDDO
5722       ENDDO
5723
5724       !! 3.6 Diagnose under_mcr to adapt water stress calculation below
5725       !      This routine does not change tmc but decides where we should turn off ET to prevent further mc decrease
5726       !      Like above, the tests are made on total mc, compared to mcr
5727       CALL hydrol_soil_smooth_under_mcr(kjpindex, jst, njsc, is_under_mcr, check_under_ns)
5728 
5729       !! 4. At the end of the prognostic calculations, we recompute important moisture variables
5730
5731       !! 4.1 Total soil moisture content (water2infilt added below)
5732       DO ji = 1, kjpindex
5733          tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
5734       ENDDO
5735       DO jsl = 2,nslm-1
5736          DO ji = 1, kjpindex
5737             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) &
5738                  & * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
5739                  & + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
5740          ENDDO
5741       ENDDO
5742       DO ji = 1, kjpindex
5743          tmc(ji,jst) = tmc(ji,jst) + dz(nslm) &
5744               & * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
5745       END DO
5746
5747       !! 4.2 mcl is a module variable; we update it here for calculating bare soil evaporation,
5748       !!     and in case we would like to export it (xios)
5749       DO jsl = 1, nslm
5750          DO ji =1, kjpindex
5751             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(njsc(ji)) + &
5752                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
5753             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
5754          ENDDO
5755       ENDDO
5756       
5757       !! 5. Optional check of the water balance of soil column (if check_cwrr)
5758
5759       IF (check_cwrr) THEN
5760
5761          !! 5.1 Computation of the vertical water fluxes
5762          CALL hydrol_soil_flux(kjpindex,jst,mclint,flux_top)
5763         
5764          !! 5.2 Total mc conservation
5765          DO ji = 1,kjpindex   
5766             deltahum(ji) = (tmc(ji,jst) - tmcold(ji))
5767             diff(ji) = flux_infilt(ji) - flux_top(ji) - SUM(rootsink(ji,:,jst)) &
5768                   -ru_ns(ji,jst) - dr_ns(ji,jst)
5769             test(ji) = (ABS(deltahum(ji)-diff(ji))*mask_soiltile(ji,jst) .GT. allowed_err)
5770 
5771             IF (test(ji)) THEN             
5772                WRITE (numout,*)'CWRR water conservation pb:',ji,jst,njsc(ji),deltahum(ji)-diff(ji)
5773                WRITE (numout,*)'tmc,tmcold,diff',tmc(ji,jst),tmcold(ji),deltahum(ji)
5774                WRITE(numout,*) 'evapot,evapot_penm,ae_ns,flux_top',evapot(ji),evapot_penm(ji),&
5775                     ae_ns(ji,jst),flux_top(ji)
5776                WRITE (numout,*)'ru_ns,dr_ns,SUM(rootsink)',ru_ns(ji,jst),dr_ns(ji,jst), &
5777                     SUM(rootsink(ji,:,jst))
5778                WRITE (numout,*)'precisol, flux_infilt',precisol_ns(ji,jst)
5779                WRITE (numout,*)'irrigation, returnflow, reinfiltration', &
5780                      irrigation_soil(ji,jst),returnflow_soil(ji),reinfiltration_soil(ji)
5781                WRITE (numout,*)'mc',mc(ji,:,jst) ! along jsl
5782                WRITE (numout,*)'qflux',qflux(ji,:,jst) ! along jsl
5783                WRITE (numout,*)'k', k(ji,:) ! along jsl
5784                WRITE (numout,*)'soiltile',soiltile(ji,jst)
5785                WRITE (numout,*)'veget_max', veget_max(ji,:)
5786               
5787                error=.TRUE.
5788                CALL ipslerr_p(2, 'hydrol_soil', 'We will STOP in the end of this subroutine.',&
5789                     & 'CWRR water balance check','')
5790             ENDIF
5791          ENDDO
5792
5793          !! 5.3 Total mc should not reach zero, or the tridiag solver will have problems
5794          DO ji = 1,kjpindex
5795             IF(MINVAL(mc(ji,:,jst)).LT. min_sechiba) THEN
5796                WRITE (numout,*)'CWRR MC NEGATIVE', &
5797                     ji,lalo(ji,:),MINLOC(mc(ji,:,jst)),jst,mc(ji,:,jst)
5798                WRITE(numout,*) 'evapot,evapot_penm,ae_ns,flux_top',evapot(ji),evapot_penm(ji),&
5799                     ae_ns(ji,jst),flux_top(ji)
5800                WRITE (numout,*)'ru_ns,dr_ns,SUM(rootsink)',ru_ns(ji,jst),dr_ns(ji,jst), &
5801                     SUM(rootsink(ji,:,jst))
5802                WRITE (numout,*)'precisol, flux_infilt',precisol_ns(ji,jst)
5803                WRITE (numout,*)'irrigation, returnflow, reinfiltration', &
5804                      irrigation_soil(ji,jst),returnflow_soil(ji),reinfiltration_soil(ji)
5805                WRITE (numout,*)'mc',mc(ji,:,jst) ! along jsl
5806                WRITE (numout,*)'qflux',qflux(ji,:,jst) ! along jsl
5807                WRITE (numout,*)'k', k(ji,:) ! along jsl
5808                WRITE (numout,*)'soiltile',soiltile(ji,jst)
5809                WRITE (numout,*)'veget_max', veget_max(ji,:)             
5810
5811                error=.TRUE.
5812                CALL ipslerr_p(2, 'hydrol_soil', 'We will STOP in the end of this subroutine.',&
5813                     & 'CWRR MC NEGATIVE','')
5814             ENDIF
5815          END DO
5816
5817       ENDIF
5818
5819       !! 6. SM DIAGNOSTICS FOR OTHER ROUTINES, MODULES, OR NEXT STEP
5820       !    Starting here, mc and mcl should not change anymore
5821       
5822       !! 6.1 Total soil moisture, soil moisture at litter levels, soil wetness, us, humrelv, vesgtressv
5823       !!     (based on mc)
5824
5825       !! In output, tmc includes water2infilt(ji,jst)
5826       DO ji=1,kjpindex
5827          tmc(ji,jst) = tmc(ji,jst) + water2infilt(ji,jst)
5828       END DO
5829!gmjc top 5 layer mc for grazing
5830       ! The trampling depth is the 5 top levels of the soil
5831       ! Compute various field of soil moisture for the litter (used for stomate
5832       ! and for albedo)
5833
5834       DO ji=1,kjpindex
5835          tmc_trampling(ji,jst) = dz(2) * (trois*mc(ji,1,jst)+mc(ji,2,jst))/huit
5836          tmc_trampling(ji,jst) = tmc_trampling(ji,jst)
5837       END DO
5838
5839       ! sum from level 1 to 5
5840
5841       DO jsl=2,6
5842          DO ji=1,kjpindex
5843             tmc_trampling(ji,jst) = tmc_trampling(ji,jst) + dz(jsl) * &
5844                  & ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
5845                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
5846          END DO
5847       END DO
5848
5849!    tmc_topgrass(:) = tmc_trampling(:,3)
5850!WRITE (numout,*) 'sechiba tmc_trampling',tmc_trampling(:,jst),tmc(:,jst)
5851!WRITE (numout,*) 'sechiba mc',mc(:,1,jst)
5852!end gmjc
5853
5854       ! The litter is the 4 top levels of the soil
5855       ! Compute various field of soil moisture for the litter (used for stomate and for albedo)
5856       DO ji=1,kjpindex
5857          tmc_litter(ji,jst) = dz(2) * ( trois*mc(ji,1,jst)+ mc(ji,2,jst))/huit
5858       END DO
5859       ! sum from level 1 to 4
5860       DO jsl=2,4
5861          DO ji=1,kjpindex
5862             tmc_litter(ji,jst) = tmc_litter(ji,jst) + dz(jsl) * & 
5863                  & ( trois*mc(ji,jsl,jst) + mc(ji,jsl-1,jst))/huit &
5864                  & + dz(jsl+1)*(trois*mc(ji,jsl,jst) + mc(ji,jsl+1,jst))/huit
5865          END DO
5866       END DO
5867
5868       ! Subsequent calculation of soil_wet_litter (tmc-tmcw)/(tmcf-tmcw)
5869       DO ji=1,kjpindex
5870          soil_wet_litter(ji,jst) = MIN(un, MAX(zero,&
5871               & (tmc_litter(ji,jst)-tmc_litter_wilt(ji,jst)) / &
5872               & (tmc_litter_field(ji,jst)-tmc_litter_wilt(ji,jst)) ))
5873       END DO
5874
5875       ! Preliminary calculation of various soil moistures (for each layer, in kg/m2)
5876       sm(:,1)  = dz(2) * (trois*mcl(:,1,jst) + mcl(:,2,jst))/huit
5877       smw(:,1) = dz(2) * (quatre*mcw(:))/huit
5878       smf(:,1) = dz(2) * (quatre*mcf(:))/huit
5879       sms(:,1) = dz(2) * (quatre*mcs(:))/huit
5880       smw_tmp(:,1) = dz(2) * (quatre*mcw_mineral(njsc(:)))/huit
5881       smf_tmp(:,1) = dz(2) * (quatre*mcf_mineral(njsc(:)))/huit
5882       sms_tmp(:,1) = dz(2) * (quatre*mcs_mineral(njsc(:)))/huit
5883       DO jsl = 2,nslm-1
5884          sm(:,jsl)  = dz(jsl) * (trois*mcl(:,jsl,jst)+mcl(:,jsl-1,jst))/huit &
5885               + dz(jsl+1) * (trois*mcl(:,jsl,jst)+mcl(:,jsl+1,jst))/huit
5886          smw(:,jsl) = dz(jsl) * ( quatre*mcw(:) )/huit &
5887               + dz(jsl+1) * ( quatre*mcw(:) )/huit
5888          smf(:,jsl) = dz(jsl) * ( quatre*mcf(:) )/huit &
5889               + dz(jsl+1) * ( quatre*mcf(:) )/huit
5890          sms(:,jsl) = dz(jsl) * ( quatre*mcs(:) )/huit &
5891               + dz(jsl+1) * ( quatre*mcs(:) )/huit
5892          smw_tmp(:,jsl) = dz(jsl) * ( quatre*mcw_mineral(njsc(:)) )/huit + dz(jsl+1) * ( quatre*mcw_mineral(njsc(:)) )/huit
5893          smf_tmp(:,jsl) = dz(jsl) * ( quatre*mcf_mineral(njsc(:)) )/huit + dz(jsl+1) * ( quatre*mcf_mineral(njsc(:)) )/huit
5894          sms_tmp(:,jsl) = dz(jsl) * ( quatre*mcs_mineral(njsc(:)) )/huit + dz(jsl+1) * ( quatre*mcs_mineral(njsc(:)) )/huit
5895       ENDDO
5896       sm(:,nslm)  = dz(nslm) * (trois*mcl(:,nslm,jst) + mcl(:,nslm-1,jst))/huit     
5897       smw(:,nslm) = dz(nslm) * (quatre*mcw(:))/huit
5898       smf(:,nslm) = dz(nslm) * (quatre*mcf(:))/huit
5899       sms(:,nslm) = dz(nslm) * (quatre*mcs(:))/huit
5900       smw_tmp(:,nslm) = dz(nslm) * (quatre*mcw_mineral(njsc(:)))/huit
5901       smf_tmp(:,nslm) = dz(nslm) * (quatre*mcf_mineral(njsc(:)))/huit
5902       sms_tmp(:,nslm) = dz(nslm) * (quatre*mcs_mineral(njsc(:)))/huit
5903       ! sm_nostress = soil moisture of each layer at which us reaches 1, here at the middle of [smw,smf]
5904       DO jsl = 1,nslm
5905          sm_nostress(:,jsl) = smw(:,jsl) + pcent(njsc(:)) * (smf(:,jsl)-smw(:,jsl))
5906       END DO
5907
5908       ! Saturated litter soil moisture for rsoil
5909       tmcs_litter(:) = zero
5910       DO jsl = 1,4
5911          tmcs_litter(:) = tmcs_litter(:) + sms(:,jsl)
5912       END DO
5913             
5914       ! Soil wetness profiles (W-Ww)/(Ws-Ww)
5915       ! soil_wet is the ratio of available soil moisture to max available soil moisture
5916       ! (ie soil moisture at saturation minus soil moisture at wilting point).
5917       ! soil wet is a water stress for stomate, to control C decomposition
5918       DO jsl=1,nslm
5919          DO ji=1,kjpindex
5920             soil_wet(ji,jsl,jst) = MIN(un, MAX(zero, &
5921                  (sm(ji,jsl)-smw_tmp(ji,jsl))*(sms(ji,jsl)-smw(ji,jsl))/(sms_tmp(ji,jsl)-smw_tmp(ji,jsl))**2 ))
5922          END DO
5923       END DO
5924
5925       ! Compute us and the new humrelv to use in sechiba (with loops on the vegetation types)
5926       ! This is the water stress for transpiration (diffuco) and photosynthesis (diffuco)
5927       ! humrel is never used in stomate
5928
5929       ! -- PFT1
5930       humrelv(:,1,jst) = zero       
5931       ! -- Top layer
5932       DO jv = 2,nvm
5933          DO ji=1,kjpindex
5934             !- Here we make the assumption that roots do not take water from the 1st layer.
5935             us(ji,jv,jst,1) = zero
5936             humrelv(ji,jv,jst) = zero ! initialisation of the sum
5937          END DO
5938       ENDDO
5939
5940       IF (ok_freeze_cwrr) THEN
5941           CALL hydrol_soil_coef(kjpindex,jst,njsc)
5942       ENDIF
5943
5944       !! Dynamic nroot to optimize water use: the root profile used to weight the water stress function
5945       !! of each soil layer is updated at each time step in order to match the soil water profile
5946       !! (the soil water content of each layer available for transpiration)
5947       IF (ok_dynroot) THEN
5948          DO jv = 1, nvm
5949             IF ( is_tree(jv) ) THEN
5950                DO ji = 1,kjpindex
5951                   nroot_tmp(:) = zero
5952                   DO jsl = 2,nslm
5953                      nroot_tmp(jsl) = MIN(un,MAX(zero,(sm(ji,jsl)-smw_tmp(ji,jsl))/(pcent(njsc(ji))*(smf_tmp(ji,jsl)-smw_tmp(ji,jsl)))*(smf(ji,jsl)-smw(ji,jsl))/(smf_tmp(ji,jsl)-smw_tmp(ji,jsl)) ))
5954                      IF (nroot(ji,jv,jsl) .EQ. zero) nroot_tmp(jsl)=zero
5955                   ENDDO
5956                   IF (SUM(nroot_tmp(:)) .GT. zero ) nroot(ji,jv,:)=nroot_tmp(:)/SUM(nroot_tmp(:))
5957               ENDDO
5958
5959             ELSE
5960                ! Specific case for grasses where we only consider the first 1m of soil.               
5961                DO ji = 1, kjpindex
5962                   nroot_tmp(:) = zero
5963                   DO jsl = 2,nslm
5964                      IF (znt(jsl) .LT. un) THEN
5965                         nroot_tmp(jsl) = MIN(un,MAX(zero,(sm(ji,jsl)-smw_tmp(ji,jsl))/(pcent(njsc(ji))*(smf_tmp(ji,jsl)-smw_tmp(ji,jsl)))*(smf(ji,jsl)-smw(ji,jsl))/(smf_tmp(ji,jsl)-smw_tmp(ji,jsl)) ))
5966                         IF (nroot(ji,jv,jsl) .EQ. zero) nroot_tmp(jsl)=zero
5967                      ENDIF
5968                   ENDDO
5969
5970                   IF (SUM(nroot_tmp(:)) .GT. zero ) THEN
5971                      DO jsl = 2,nslm
5972                         IF (znt(jsl) .LT. un) THEN
5973                            nroot(ji,jv,jsl)=nroot_tmp(jsl)/SUM(nroot_tmp(:))
5974                         ELSE
5975                            nroot(ji,jv,jsl)= zero
5976                         ENDIF ! (znt(jsl) .LT. un)
5977                      ENDDO ! jsl = 2,nslm
5978                   ENDIF ! SUM(nroot_tmp(:)) .GT. zero )
5979                ENDDO ! ji = 1, kjpindex
5980             ENDIF ! ( is_tree(jv) ) THEN
5981          ENDDO ! jv = 1, nvm
5982       ENDIF ! (ok_dynroot) THEN
5983
5984       ! -- Intermediate and bottom layers
5985       DO jsl = 2,nslm
5986          DO jv = 2, nvm
5987             DO ji=1,kjpindex
5988                ! AD16*** Although plants can only withdraw liquid water, we compute here the water stress
5989                ! based on mc and the corresponding thresholds mcs, pcent, or potentially mcw and mcf
5990                ! This is consistent with assuming that ice is uniformly distributed within the poral space
5991                ! In such a case, freezing makes mcl and the "liquid" porosity smaller than the "total" values
5992                ! And it is the same for all the moisture thresholds, which are proportional to porosity.
5993                ! Since the stress is based on relative moisture, it could thus independent from the porosity
5994                ! at first order, thus independent from freezing.             
5995                IF(new_watstress) THEN
5996                   IF((sm(ji,jsl)-smw(ji,jsl)) .GT. min_sechiba) THEN
5997                      us(ji,jv,jst,jsl) = MIN(un, MAX(zero, &
5998                           (EXP(- alpha_watstress * &
5999                           ( (smf(ji,jsl) - smw(ji,jsl)) / ( sm_nostress(ji,jsl) - smw(ji,jsl)) ) * &
6000                           ( (sm_nostress(ji,jsl) - sm(ji,jsl)) / ( sm(ji,jsl) - smw(ji,jsl)) ) ) ) ))&
6001                           * nroot(ji,jv,jsl)
6002                   ELSE
6003                      us(ji,jv,jst,jsl) = 0.
6004                   ENDIF
6005                ELSE
6006                   us(ji,jv,jst,jsl) = MIN(un, MAX(zero, &
6007                        (sm(ji,jsl)-smw_tmp(ji,jsl))/(pcent(njsc(ji))*(smf_tmp(ji,jsl)-smw_tmp(ji,jsl)))*(smf(ji,jsl)-smw(ji,jsl))/(smf_tmp(ji,jsl)-smw_tmp(ji,jsl)) )) * nroot(ji,jv,jsl)
6008                ENDIF
6009                humrelv(ji,jv,jst) = humrelv(ji,jv,jst) + us(ji,jv,jst,jsl)
6010             END DO
6011          END DO
6012       ENDDO
6013
6014       !! vegstressv is the water stress for phenology in stomate
6015       !! It varies linearly from zero at wilting point to 1 at field capacity
6016       vegstressv(:,:,jst) = zero
6017       DO jv = 2, nvm
6018          DO ji=1,kjpindex
6019             DO jsl=1,nslm
6020                vegstressv(ji,jv,jst) = vegstressv(ji,jv,jst) + &
6021                     MIN(un, MAX(zero, (sm(ji,jsl)-smw_tmp(ji,jsl))*(smf(ji,jsl)-smw(ji,jsl))/(smf_tmp(ji,jsl)-smw_tmp(ji,jsl))**2 ) ) &
6022                     * nroot(ji,jv,jsl)
6023             END DO
6024          END DO
6025       END DO
6026
6027
6028       ! -- If the PFT is absent, the corresponding humrelv and vegstressv = 0
6029       DO jv = 2, nvm
6030          DO ji = 1, kjpindex
6031             IF (vegetmax_soil(ji,jv,jst) .LT. min_sechiba) THEN
6032                humrelv(ji,jv,jst) = zero
6033                vegstressv(ji,jv,jst) = zero
6034                us(ji,jv,jst,:) = zero
6035             ENDIF
6036          END DO
6037       END DO
6038
6039       !! 6.2 We need to turn off evaporation when is_under_mcr
6040       !!     We set us, humrelv and vegstressv to zero in this case
6041       !!     WARNING: It's different from having locally us=0 in the soil layers(s) where mc<mcr
6042       !!              This part is crucial to preserve water conservation
6043       DO jsl = 1,nslm
6044          DO jv = 2, nvm
6045             WHERE (is_under_mcr(:,jst))
6046                us(:,jv,jst,jsl) = zero
6047             ENDWHERE
6048          ENDDO
6049       ENDDO
6050       DO jv = 2, nvm
6051          WHERE (is_under_mcr(:,jst))
6052             humrelv(:,jv,jst) = zero
6053          ENDWHERE
6054       ENDDO
6055       
6056       ! For consistency in stomate, we also set moderwilt and soil_wet to zero in this case.
6057       ! They are used later for shumdiag and shumdiag_perma
6058       DO jsl = 1,nslm
6059          WHERE (is_under_mcr(:,jst))
6060             soil_wet(:,jsl,jst) = zero
6061          ENDWHERE
6062       ENDDO
6063
6064       ! Counting the nb of under_mcr occurences in each grid-cell
6065       WHERE (is_under_mcr(:,jst))
6066          undermcr = undermcr + un
6067       ENDWHERE
6068
6069       !! 6.3 Calculate the volumetric soil moisture content (mc_layh and mcl_layh) needed in
6070       !!     thermosoil for the thermal conductivity. Calculate also total soil moisture content(tmc_layh)
6071       !!     needed in thermosoil for the heat capacity.
6072       !! The multiplication by vegtot creates grid-cell average values
6073       ! *** To be checked for consistency with the use of nobio properties in thermosoil
6074       mc_layh_s = mc
6075       mcl_layh_s = mc
6076       DO ji=1,kjpindex
6077          DO jsl=1,nslm
6078             mc_layh(ji,jsl) = mc_layh(ji,jsl) + mc(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji) 
6079             mcl_layh(ji,jsl) = mcl_layh(ji,jsl) + mcl(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji)
6080          ENDDO
6081          tmc_layh_ns(ji,1,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
6082          DO jsl = 2,nslm-1
6083             tmc_layh_ns(ji,jsl,jst) = dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
6084                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
6085          ENDDO
6086          tmc_layh_ns(ji,nslm,jst) = dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
6087          DO jsl = 1,nslm
6088             tmc_layh(ji,jsl) = tmc_layh(ji,jsl) + tmc_layh_ns(ji,jsl,jst) * soiltile(ji,jst) * vegtot(ji)
6089          ENDDO
6090       END DO
6091
6092       !! 6.4 The hydraulic conductivities exported here are the ones used in the diffusion/redistribution
6093       ! (no call of hydrol_soil_coef since 2.1)
6094       ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6095       IF (ok_freeze_cwrr) THEN
6096          DO ji = 1, kjpindex
6097             kk_moy(ji,:) = kk_moy(ji,:) + soiltile(ji,jst) * k(ji,:) * vegtot(ji)
6098             kk(ji,:,jst) = k(ji,:)
6099          ENDDO
6100       ENDIF
6101       
6102      IF (printlev>=3) WRITE (numout,*) ' prognostic/diagnostic part of hydrol_soil done for jst =', jst         
6103
6104   END DO  ! end of loop on soiltile
6105
6106!gmjc top 5 layer grassland soil moisture for grazing
6107    ! should be calculated after loop soiltile
6108    ! tmc_trampling unit mm water
6109    ! for soil moisture, it should be divided by 5 layer soil depth
6110    tmc_topgrass(:) = tmc_trampling(:,3)/(SUM(dz(1:6))+dz(7)/2)
6111!WRITE (numout,*) 'sechiba tmc',tmc(:,jst),tmc_topgrass(:)
6112!end gmjc
6113
6114    !! -- ENDING THE MAIN LOOP ON SOILTILES
6115
6116    !! 7. Summing 3d variables into 2d variables
6117    CALL hydrol_diag_soil (kjpindex, veget_max, soiltile, njsc, runoff, drainage, &
6118         & evapot, vevapnu, returnflow, reinfiltration, irrigation, &
6119         & shumdiag,shumdiag_perma, k_litt, litterhumdiag, humrel, vegstress, drysoil_frac,tot_melt, & !pss:+
6120         & drunoff_tot) !pss:-
6121
6122    ! Means of wtd, runoff and drainage corrections, across soiltiles   
6123    wtd(:) = zero 
6124    ru_corr(:) = zero
6125    ru_corr2(:) = zero
6126    dr_corr(:) = zero
6127    dr_corrnum(:) = zero
6128    dr_force(:) = zero
6129    DO jst = 1, nstm
6130       DO ji = 1, kjpindex 
6131          wtd(ji) = wtd(ji) + soiltile(ji,jst) * wtd_ns(ji,jst) ! average over vegtot only
6132          IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
6133             ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6134             ru_corr(ji) = ru_corr(ji) + vegtot(ji) * soiltile(ji,jst) * ru_corr_ns(ji,jst) 
6135             ru_corr2(ji) = ru_corr2(ji) + vegtot(ji) * soiltile(ji,jst) * ru_corr2_ns(ji,jst) 
6136             dr_corr(ji) = dr_corr(ji) + vegtot(ji) * soiltile(ji,jst) * dr_corr_ns(ji,jst) 
6137             dr_corrnum(ji) = dr_corrnum(ji) + vegtot(ji) * soiltile(ji,jst) * dr_corrnum_ns(ji,jst)
6138             dr_force(ji) = dr_force(ji) - vegtot(ji) * soiltile(ji,jst) * dr_force_ns(ji,jst)
6139                                       ! the sign is OK to get a negative drainage flux
6140          ENDIF
6141       ENDDO
6142    ENDDO
6143
6144    ! Means local variables, including water conservation checks
6145    ru_infilt(:)=0.
6146    qinfilt(:)=0.
6147    check_infilt(:)=0.
6148    check_tr(:)=0.
6149    check_over(:)=0.
6150    check_under(:)=0.
6151    DO jst = 1, nstm
6152       DO ji = 1, kjpindex 
6153          IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
6154             ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6155             ru_infilt(ji) = ru_infilt(ji) + vegtot(ji) * soiltile(ji,jst) * ru_infilt_ns(ji,jst)
6156             qinfilt(ji) = qinfilt(ji) + vegtot(ji) * soiltile(ji,jst) * qinfilt_ns(ji,jst)
6157          ENDIF
6158       ENDDO
6159    ENDDO
6160 
6161    IF (check_cwrr2) THEN
6162       DO jst = 1, nstm
6163          DO ji = 1, kjpindex 
6164             IF (vegtot(ji) .GT. min_sechiba) THEN ! to mimic hydrol_diag_soil
6165                ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
6166                check_infilt(ji) = check_infilt(ji) + vegtot(ji) * soiltile(ji,jst) * check_infilt_ns(ji,jst)
6167                check_tr(ji) = check_tr(ji) + vegtot(ji) * soiltile(ji,jst) * check_tr_ns(ji,jst)
6168                check_over(ji) = check_over(ji) + vegtot(ji) * soiltile(ji,jst) * check_over_ns(ji,jst)
6169                check_under(ji) =  check_under(ji) + vegtot(ji) * soiltile(ji,jst) * check_under_ns(ji,jst)
6170             ENDIF
6171          ENDDO
6172       ENDDO
6173    END IF
6174    !! 8. COMPUTING EVAP_BARE_LIM_NS FOR NEXT TIME STEP, WITH A LOOP ON SOILTILES
6175    !!    The principle is to run a dummy integration of the water redistribution scheme
6176    !!    to check if the SM profile can sustain a potential evaporation.
6177    !!    If not, the dummy integration is redone from the SM profile of the end of the normal integration,
6178    !!    with a boundary condition leading to a very severe water limitation: mc(1)=mcr
6179
6180    ! evap_bare_lim = beta factor for bare soil evaporation
6181    evap_bare_lim(:) = zero
6182    evap_bare_lim_ns(:,:) = zero
6183!    evap_bare_lim_pft(:,:) = zero
6184
6185    ! Loop on soil tiles 
6186    DO jst = 1,nstm
6187
6188       !! 8.1 Save actual mc, mcl, and tmc for restoring at the end of the time step
6189       !!      and calculate tmcint corresponding to mc without water2infilt
6190       DO jsl = 1, nslm
6191          DO ji = 1, kjpindex
6192             mcint(ji,jsl) = mask_soiltile(ji,jst) * mc(ji,jsl,jst)
6193             mclint(ji,jsl) = mask_soiltile(ji,jst) * mcl(ji,jsl,jst)
6194          ENDDO
6195       ENDDO
6196
6197       DO ji = 1, kjpindex
6198          temp(ji) = tmc(ji,jst)
6199          tmcint(ji) = temp(ji) - water2infilt(ji,jst) ! to estimate bare soil evap based on water budget
6200       ENDDO
6201
6202       !! 8.2 Since we estimate bare soile evap for the next time step, we update profil_froz_hydro and mcl
6203       !     (effect of mc only, the change in temp_hydro is neglected)
6204       IF ( ok_freeze_cwrr ) CALL hydrol_soil_froz(kjpindex,jst,njsc)
6205        DO jsl = 1, nslm
6206          DO ji =1, kjpindex
6207             mcl(ji,jsl,jst)= MIN( mc(ji,jsl,jst), mcr(njsc(ji)) + &
6208                  (un-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
6209             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we keep mcl=mc
6210          ENDDO
6211       ENDDO         
6212
6213       !! 8.3 K and D are recomputed for the updated profile of mc/mcl
6214       CALL hydrol_soil_coef(kjpindex,jst,njsc)
6215
6216       !! 8.4 Set the tridiagonal matrix coefficients for the diffusion/redistribution scheme
6217       CALL hydrol_soil_setup(kjpindex,jst)
6218       resolv(:) = (mask_soiltile(:,jst) .GT. 0) 
6219
6220       !! 8.5 We define the system of linear equations, based on matrix coefficients,
6221
6222       !- Impose potential evaporation as flux_top in mm/step, assuming the water is available
6223       ! Note that this should lead to never have evapnu>evapot_penm(ji)
6224
6225       DO ji = 1, kjpindex
6226         
6227          IF (vegtot(ji).GT.min_sechiba) THEN
6228             
6229             ! We calculate a reduced demand, by means of a soil resistance
6230             IF (do_rsoil) THEN
6231                mc_rel(ji) = tmc_litter(ji,jst)/tmcs_litter(ji)
6232                ! based on SM in the top 4 soil layers (litter) to smooth variability
6233                r_soil_ns(ji,jst) = exp(8.206 - 4.255 * mc_rel(ji))
6234             ELSE
6235                r_soil_ns(ji,jst) = zero
6236             ENDIF
6237
6238             ! Aerodynamic resistance
6239             speed = MAX(min_wind, SQRT (u(ji)*u(ji) + v(ji)*v(ji)))
6240             IF (speed * tq_cdrag(ji) .GT. min_sechiba) THEN
6241                ra = un / (speed * tq_cdrag(ji))
6242                evap_soil(ji) = evapot_penm(ji) / (un + r_soil_ns(ji,jst)/ra)
6243             ELSE
6244                evap_soil(ji) = evapot_penm(ji)
6245             ENDIF
6246             
6247       ! AD16*** et si evap_bare_lim_ns<0 ?? car on suppose que tmcint > tmc(new)
6248       ! (water2inflit permet de propager de la ponded water d'un pas de temps a l'autre:
6249       ! peut-on s'en servir pour creer des cas d'evapnu potentielle negative ? a gerer dans diffuco ?)
6250             
6251             flux_top(ji) = evap_soil(ji) * &
6252                  AINT(frac_bare_ns(ji,jst)+un-min_sechiba)
6253          ELSE
6254             
6255             flux_top(ji) = zero
6256             
6257          ENDIF
6258       ENDDO
6259
6260       IF (ok_freeze_cwrr) THEN
6261          CALL hydrol_soil_coef(kjpindex,jst,njsc)
6262          DO ji =1, kjpindex
6263             DO jsl = 1, nslm
6264                mcl(ji,jsl,jst)= MIN(mc(ji,jsl,jst),mcr(njsc(ji))+(1-profil_froz_hydro_ns(ji,jsl,jst))*(mc(ji,jsl,jst)-mcr(njsc(ji))))
6265             ENDDO
6266          ENDDO
6267       ELSE
6268          mcl(:,:,jst)=mc(:,:,jst)
6269       ENDIF
6270
6271       ! We don't use rootsinks, because we assume there is no transpiration in the bare soil fraction (??)
6272       !- First layer
6273       DO ji = 1, kjpindex
6274          tmat(ji,1,1) = zero
6275          tmat(ji,1,2) = f(ji,1)
6276          tmat(ji,1,3) = g1(ji,1)
6277          rhs(ji,1)    = fp(ji,1) * mcl(ji,1,jst) + gp(ji,1)*mcl(ji,2,jst) &
6278               - flux_top(ji) - (b(ji,1)+b(ji,2))/deux *(dt_sechiba/one_day)
6279       ENDDO
6280       !- soil body
6281       DO jsl=2, nslm-1
6282          DO ji = 1, kjpindex
6283             tmat(ji,jsl,1) = e(ji,jsl)
6284             tmat(ji,jsl,2) = f(ji,jsl)
6285             tmat(ji,jsl,3) = g1(ji,jsl)
6286             rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
6287                  +  gp(ji,jsl) * mcl(ji,jsl+1,jst) &
6288                  + (b(ji,jsl-1) - b(ji,jsl+1)) * (dt_sechiba/one_day) / deux
6289          ENDDO
6290       ENDDO
6291       !- Last layer
6292       DO ji = 1, kjpindex
6293          jsl=nslm
6294          tmat(ji,jsl,1) = e(ji,jsl)
6295          tmat(ji,jsl,2) = f(ji,jsl)
6296          tmat(ji,jsl,3) = zero
6297          rhs(ji,jsl) = ep(ji,jsl)*mcl(ji,jsl-1,jst) + fp(ji,jsl)*mcl(ji,jsl,jst) &
6298               + (b(ji,jsl-1) + b(ji,jsl)*(un-deux*free_drain_coef(ji,jst))) * (dt_sechiba/one_day) / deux
6299       ENDDO
6300       !- Store the equations for later use (9.6)
6301       DO jsl=1,nslm
6302          DO ji = 1, kjpindex
6303             srhs(ji,jsl) = rhs(ji,jsl)
6304             stmat(ji,jsl,1) = tmat(ji,jsl,1)
6305             stmat(ji,jsl,2) = tmat(ji,jsl,2)
6306             stmat(ji,jsl,3) = tmat(ji,jsl,3)
6307          ENDDO
6308       ENDDO
6309
6310       !! 8.6 Solve the diffusion equation, assuming that flux_top=evapot_penm (updates mcl)
6311       CALL hydrol_soil_tridiag(kjpindex,jst)
6312
6313       !! 9.7 Alternative solution with mc(1)=mcr in points where the above solution leads to mcl<mcr
6314       ! hydrol_soil_tridiag calculates mc recursively from the top as a fonction of rhs and tmat
6315       ! We re-use these the above values, but for mc(1)=mcr and the related tmat
6316       
6317       DO ji = 1, kjpindex
6318          ! by construction, mc and mcl are always on the same side of mcr, so we can use mcl here
6319          resolv(ji) = (mcl(ji,1,jst).LT.(mcr(njsc(ji))).AND.flux_top(ji).GT.min_sechiba)
6320       ENDDO
6321       !! Reset the coefficient for diffusion (tridiag is only solved if resolv(ji) = .TRUE.)O
6322       DO jsl=1,nslm
6323          !- The new condition is to put the upper layer at residual soil moisture
6324          DO ji = 1, kjpindex
6325             rhs(ji,jsl) = srhs(ji,jsl)
6326             tmat(ji,jsl,1) = stmat(ji,jsl,1)
6327             tmat(ji,jsl,2) = stmat(ji,jsl,2)
6328             tmat(ji,jsl,3) = stmat(ji,jsl,3)
6329          END DO
6330       END DO
6331       
6332       DO ji = 1, kjpindex
6333          tmat(ji,1,2) = un
6334          tmat(ji,1,3) = zero
6335          rhs(ji,1) = mcr(njsc(ji))
6336       ENDDO
6337       
6338       ! Solves the diffusion equation with new surface bc where resolv=T
6339       CALL hydrol_soil_tridiag(kjpindex,jst)
6340
6341       ! Calculation of total soil moisture content (liquid + frozen)
6342       IF (ok_freeze_cwrr) THEN
6343          CALL hydrol_soil_coef(kjpindex,jst,njsc)           
6344          DO ji =1, kjpindex
6345             DO jsl = 1, nslm
6346                mc(ji,jsl,jst)=MAX(mcl(ji,jsl,jst), mcl(ji,jsl,jst)+profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(njsc(ji))))
6347             ENDDO
6348          ENDDO
6349       ELSE
6350          mc(:,:,jst)=mcl(:,:,jst)
6351       ENDIF
6352!      IF (minval(mc) .LT. zero) THEN
6353!       WRITE (numout,*) 'BOOM mc LT zero 6292'
6354!      END IF
6355
6356       !! Correct bad moisture content due to numerical errors before water balance
6357       !! 8.8 In both case, we have drainage to be consistent with rhs
6358       DO ji = 1, kjpindex
6359          flux_bottom(ji) = mask_soiltile(ji,jst)*k(ji,nslm)*free_drain_coef(ji,jst) * (dt_sechiba/one_day)
6360       ENDDO
6361       
6362       !! 8.9 Water budget to assess the top flux = soil evaporation
6363       !      Where resolv=F at the 2nd step (9.6), it should simply be the potential evaporation
6364
6365       ! Total soil moisture content for water budget
6366
6367       DO jsl = 1, nslm
6368          DO ji =1, kjpindex
6369             mc(ji,jsl,jst) = MAX( mcl(ji,jsl,jst), mcl(ji,jsl,jst) + &
6370                  profil_froz_hydro_ns(ji,jsl,jst)*(mc(ji,jsl,jst)-mcr(njsc(ji))) )
6371             ! if profil_froz_hydro_ns=0 (including NOT ok_freeze_cwrr) we get mc=mcl
6372          ENDDO
6373       ENDDO
6374!       IF (minval(mc) .LT. zero) THEN
6375!       WRITE (numout,*) 'BOOM mc LT zero 6314'
6376!      END IF     
6377       DO ji = 1, kjpindex
6378          tmc(ji,jst) = dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
6379       ENDDO       
6380       DO jsl = 2,nslm-1
6381          DO ji = 1, kjpindex
6382             tmc(ji,jst) = tmc(ji,jst) + dz(jsl) &
6383                  * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
6384                  + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit
6385          ENDDO
6386       ENDDO
6387       DO ji = 1, kjpindex
6388          tmc(ji,jst) = tmc(ji,jst) + dz(nslm) &
6389               * (trois * mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
6390       END DO
6391   
6392       ! Deduce upper flux from soil moisture variation and bottom flux
6393       ! TMCi-D-BSE=TMC (BSE=bare soil evap=TMCi-TMC-D)
6394       ! The numerical errors of tridiag close to saturation cannot be simply solved here,
6395       ! we can only hope they are not too large because we don't add water at this stage...
6396       DO ji = 1, kjpindex
6397          evap_bare_lim_ns(ji,jst) = mask_soiltile(ji,jst) * &
6398               (tmcint(ji)-tmc(ji,jst)-flux_bottom(ji))
6399       END DO
6400
6401       !! 8.10 evap_bare_lim_ns is turned from an evaporation rate to a beta
6402       DO ji = 1, kjpindex
6403          ! Here we weight evap_bare_lim_ns by the fraction of bare evaporating soil.
6404          ! This is given by frac_bare_ns, taking into account bare soil under vegetation
6405          IF(vegtot(ji) .GT. min_sechiba) THEN
6406             evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) * frac_bare_ns(ji,jst)
6407          ELSE
6408             evap_bare_lim_ns(ji,jst) = 0.
6409          ENDIF
6410       END DO
6411
6412       ! We divide by evapot, which is consistent with diffuco (evap_bare_lim_ns < evapot_penm/evapot)
6413       ! Further decrease if tmc_litter is below the wilting point
6414
6415       IF (do_rsoil) THEN
6416          DO ji=1,kjpindex
6417             IF (evapot(ji).GT.min_sechiba) THEN
6418                evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) / evapot(ji)
6419             ELSE
6420                evap_bare_lim_ns(ji,jst) = zero ! not redundant with the is_under_mcr case below
6421                                                ! but not necessarily useful
6422             END IF
6423             evap_bare_lim_ns(ji,jst)=MAX(MIN(evap_bare_lim_ns(ji,jst),1.),0.)
6424          END DO
6425       ELSE
6426          DO ji=1,kjpindex
6427             IF ((evapot(ji).GT.min_sechiba) .AND. &
6428                  (tmc_litter(ji,jst).GT.(tmc_litter_wilt(ji,jst)))) THEN
6429                evap_bare_lim_ns(ji,jst) = evap_bare_lim_ns(ji,jst) / evapot(ji)
6430             ELSEIF((evapot(ji).GT.min_sechiba).AND. &
6431                  (tmc_litter(ji,jst).GT.(tmc_litter_res(ji,jst)))) THEN
6432                evap_bare_lim_ns(ji,jst) =  (un/deux) * evap_bare_lim_ns(ji,jst) / evapot(ji)
6433                ! This is very arbitrary, with no justification from the literature
6434             ELSE
6435                evap_bare_lim_ns(ji,jst) = zero
6436             END IF
6437             evap_bare_lim_ns(ji,jst)=MAX(MIN(evap_bare_lim_ns(ji,jst),1.),0.)
6438          END DO
6439       ENDIF
6440
6441       !! 8.11 Set evap_bare_lim_ns to zero if is_under_mcr at the end of the prognostic loop
6442       !!      (cf us, humrelv, vegstressv in 5.2)
6443       WHERE (is_under_mcr(:,jst))
6444          evap_bare_lim_ns(:,jst) = zero
6445       ENDWHERE
6446
6447       !! 8.12 Restores mc, mcl, and tmc, to erase the effect of the dummy integrations
6448       !!      on these prognostic variables
6449       DO jsl = 1, nslm
6450          DO ji = 1, kjpindex
6451             mc(ji,jsl,jst) = mask_soiltile(ji,jst) * mcint(ji,jsl)
6452             mcl(ji,jsl,jst) = mask_soiltile(ji,jst) * mclint(ji,jsl)
6453          ENDDO
6454       ENDDO
6455!       IF (minval(mc) .LT. zero) THEN
6456!       WRITE (numout,*) 'BOOM mc LT zero 6395'
6457!      END IF
6458       DO ji = 1, kjpindex
6459          tmc(ji,jst) = temp(ji)
6460       ENDDO
6461
6462    ENDDO !end loop on tiles for dummy integration
6463
6464    !! 9. evap_bar_lim is the grid-cell scale beta
6465    DO ji = 1, kjpindex
6466       evap_bare_lim(ji) =  SUM(evap_bare_lim_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
6467       r_soil(ji) =  SUM(r_soil_ns(ji,:)*vegtot(ji)*soiltile(ji,:))
6468    ENDDO
6469
6470    !! 10. Writing variables to DOC calculation in stomate
6471    wat_flux(:,:,:) = zero
6472    wat_flux0(:,:) = zero
6473    soil_mc(:,:,:)=zero
6474    litter_mc(:,:)=zero
6475    drainage_per_soil(:,:) = zero
6476    runoff_per_soil(:,:) = zero
6477    soil_mc(:,:,:)=mc(:,:,:)
6478    litter_mc(:,:)=tmc_litter(:,:)
6479    drainage_per_soil(:,:) = dr_ns(:,:)
6480    runoff_per_soil(:,:) = ru_ns(:,:)
6481    wat_flux(:,:,:) = qflux(:,:,:)
6482    !wat_flux0(:,:) = qflux00(:,:)
6483
6484    !! 10. XIOS export of local variables, including water conservation checks
6485
6486    CALL xios_orchidee_send_field("wtd",wtd) ! in m
6487    CALL xios_orchidee_send_field("ru_corr",ru_corr/dt_sechiba)   ! adjustment flux added to surface runoff (included in runoff)
6488    CALL xios_orchidee_send_field("ru_corr2",ru_corr2/dt_sechiba)
6489    CALL xios_orchidee_send_field("dr_corr",dr_corr/dt_sechiba)   ! adjustment flux added to drainage (included in drainage)
6490    CALL xios_orchidee_send_field("dr_corrnum",dr_corrnum/dt_sechiba) 
6491    CALL xios_orchidee_send_field("dr_force",dr_force/dt_sechiba) ! adjustement flux added to drainage to sustain a forced wtd
6492    CALL xios_orchidee_send_field("qinfilt",qinfilt/dt_sechiba)
6493    CALL xios_orchidee_send_field("ru_infilt",ru_infilt/dt_sechiba)
6494    CALL xios_orchidee_send_field("r_soil",r_soil) ! s/m
6495
6496    IF (check_cwrr2) THEN
6497       CALL xios_orchidee_send_field("check_infilt",check_infilt/dt_sechiba)
6498       CALL xios_orchidee_send_field("check_tr",check_tr/dt_sechiba)
6499       CALL xios_orchidee_send_field("check_over",check_over/dt_sechiba)
6500       CALL xios_orchidee_send_field("check_under",check_under/dt_sechiba)   
6501    END IF
6502
6503    !! 11. Exit if error was found previously in this subroutine
6504   
6505    IF ( error ) THEN
6506       WRITE(numout,*) 'One or more errors have been detected in hydrol_soil. Model stops.'
6507       CALL ipslerr_p(3, 'hydrol_soil', 'We will STOP now.',&
6508                  & 'One or several fatal errors were found previously.','')
6509    END IF
6510
6511    IF (printlev>=3) WRITE(numout,*) 'hydrol_soil done'
6512
6513  END SUBROUTINE hydrol_soil
6514
6515
6516!! ================================================================================================================================
6517!! SUBROUTINE   : hydrol_soil_infilt
6518!!
6519!>\BRIEF        Infiltration
6520!!
6521!! DESCRIPTION  :
6522!! 1. We calculate the total SM at the beginning of the routine
6523!! 2. Infiltration process
6524!! 2.1 Initialization of time counter and infiltration rate
6525!! 2.2 Infiltration layer by layer, accounting for an exponential law for subgrid variability
6526!! 2.3 Resulting infiltration and surface runoff
6527!! 3. For water conservation check, we calculate the total SM at the beginning of the routine,
6528!!    and export the difference with the flux
6529!! 5. Local verification
6530!!
6531!! RECENT CHANGE(S) : 2016 by A. Ducharne
6532!! Adding checks and interactions variables with hydrol_soil, but the processes are unchanged
6533!!
6534!! MAIN OUTPUT VARIABLE(S) :
6535!!
6536!! REFERENCE(S) :
6537!!
6538!! FLOWCHART    : None
6539!! \n
6540!_ ================================================================================================================================
6541!_ hydrol_soil_infilt
6542
6543  SUBROUTINE hydrol_soil_infilt(kjpindex, ins, njsc, flux_infilt, qinfilt_ns, ru_infilt, check)
6544
6545    !! 0. Variable and parameter declaration
6546
6547    !! 0.1 Input variables
6548
6549    ! GLOBAL (in or inout)
6550    INTEGER(i_std), INTENT(in)                        :: kjpindex        !! Domain size
6551    INTEGER(i_std), INTENT(in)                        :: ins
6552    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc            !! Index of the dominant soil textural class in the grid cell
6553                                                                         !!  (1-nscm, unitless)
6554    REAL(r_std), DIMENSION (kjpindex), INTENT (in)    :: flux_infilt     !! Water to infiltrate
6555                                                                         !!  @tex $(kg m^{-2})$ @endtex
6556
6557    !! 0.2 Output variables
6558    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check       !! delta SM - flux (mm/dt_sechiba)
6559    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: ru_infilt   !! Surface runoff from soil_infilt (mm/dt_sechiba)
6560    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: qinfilt_ns  !! Effective infiltration flux (mm/dt_sechiba)
6561
6562    !! 0.3 Modified variables
6563
6564    !! 0.4 Local variables
6565
6566    INTEGER(i_std)                                :: ji, jsl      !! Indices
6567    REAL(r_std), DIMENSION (kjpindex)             :: wat_inf_pot  !! infiltrable water in the layer
6568    REAL(r_std), DIMENSION (kjpindex)             :: wat_inf      !! infiltrated water in the layer
6569    REAL(r_std), DIMENSION (kjpindex)             :: dt_tmp       !! time remaining before the end of the time step
6570    REAL(r_std), DIMENSION (kjpindex)             :: dt_inf       !! the time it takes to complete the infiltration in the
6571                                                                  !! layer
6572    REAL(r_std)                                   :: k_m          !! the mean conductivity used for the saturated front
6573    REAL(r_std), DIMENSION (kjpindex)             :: infilt_tmp   !! infiltration rate for the considered layer
6574    REAL(r_std), DIMENSION (kjpindex)             :: infilt_tot   !! total infiltration
6575    REAL(r_std), DIMENSION (kjpindex)             :: flux_tmp     !! rate at which precip hits the ground
6576
6577    REAL(r_std), DIMENSION(kjpindex)              :: tmci         !! total SM at beginning of routine (kg/m2)
6578    REAL(r_std), DIMENSION(kjpindex)              :: tmcf         !! total SM at end of routine (kg/m2)
6579   
6580
6581!_ ================================================================================================================================
6582
6583    ! If data (or coupling with GCM) was available, a parameterization for subgrid rainfall could be performed
6584
6585    !! 1. We calculate the total SM at the beginning of the routine
6586    IF (check_cwrr2) THEN
6587       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
6588!       IF (minval(tmci) .LT. zero) THEN
6589!       WRITE (numout,*) 'BOOM L6528 tmci LT zero'
6590!       ENDIF
6591       DO jsl = 2,nslm-1
6592          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
6593               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
6594       ENDDO
6595       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
6596    ENDIF
6597
6598    !! 2. Infiltration process
6599
6600    !! 2.1 Initialization
6601
6602    DO ji = 1, kjpindex
6603       !! First we fill up the first layer (about 1mm) without any resistance and quasi-immediately
6604       wat_inf_pot(ji) = MAX((mcs(ji)-mc(ji,1,ins)) * dz(2) / deux, zero)
6605       wat_inf(ji) = MIN(wat_inf_pot(ji), flux_infilt(ji))
6606       mc(ji,1,ins) = mc(ji,1,ins) + wat_inf(ji) * deux / dz(2)
6607       !
6608    ENDDO
6609!       WRITE (numout,*) 'BOOM wat_inf_pot min max =',(minval(wat_inf_pot)) , (maxval(wat_inf_pot))
6610!        WRITE (numout,*) 'BOOM min mcs = ',(minval(mcs))
6611!         WRITE (numout,*) 'BOOM min/max flux_infilt =', (minval(flux_infilt)) , (maxval(flux_infilt))
6612!          WRITE (numout,*) 'BOOM min wat_inf =', (minval(wat_inf))
6613
6614    !! Initialize a countdown for infiltration during the time-step and the value of potential runoff
6615    dt_tmp(:) = dt_sechiba / one_day
6616    infilt_tot(:) = wat_inf(:)
6617    !! Compute the rate at which water will try to infiltrate each layer
6618    ! flux_temp is converted here to the same unit as k_m
6619    flux_tmp(:) = (flux_infilt(:)-wat_inf(:)) / dt_tmp(:)
6620
6621    !! 2.2 Infiltration layer by layer
6622    DO jsl = 2, nslm-1
6623       DO ji = 1, kjpindex
6624          !! Infiltrability of each layer if under a saturated one
6625          ! This is computed by an simple arithmetic average because
6626          ! the time step (30min) is not appropriate for a geometric average (advised by Haverkamp and Vauclin)
6627          k_m = (k(ji,jsl) + ks(njsc(ji))*kfact(jsl-1,njsc(ji))*kfact_root(ji,jsl,ins)) / deux 
6628
6629          IF (ok_freeze_cwrr) THEN
6630             IF (temp_hydro(ji, jsl) .LT. ZeroCelsius) THEN
6631                k_m = k(ji,jsl)
6632             ENDIF
6633          ENDIF
6634
6635          !! We compute the mean rate at which water actually infiltrate:
6636          ! Subgrid: Exponential distribution of k around k_m, but average p directly used
6637          ! See d'Orgeval 2006, p 78, but it's not fully clear to me (AD16***)
6638          infilt_tmp(ji) = k_m * (un - EXP(- flux_tmp(ji) / k_m)) 
6639
6640          !! From which we deduce the time it takes to fill up the layer or to end the time step...
6641          wat_inf_pot(ji) =  MAX((mcs(ji)-mc(ji,jsl,ins)) * (dz(jsl) + dz(jsl+1)) / deux, zero)
6642          IF ( infilt_tmp(ji) > min_sechiba) THEN
6643             dt_inf(ji) =  MIN(wat_inf_pot(ji)/infilt_tmp(ji), dt_tmp(ji))
6644             ! The water infiltration TIME has to limited by what is still available for infiltration.
6645             IF ( dt_inf(ji) * infilt_tmp(ji) > flux_infilt(ji)-infilt_tot(ji) ) THEN
6646                dt_inf(ji) = MAX(flux_infilt(ji)-infilt_tot(ji),zero)/infilt_tmp(ji)
6647             ENDIF
6648          ELSE
6649             dt_inf(ji) = dt_tmp(ji)
6650          ENDIF
6651
6652          !! The water enters in the layer
6653          wat_inf(ji) = dt_inf(ji) * infilt_tmp(ji)
6654          ! bviously the moisture content
6655          mc(ji,jsl,ins) = mc(ji,jsl,ins) + &
6656               & wat_inf(ji) * deux / (dz(jsl) + dz(jsl+1))
6657          ! the time remaining before the next time step
6658          dt_tmp(ji) = dt_tmp(ji) - dt_inf(ji)
6659          ! and finally the infilt_tot (which is just used to check if there is a problem, below)
6660          infilt_tot(ji) = infilt_tot(ji) + infilt_tmp(ji) * dt_inf(ji)
6661       ENDDO
6662    ENDDO
6663
6664    !! 2.3 Resulting infiltration and surface runoff
6665    ru_infilt(:,ins) = flux_infilt(:) - infilt_tot(:)
6666    qinfilt_ns(:,ins) = infilt_tot(:)
6667
6668!       WRITE (numout,*) 'ru_infilt maxval =', (maxval(ru_infilt))
6669!       WRITE (numout,*) 'ru_infilt minval =', (minval(ru_infilt))
6670!       WRITE (numout,*) 'qinfilt_ns maxval =', (maxval(qinfilt_ns))
6671!       WRITE (numout,*) 'qinfilt_ns minval =', (minval(qinfilt_ns))
6672!       WRITE (numout,*) 'flux_infilt maxval =', (maxval(flux_infilt))
6673!       WRITE (numout,*) 'flux_infilt minval =', (minval(flux_infilt))
6674       
6675
6676    !! 3. For water conservation check: we calculate the total SM at the beginning of the routine
6677    !!    and export the difference with the flux
6678    IF (check_cwrr2) THEN
6679       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
6680       DO jsl = 2,nslm-1
6681          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
6682               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
6683       ENDDO
6684       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
6685       ! Normally, tcmf=tmci+infilt_tot
6686       check(:,ins) = tmcf(:)-(tmci(:)+infilt_tot(:))
6687    ENDIF
6688   
6689    !! 5. Local verification
6690    DO ji = 1, kjpindex
6691       IF (infilt_tot(ji) .LT. -min_sechiba .OR. infilt_tot(ji) .GT. flux_infilt(ji) + min_sechiba) THEN         
6692          WRITE (numout,*) 'Error in the calculation of infilt tot', infilt_tot(ji)
6693          WRITE (numout,*) 'Error in the calculation of infilt tot', infilt_tot(ji)
6694         
6695          WRITE (numout,*) 'k, ji, jst, mc', k(ji,1:2), ji, ins, mc(ji,1,ins)
6696          CALL ipslerr_p(3, 'hydrol_soil_infilt', 'We will STOP now.','Error in calculation of infilt tot','')
6697       ENDIF
6698    ENDDO
6699!     IF (minval(mc) .LT. zero) THEN
6700!       WRITE (numout,*) 'BOOM mc LT zero 6694'
6701!      END IF
6702  END SUBROUTINE hydrol_soil_infilt
6703
6704
6705!! ================================================================================================================================
6706!! SUBROUTINE   : hydrol_soil_smooth_under_mcr
6707!!
6708!>\BRIEF        : Modifies the soil moisture profile to avoid under-residual values,
6709!!                then diagnoses the points where such "excess" values remain.
6710!!
6711!! DESCRIPTION  :
6712!! The "excesses" under-residual are corrected from top to bottom, by transfer of excesses
6713!! to the lower layers. The reverse transfer is performed to smooth any remaining "excess" in the bottom layer.
6714!! If some "excess" remain afterwards, the entire soil profile is at the threshold value (mcs or mcr),
6715!! and the remaining "excess" is necessarily concentrated in the top layer.
6716!! This allowing diagnosing the flag is_under_mcr.
6717!! Eventually, the remaining "excess" is split over the entire profile
6718!! 1. We calculate the total SM at the beginning of the routine
6719!! 2. Smoothes the profile to avoid negative values of punctual soil moisture
6720!! Note that we check that mc > min_sechiba in hydrol_soil
6721!! 3. For water conservation check, We calculate the total SM at the beginning of the routine,
6722!!    and export the difference with the flux
6723!!
6724!! RECENT CHANGE(S) : 2016 by A. Ducharne
6725!!
6726!! MAIN OUTPUT VARIABLE(S) :
6727!!
6728!! REFERENCE(S) :
6729!!
6730!! FLOWCHART    : None
6731!! \n
6732!_ ================================================================================================================================
6733!_ hydrol_soil_smooth_under_mcr
6734
6735  SUBROUTINE hydrol_soil_smooth_under_mcr(kjpindex, ins, njsc, is_under_mcr, check)
6736
6737    !- arguments
6738
6739    !! 0. Variable and parameter declaration
6740
6741    !! 0.1 Input variables
6742
6743    INTEGER(i_std), INTENT(in)                         :: kjpindex     !! Domain size
6744    INTEGER(i_std), INTENT(in)                         :: ins          !! Soiltile index (1-nstm, unitless)
6745    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: njsc         !! Index of the dominant soil textural class in grid cell
6746                                                                       !! (1-nscm, unitless)   
6747   
6748    !! 0.2 Output variables
6749
6750    LOGICAL, DIMENSION(kjpindex,nstm), INTENT(out)     :: is_under_mcr !! Flag diagnosing under residual soil moisture
6751    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out) :: check        !! delta SM - flux
6752
6753    !! 0.3 Modified variables
6754
6755    !! 0.4 Local variables
6756
6757    INTEGER(i_std)                       :: ji,jsl
6758    REAL(r_std)                          :: excess
6759    REAL(r_std), DIMENSION(kjpindex)     :: excessji
6760    REAL(r_std), DIMENSION(kjpindex)     :: tmci      !! total SM at beginning of routine
6761    REAL(r_std), DIMENSION(kjpindex)     :: tmcf      !! total SM at end of routine
6762
6763!_ ================================================================================================================================       
6764
6765    !! 1. We calculate the total SM at the beginning of the routine
6766    IF (check_cwrr2) THEN
6767       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
6768      IF (minval(tmci) .LT. zero) THEN
6769       WRITE (numout,*) 'before DO tmci LT zero value =', (minval(tmci))
6770      END IF
6771       DO jsl = 2,nslm-1
6772          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
6773               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
6774       ENDDO
6775       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
6776         IF (minval(tmci) .LT. zero) THEN
6777       WRITE (numout,*) 'after DO tmci LT zero value =', (minval(tmci))
6778      END IF
6779    ENDIF
6780
6781    !! 2. Smoothes the profile to avoid negative values of punctual soil moisture
6782 
6783
6784!     IF (minval(mc) .LT. zero) THEN
6785!       WRITE (numout,*) 'BOOM mc LT zero 6710'
6786!      END IF
6787    ! 2.1 smoothing from top to bottom
6788    DO jsl = 1,nslm-2
6789       DO ji=1, kjpindex
6790          excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
6791          mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
6792          mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) - excess * &
6793               &  (dz(jsl)+dz(jsl+1))/(dz(jsl+1)+dz(jsl+2))
6794       ENDDO
6795    ENDDO
6796!      IF (minval(mc) .LT. zero) THEN
6797!       WRITE (numout,*) 'BOOM mc LT zero 6711'
6798!      END IF
6799!       WRITE (numout,*) ' 6711 mcr minval =', (minval(mcr))
6800!       WRITE (numout,*) ' 6711 mc minval =', (minval(mc))
6801!       WRITE (numout,*) '6711 njsc maxval =', (maxval(njsc))
6802!       WRITE (numout,*) '6711 njsc minval =', (minval(njsc))       
6803    jsl = nslm-1
6804    DO ji=1, kjpindex
6805       excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
6806       mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
6807       mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) - excess * &
6808            &  (dz(jsl)+dz(jsl+1))/dz(jsl+1)
6809    ENDDO
6810!      IF (minval(mc) .LT. zero) THEN
6811!       WRITE (numout,*) 'BOOM mc LT zero 6720'
6812!      END IF
6813    jsl = nslm
6814    DO ji=1, kjpindex
6815       excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
6816       mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
6817       mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) - excess * &
6818            &  dz(jsl)/(dz(jsl-1)+dz(jsl))
6819    ENDDO
6820!      IF (minval(mc) .LT. zero) THEN
6821!       WRITE (numout,*) 'BOOM mc LT zero 6730'
6822!      END IF
6823    ! 2.2 smoothing from bottom to top
6824    DO jsl = nslm-1,2,-1
6825       DO ji=1, kjpindex
6826          excess = MAX(mcr(njsc(ji))-mc(ji,jsl,ins),zero)
6827          mc(ji,jsl,ins) = mc(ji,jsl,ins) + excess
6828          mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) - excess * &
6829               &  (dz(jsl)+dz(jsl+1))/(dz(jsl-1)+dz(jsl))
6830       ENDDO
6831    ENDDO
6832!      IF (minval(mc) .LT. zero) THEN
6833!       WRITE (numout,*) 'BOOM mc LT zero 6744'
6834!      END IF
6835    ! 2.3 diagnoses is_under_mcr(ji), and updates the entire profile
6836    ! excess > 0
6837    DO ji=1, kjpindex
6838       excessji(ji) = mask_soiltile(ji,ins) * MAX(mcr(njsc(ji))-mc(ji,1,ins),zero)
6839    ENDDO
6840    DO ji=1, kjpindex
6841       mc(ji,1,ins) = mc(ji,1,ins) + excessji(ji) ! then mc(1)=mcr
6842       is_under_mcr(ji,ins) = (excessji(ji) .GT. min_sechiba)
6843    ENDDO
6844!      IF (minval(mc) .LT. zero) THEN
6845!       WRITE (numout,*) 'BOOM mc LT zero 6755'
6846!      END IF
6847    ! 2.4 The amount of water corresponding to excess in the top soil layer is redistributed in all soil layers
6848      ! -excess(ji) * dz(2) / deux donne le deficit total, negatif, en mm
6849      ! diviser par la profondeur totale en mm donne des delta_mc identiques en chaque couche, en mm
6850      ! retransformes en delta_mm par couche selon les bonnes eqs (eqs_hydrol.pdf, Eqs 13-15), puis sommes
6851      ! retourne bien le deficit total en mm
6852    DO jsl = 1, nslm
6853       DO ji=1, kjpindex
6854          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excessji(ji) * dz(2) / (deux * zmaxh*mille)
6855       ENDDO
6856    ENDDO
6857!      IF (minval(mc) .LT. zero) THEN
6858!       WRITE (numout,*) 'BOOM mc LT zero 6768'
6859!      END IF
6860    ! This can lead to mc(jsl) < mcr depending on the value of excess,
6861    ! but this is no major pb for the diffusion
6862    ! Yet, we need to prevent evaporation if is_under_mcr
6863   
6864    !! Note that we check that mc > min_sechiba in hydrol_soil
6865
6866    ! We just make sure that mc remains at 0 where soiltile=0
6867    DO jsl = 1, nslm
6868       DO ji=1, kjpindex
6869          mc(ji,jsl,ins) = mask_soiltile(ji,ins) * mc(ji,jsl,ins)
6870       ENDDO
6871    ENDDO
6872!      IF (minval(mc) .LT. zero) THEN
6873!       WRITE (numout,*) 'BOOM mc LT zero 6783'
6874!      END IF
6875    !! 3. For water conservation check, We calculate the total SM at the beginning of the routine,
6876    !!    and export the difference with the flux
6877    IF (check_cwrr2) THEN
6878       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
6879       DO jsl = 2,nslm-1
6880          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
6881               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
6882       ENDDO
6883       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
6884       ! Normally, tcmf=tmci since we just redistribute the deficit
6885       check(:,ins) = tmcf(:)-tmci(:)
6886    ENDIF
6887       
6888  END SUBROUTINE hydrol_soil_smooth_under_mcr
6889
6890
6891!! ================================================================================================================================
6892!! SUBROUTINE   : hydrol_soil_smooth_over_mcs
6893!!
6894!>\BRIEF        : Modifies the soil moisture profile to avoid over-saturation values,
6895!!                by putting the excess in ru_ns
6896!!                Thus, no point remain where such "excess" values remain (is_over_mcs becomes useless)
6897!!
6898!! DESCRIPTION  :
6899!! The "excesses" over-saturation are corrected from top to bottom, by transfer of excesses
6900!! to the lower layers. The reverse transfer is performed to smooth any remaining "excess" in the bottom layer.
6901!! If some "excess" remain afterwards, the entire soil profile is at the threshold value (mcs or mcr),
6902!! and the remaining "excess" is necessarily concentrated in the top layer.
6903!! Eventually, the remaining "excess" creates rudr_corr, to be added to ru_ns or dr_ns
6904!! 1. We calculate the total SM at the beginning of the routine
6905!! 2. In case of over-saturation we put the water where it is possible by smoothing
6906!! 3. The excess is transformed into surface runoff, with conversion from m3/m3 to kg/m2
6907!! 4. For water conservation checks, we calculate the total SM at the beginning of the routine,
6908!!    and export the difference with the flux
6909!!
6910!! RECENT CHANGE(S) : 2016 by A. Ducharne
6911!!
6912!! MAIN OUTPUT VARIABLE(S) :
6913!!
6914!! REFERENCE(S) :
6915!!
6916!! FLOWCHART    : None
6917!! \n
6918!_ ================================================================================================================================
6919!_ hydrol_soil_smooth_over_mcs
6920
6921  SUBROUTINE hydrol_soil_smooth_over_mcs(kjpindex, ins, njsc, is_over_mcs, rudr_corr, check)
6922
6923    !- arguments
6924
6925    !! 0. Variable and parameter declaration
6926
6927    !! 0.1 Input variables
6928
6929    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size
6930    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless)
6931    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell
6932                                                                            !! (1-nscm, unitless)
6933   
6934    !! 0.2 Output variables
6935
6936    LOGICAL, DIMENSION(kjpindex), INTENT(out)            :: is_over_mcs     !! Flag diagnosing over saturated soil moisture 
6937    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out)   :: check           !! delta SM - flux
6938   
6939    !! 0.3 Modified variables   
6940    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(inout):: rudr_corr         !! Surface runoff produced to correct excess (mm/dtstep)
6941
6942    !! 0.4 Local variables
6943
6944    INTEGER(i_std)                        :: ji,jsl
6945    REAL(r_std)                           :: excess
6946    REAL(r_std), DIMENSION(kjpindex)      :: tmci    !! total SM at beginning of routine
6947    REAL(r_std), DIMENSION(kjpindex)      :: tmcf    !! total SM at end of routine
6948
6949    !_ ================================================================================================================================
6950
6951    !! 1. We calculate the total SM at the beginning of the routine
6952    IF (check_cwrr2) THEN
6953       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
6954       DO jsl = 2,nslm-1
6955          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
6956               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
6957       ENDDO
6958       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
6959    ENDIF
6960
6961    !! 2. In case of over-saturation we put the water where it is possible by smoothing
6962
6963    ! 2.1 smoothing from top to bottom
6964    DO jsl = 1, nslm-2
6965       DO ji=1, kjpindex
6966          excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
6967          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
6968          mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) + excess * &
6969               &  (dz(jsl)+dz(jsl+1))/(dz(jsl+1)+dz(jsl+2))
6970       ENDDO
6971    ENDDO
6972!      IF (minval(mc) .LT. zero) THEN
6973!       WRITE (numout,*) 'BOOM mc LT zero 6882'
6974!      END IF
6975    jsl = nslm-1
6976    DO ji=1, kjpindex
6977       excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
6978       mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
6979       mc(ji,jsl+1,ins) = mc(ji,jsl+1,ins) + excess * &
6980            &  (dz(jsl)+dz(jsl+1))/dz(jsl+1)
6981    ENDDO
6982!      IF (minval(mc) .LT. zero) THEN
6983!       WRITE (numout,*) 'BOOM mc LT zero 6891'
6984!      END IF
6985    jsl = nslm
6986    DO ji=1, kjpindex
6987       excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
6988       mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
6989       mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) + excess * &
6990            &  dz(jsl)/(dz(jsl-1)+dz(jsl))
6991    ENDDO
6992!      IF (minval(mc) .LT. zero) THEN
6993!       WRITE (numout,*) 'BOOM mc LT zero 6902'
6994!      END IF
6995    ! 2.2 smoothing from bottom to top, leading  to keep most of the excess in the soil column
6996    DO jsl = nslm-1,2,-1
6997       DO ji=1, kjpindex
6998          excess = MAX(mc(ji,jsl,ins)-mcs(ji),zero)
6999          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess
7000          mc(ji,jsl-1,ins) = mc(ji,jsl-1,ins) + excess * &
7001               &  (dz(jsl)+dz(jsl+1))/(dz(jsl-1)+dz(jsl))
7002       ENDDO
7003    ENDDO
7004!      IF (minval(mc) .LT. zero) THEN
7005!       WRITE (numout,*) 'BOOM mc LT zero 6915'
7006!      END IF
7007    !! 3. The excess is transformed into surface runoff, with conversion from m3/m3 to kg/m2
7008
7009    DO ji=1, kjpindex
7010       excess = mask_soiltile(ji,ins) * MAX(mc(ji,1,ins)-mcs(ji),zero)
7011       mc(ji,1,ins) = mc(ji,1,ins) - excess ! then mc(1)=mcs
7012       rudr_corr(ji,ins) = rudr_corr(ji,ins) + excess * dz(2) / deux 
7013       is_over_mcs(ji) = .FALSE.
7014    ENDDO
7015!      IF (minval(mc) .LT. zero) THEN
7016!       WRITE (numout,*) 'BOOM mc LT zero 6926'
7017!      END IF
7018    !! 4. For water conservation checks, we calculate the total SM at the beginning of the routine,
7019    !!    and export the difference with the flux
7020
7021    IF (check_cwrr2) THEN
7022       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
7023       DO jsl = 2,nslm-1
7024          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
7025               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
7026       ENDDO
7027       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
7028       ! Normally, tcmf=tmci-rudr_corr
7029       check(:,ins) = tmcf(:)-(tmci(:)-rudr_corr(:,ins))
7030    ENDIF
7031   
7032  END SUBROUTINE hydrol_soil_smooth_over_mcs
7033
7034 !! ================================================================================================================================
7035!! SUBROUTINE   : hydrol_soil_smooth_over_mcs2
7036!!
7037!>\BRIEF        : Modifies the soil moisture profile to avoid over-saturation values,
7038!!                by putting the excess in ru_ns
7039!!                Thus, no point remain where such "excess" values remain (is_over_mcs becomes useless)
7040!!
7041!! DESCRIPTION  :
7042!! The "excesses" over-saturation are corrected, by directly discarding the excess as rudr_corr,
7043!! to be added to ru_ns or dr_nsrunoff (via rudr_corr).
7044!! Therefore, there is no more smoothing, and this helps preventing the saturation of too many layers,
7045!! which leads to numerical errors with tridiag.
7046!! 1. We calculate the total SM at the beginning of the routine
7047!! 2. In case of over-saturation, we directly eliminate the excess via rudr_corr
7048!!    The calculation of the adjustement flux needs to account for nodes n-1 and n+1.
7049!! 3. For water conservation checks, we calculate the total SM at the beginning of the routine,
7050!!    and export the difference with the flux   
7051!!
7052!! RECENT CHANGE(S) : 2016 by A. Ducharne
7053!!
7054!! MAIN OUTPUT VARIABLE(S) :
7055!!
7056!! REFERENCE(S) :
7057!!
7058!! FLOWCHART    : None
7059!! \n
7060!_ ================================================================================================================================
7061!_ hydrol_soil_smooth_over_mcs2
7062
7063  SUBROUTINE hydrol_soil_smooth_over_mcs2(kjpindex, ins, njsc, is_over_mcs, rudr_corr, check)
7064
7065    !- arguments
7066
7067    !! 0. Variable and parameter declaration
7068
7069    !! 0.1 Input variables
7070
7071    INTEGER(i_std), INTENT(in)                           :: kjpindex        !! Domain size
7072    INTEGER(i_std), INTENT(in)                           :: ins             !! Soiltile index (1-nstm, unitless)
7073    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)     :: njsc            !! Index of the dominant soil textural class in grid cell
7074                                                                            !! (1-nscm, unitless)
7075   
7076    !! 0.2 Output variables
7077
7078    LOGICAL, DIMENSION(kjpindex), INTENT(out)            :: is_over_mcs     !! Flag diagnosing over saturated soil moisture 
7079    REAL(r_std), DIMENSION(kjpindex,nstm), INTENT(out)   :: check           !! delta SM - flux
7080   
7081    !! 0.3 Modified variables   
7082    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT(inout):: rudr_corr         !! Surface runoff produced to correct excess (mm/dtstep)
7083
7084    !! 0.4 Local variables
7085
7086    INTEGER(i_std)                        :: ji,jsl
7087    REAL(r_std), DIMENSION(kjpindex,nslm) :: excess
7088    REAL(r_std), DIMENSION(kjpindex)      :: tmci    !! total SM at beginning of routine
7089    REAL(r_std), DIMENSION(kjpindex)      :: tmcf    !! total SM at end of routine
7090
7091!_ ================================================================================================================================       
7092    !-
7093
7094    !! 1. We calculate the total SM at the beginning of the routine
7095    IF (check_cwrr2) THEN
7096       tmci(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
7097       DO jsl = 2,nslm-1
7098          tmci(:) = tmci(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
7099               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
7100       ENDDO
7101       tmci(:) = tmci(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
7102    ENDIF 
7103
7104    !! 2. In case of over-saturation, we don't do any smoothing,
7105    !! but directly eliminate the excess as runoff (via rudr_corr)
7106    !    we correct the calculation of the adjustement flux, which needs to account for nodes n-1 and n+1 
7107    !    for the calculation to remain simple and accurate, we directly drain all the oversaturated mc,
7108    !    without transfering to lower layers       
7109
7110    !! 2.1 thresholding from top to bottom, with excess defined along jsl
7111    DO jsl = 1, nslm
7112       DO ji=1, kjpindex
7113          excess(ji,jsl) = MAX(mc(ji,jsl,ins)-mcs(ji),zero) ! >=0
7114          mc(ji,jsl,ins) = mc(ji,jsl,ins) - excess(ji,jsl) ! here mc either does not change or decreases
7115       ENDDO
7116    ENDDO
7117!      IF (minval(mc) .LT. zero) THEN
7118!       WRITE (numout,*) 'BOOM mc LT zero 7024'
7119!      END IF
7120    !! 2.2 To ensure conservation, this needs to be balanced by additional drainage (in kg/m2/dt)                       
7121    DO ji = 1, kjpindex
7122       rudr_corr(ji,ins) = dz(2) * ( trois*excess(ji,1) + excess(ji,2) )/huit ! top layer = initialisation 
7123    ENDDO
7124    DO jsl = 2,nslm-1 ! intermediate layers     
7125       DO ji = 1, kjpindex
7126          rudr_corr(ji,ins) = rudr_corr(ji,ins) + dz(jsl) &
7127               & * (trois*excess(ji,jsl)+excess(ji,jsl-1))/huit &
7128               & + dz(jsl+1) * (trois*excess(ji,jsl)+excess(ji,jsl+1))/huit
7129       ENDDO
7130    ENDDO
7131    DO ji = 1, kjpindex
7132       rudr_corr(ji,ins) = rudr_corr(ji,ins) + dz(nslm) &    ! bottom layer
7133            & * (trois * excess(ji,nslm) + excess(ji,nslm-1))/huit
7134       is_over_mcs(ji) = .FALSE. 
7135    END DO
7136
7137    !! 3. For water conservation checks, we calculate the total SM at the beginning of the routine,
7138    !!    and export the difference with the flux
7139
7140    IF (check_cwrr2) THEN
7141       tmcf(:) = dz(2) * ( trois*mc(:,1,ins) + mc(:,2,ins) )/huit
7142       DO jsl = 2,nslm-1
7143          tmcf(:) = tmcf(:) + dz(jsl) * (trois*mc(:,jsl,ins)+mc(:,jsl-1,ins))/huit &
7144               + dz(jsl+1) * (trois*mc(:,jsl,ins)+mc(:,jsl+1,ins))/huit
7145       ENDDO
7146       tmcf(:) = tmcf(:) + dz(nslm) * (trois*mc(:,nslm,ins) + mc(:,nslm-1,ins))/huit
7147       ! Normally, tcmf=tmci-rudr_corr
7148       check(:,ins) = tmcf(:)-(tmci(:)-rudr_corr(:,ins))
7149    ENDIF
7150   
7151  END SUBROUTINE hydrol_soil_smooth_over_mcs2
7152
7153
7154!! ================================================================================================================================
7155!! SUBROUTINE   : hydrol_soil_flux
7156!!
7157!>\BRIEF        : This subroutine diagnoses the vertical liquid water fluxes between the
7158!!                different soil layers, based on each layer water budget. It also checks the
7159!!                corresponding water conservation (during redistribution).
7160!!
7161!! DESCRIPTION  :
7162!! 1. Initialize qflux from the bottom, with dr_ns
7163!! 2. Between layer nslm and nslm-1, by means of water budget knowing mc changes and flux at the lowest interface
7164!! 3. We go up, and deduct qflux(1:nslm-2), still by means of water budget
7165!! 4. Water balance verification: pursuing upward water budget, the flux at the surface should equal -flux_top 
7166!!
7167!! RECENT CHANGE(S) : 2016 by A. Ducharne to fit hydrol_soil
7168!!
7169!! MAIN OUTPUT VARIABLE(S) :
7170!!
7171!! REFERENCE(S) :
7172!!
7173!! FLOWCHART    : None
7174!! \n
7175!_ ================================================================================================================================
7176!_ hydrol_soil_flux
7177
7178  SUBROUTINE hydrol_soil_flux(kjpindex,ins,mclint,flux_top)
7179    !
7180    !! 0. Variable and parameter declaration
7181
7182    !! 0.1 Input variables
7183
7184    INTEGER(i_std), INTENT(in)                         :: kjpindex        !! Domain size
7185    INTEGER(i_std), INTENT(in)                         :: ins             !! index of soil type
7186    REAL(r_std), DIMENSION (kjpindex,nslm), INTENT(in) :: mclint          !! mc values at the beginning of the time step
7187    REAL(r_std), DIMENSION (kjpindex), INTENT(in)      :: flux_top        !! Exfiltration (bare soil evaporation minus infiltration)
7188   
7189    !! 0.2 Output variables
7190
7191    !! 0.3 Modified variables
7192
7193    !! 0.4 Local variables
7194
7195    INTEGER(i_std)                                     :: jsl,ji
7196    REAL(r_std), DIMENSION(kjpindex)                   :: temp
7197
7198    !_ ================================================================================================================================
7199
7200    !- Compute the diffusion flux at every level from bottom to top (using mcl,mclint, and sink values)
7201    DO ji = 1, kjpindex
7202
7203       !! 1. Initialize qflux from the bottom, with dr_ns
7204       jsl = nslm
7205       qflux(ji,jsl,ins) = dr_ns(ji,ins)
7206       !! 2. Between layer nslm and nslm-1, by means of water budget knowing mc changes and flux at the lowest interface
7207       !     qflux is downward
7208       jsl = nslm-1
7209       qflux(ji,jsl,ins) = qflux(ji,jsl+1,ins) & 
7210            &  + (mcl(ji,jsl,ins)-mclint(ji,jsl) &
7211            &  + trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1)) &
7212            &  * (dz(jsl+1)/huit) &
7213            &  + rootsink(ji,jsl+1,ins) 
7214    ENDDO
7215
7216    !! 3. We go up, and deduct qflux(1:nslm-2), still by means of water budget
7217    ! Here, qflux(ji,1,ins) is the downward flux between the top soil layer and the 2nd one
7218    DO jsl = nslm-2,1,-1
7219       DO ji = 1, kjpindex
7220          qflux(ji,jsl,ins) = qflux(ji,jsl+1,ins) & 
7221               &  + (mcl(ji,jsl,ins)-mclint(ji,jsl) &
7222               &  + trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1)) &
7223               &  * (dz(jsl+1)/huit) &
7224               &  + rootsink(ji,jsl+1,ins) &
7225               &  + (dz(jsl+2)/huit) &
7226               &  * (trois*mcl(ji,jsl+1,ins) - trois*mclint(ji,jsl+1) &
7227               &  + mcl(ji,jsl+2,ins)-mclint(ji,jsl+2)) 
7228       END DO
7229    ENDDO
7230   
7231    !! 4. Water balance verification: pursuing upward water budget, the flux at the surface (temp) should equal -flux_top
7232    DO ji = 1, kjpindex
7233       temp(ji) =  qflux(ji,1,ins) + (dz(2)/huit) &
7234            &  * (trois* (mcl(ji,1,ins)-mclint(ji,1)) + (mcl(ji,2,ins)-mclint(ji,2))) &
7235            &  + rootsink(ji,1,ins)
7236    ENDDO
7237
7238    ! flux_top is positive when upward, while temp is positive when downward
7239    DO ji = 1, kjpindex
7240       IF (ABS(flux_top(ji)+temp(ji)).GT. deux*min_sechiba) THEN
7241          WRITE(numout,*) 'Problem in the water balance, qflux computation', flux_top(ji),temp(ji)
7242          WRITE(numout,*) 'ji', ji, 'jsl',jsl,'ins',ins
7243          WRITE(numout,*) 'mclint', mclint(ji,:)
7244          WRITE(numout,*) 'mcl', mcl(ji,:,ins)
7245          WRITE (numout,*) 'rootsink', rootsink(ji,1,ins)
7246       !   CALL ipslerr_p(3, 'hydrol_soil_flux', 'We will STOP now.',&
7247       !        & 'Problem in the water balance, qflux computation','')
7248       ENDIF
7249    ENDDO
7250
7251  END SUBROUTINE hydrol_soil_flux
7252
7253
7254!! ================================================================================================================================
7255!! SUBROUTINE   : hydrol_soil_tridiag
7256!!
7257!>\BRIEF        This subroutine solves a set of linear equations which has a tridiagonal coefficient matrix.
7258!!
7259!! DESCRIPTION  : It is only applied in the grid-cells where resolv(ji)=TRUE
7260!!
7261!! RECENT CHANGE(S) : None
7262!!
7263!! MAIN OUTPUT VARIABLE(S) : mcl (global module variable)
7264!!
7265!! REFERENCE(S) :
7266!!
7267!! FLOWCHART    : None
7268!! \n
7269!_ ================================================================================================================================
7270!_ hydrol_soil_tridiag
7271
7272  SUBROUTINE hydrol_soil_tridiag(kjpindex,ins)
7273
7274    !- arguments
7275
7276    !! 0. Variable and parameter declaration
7277
7278    !! 0.1 Input variables
7279
7280    INTEGER(i_std), INTENT(in)                         :: kjpindex        !! Domain size
7281    INTEGER(i_std), INTENT(in)                         :: ins             !! number of soil type
7282
7283    !! 0.2 Output variables
7284
7285    !! 0.3 Modified variables
7286
7287    !! 0.4 Local variables
7288
7289    INTEGER(i_std)                                     :: ji,jsl
7290    REAL(r_std), DIMENSION(kjpindex)                   :: bet
7291    REAL(r_std), DIMENSION(kjpindex,nslm)              :: gam
7292
7293!_ ================================================================================================================================
7294    DO ji = 1, kjpindex
7295
7296       IF (resolv(ji)) THEN
7297          bet(ji) = tmat(ji,1,2)
7298          mcl(ji,1,ins) = rhs(ji,1)/bet(ji)
7299       ENDIF
7300    ENDDO
7301
7302    DO jsl = 2,nslm
7303       DO ji = 1, kjpindex
7304         
7305          IF (resolv(ji)) THEN
7306
7307             gam(ji,jsl) = tmat(ji,jsl-1,3)/bet(ji)
7308             bet(ji) = tmat(ji,jsl,2) - tmat(ji,jsl,1)*gam(ji,jsl)
7309             mcl(ji,jsl,ins) = (rhs(ji,jsl)-tmat(ji,jsl,1)*mcl(ji,jsl-1,ins))/bet(ji)
7310          ENDIF
7311
7312       ENDDO
7313    ENDDO
7314
7315    DO ji = 1, kjpindex
7316       IF (resolv(ji)) THEN
7317          DO jsl = nslm-1,1,-1
7318             mcl(ji,jsl,ins) = mcl(ji,jsl,ins) - gam(ji,jsl+1)*mcl(ji,jsl+1,ins)
7319          ENDDO
7320       ENDIF
7321    ENDDO
7322
7323  END SUBROUTINE hydrol_soil_tridiag
7324
7325
7326!! ================================================================================================================================
7327!! SUBROUTINE   : hydrol_soil_coef
7328!!
7329!>\BRIEF        Computes coef for the linearised hydraulic conductivity
7330!! k_lin=a_lin mc_lin+b_lin and the linearised diffusivity d_lin.
7331!!
7332!! DESCRIPTION  :
7333!! First, we identify the interval i in which the current value of mc is located.
7334!! Then, we give the values of the linearized parameters to compute
7335!! conductivity and diffusivity as K=a*mc+b and d.
7336!!
7337!! RECENT CHANGE(S) : Addition of the dependence to profil_froz_hydro_ns
7338!!
7339!! MAIN OUTPUT VARIABLE(S) :
7340!!
7341!! REFERENCE(S) :
7342!!
7343!! FLOWCHART    : None
7344!! \n
7345!_ ================================================================================================================================
7346!_ hydrol_soil_coef
7347 
7348  SUBROUTINE hydrol_soil_coef(kjpindex,ins,njsc)
7349
7350    IMPLICIT NONE
7351    !
7352    !! 0. Variable and parameter declaration
7353
7354    !! 0.1 Input variables
7355
7356    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size
7357    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type
7358    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
7359
7360    !! 0.2 Output variables
7361
7362    !! 0.3 Modified variables
7363
7364    !! 0.4 Local variables
7365
7366    INTEGER(i_std)                                    :: jsl,ji,i
7367    REAL(r_std)                                       :: mc_ratio
7368    REAL(r_std)                                       :: mc_used    !! Used liquid water content
7369    REAL(r_std)                                       :: x,m
7370   
7371!_ ================================================================================================================================
7372
7373    IF (ok_freeze_cwrr) THEN
7374   
7375       ! Calculation of liquid and frozen saturation degrees with respect to residual
7376       ! x=liquid saturation degree/residual=(mcl-mcr)/(mcs-mcr)
7377       ! 1-x=frozen saturation degree/residual=(mcf-mcr)/(mcs-mcr) (=profil_froz_hydro)
7378       
7379       DO jsl=1,nslm
7380          DO ji=1,kjpindex
7381             
7382             x = 1._r_std - profil_froz_hydro_ns(ji, jsl,ins)
7383             
7384             ! mc_used is used in the calculation of hydrological properties
7385             ! It corresponds to a liquid mc, but the expression is different from mcl in hydrol_soil,
7386             ! to ensure that we get the a, b, d of the first bin when mcl<mcr
7387             mc_used = mcr(njsc(ji))+x*MAX((mc(ji,jsl, ins)-mcr(njsc(ji))),zero) 
7388             !
7389             ! calcul de k based on mc_liq
7390             !
7391             i= MAX(imin, MIN(imax-1, INT(imin +(imax-imin)*(mc_used-mcr(njsc(ji)))/(mcs(ji)-mcr(njsc(ji))))))
7392             a(ji,jsl) = a_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
7393             b(ji,jsl) = b_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
7394             d(ji,jsl) = d_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm^2/d
7395             k(ji,jsl) = MAX(k_lin(imin+1,jsl,ji), &
7396                  a_lin(i,jsl,ji) * mc_used + b_lin(i,jsl,ji)) ! in mm/d
7397          ENDDO ! loop on grid
7398       ENDDO
7399             
7400    ELSE
7401       ! .NOT. ok_freeze_cwrr
7402       DO jsl=1,nslm
7403          DO ji=1,kjpindex 
7404             
7405             ! it is impossible to consider a mc<mcr for the binning
7406             mc_ratio = MAX(mc(ji,jsl,ins)-mcr(njsc(ji)), zero)/(mcs(ji)-mcr(njsc(ji)))
7407             
7408             i= MAX(MIN(INT((imax-imin)*mc_ratio)+imin , imax-1), imin)
7409             a(ji,jsl) = a_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
7410             b(ji,jsl) = b_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm/d
7411             d(ji,jsl) = d_lin(i,jsl,ji) * kfact_root(ji,jsl,ins) ! in mm^2/d
7412             k(ji,jsl) = MAX(k_lin(imin+1,jsl,ji), &
7413                  a_lin(i,jsl,ji) * mc(ji,jsl,ins) + b_lin(i,jsl,ji))  ! in mm/d
7414          END DO
7415       END DO
7416    ENDIF
7417   
7418  END SUBROUTINE hydrol_soil_coef
7419
7420!! ================================================================================================================================
7421!! SUBROUTINE   : hydrol_soil_froz
7422!!
7423!>\BRIEF        Computes profil_froz_hydro_ns, the fraction of frozen water in the soil layers.
7424!!
7425!! DESCRIPTION  :
7426!!
7427!! RECENT CHANGE(S) : Created by A. Ducharne in 2016.
7428!!
7429!! MAIN OUTPUT VARIABLE(S) : profil_froz_hydro_ns
7430!!
7431!! REFERENCE(S) :
7432!!
7433!! FLOWCHART    : None
7434!! \n
7435!_ ================================================================================================================================
7436!_ hydrol_soil_froz
7437 
7438  SUBROUTINE hydrol_soil_froz(kjpindex,ins,njsc)
7439
7440    IMPLICIT NONE
7441    !
7442    !! 0. Variable and parameter declaration
7443
7444    !! 0.1 Input variables
7445
7446    INTEGER(i_std), INTENT(in)                        :: kjpindex         !! Domain size
7447    INTEGER(i_std), INTENT(in)                        :: ins              !! Index of soil type
7448    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)  :: njsc             !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
7449
7450    !! 0.2 Output variables
7451
7452    !! 0.3 Modified variables
7453
7454    !! 0.4 Local variables
7455
7456    INTEGER(i_std)                                    :: jsl,ji,i
7457    REAL(r_std)                                       :: x,m
7458    REAL(r_std)                                       :: denom
7459    REAL(r_std),DIMENSION (kjpindex)                  :: froz_frac_moy
7460    REAL(r_std),DIMENSION (kjpindex)                  :: smtot_moy
7461    REAL(r_std),DIMENSION (kjpindex,nslm)             :: mc_ns
7462   
7463!_ ================================================================================================================================
7464
7465!    ONLY FOR THE (ok_freeze_cwrr) CASE
7466   
7467       ! Calculation of liquid and frozen saturation degrees above residual moisture
7468       !   x=liquid saturation degree/residual=(mcl-mcr)/(mcs-mcr)
7469       !   1-x=frozen saturation degree/residual=(mcf-mcr)/(mcs-mcr) (=profil_froz_hydro)
7470       ! It's important for the good work of the water diffusion scheme (tridiag) that the total
7471       ! liquid water also includes mcr, so mcl > 0 even when x=0
7472       
7473       DO jsl=1,nslm
7474          DO ji=1,kjpindex
7475             ! Van Genuchten parameter for thermodynamical calculation
7476             m = 1. -1./nvan(njsc(ji))
7477           
7478             IF ((.NOT. ok_thermodynamical_freezing).OR.(mc(ji,jsl, ins).LT.(mcr(njsc(ji))+min_sechiba))) THEN
7479                ! Linear soil freezing or soil moisture below residual
7480                IF (temp_hydro(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN
7481                   x=1._r_std
7482                ELSE IF ( (temp_hydro(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &
7483                     (temp_hydro(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN
7484                   x=(temp_hydro(ji, jsl)-(ZeroCelsius-fr_dT/2.))/fr_dT
7485                ELSE
7486                   x=0._r_std
7487                ENDIF
7488             ELSE IF (ok_thermodynamical_freezing) THEN
7489                ! Thermodynamical soil freezing
7490                IF (temp_hydro(ji, jsl).GE.(ZeroCelsius+fr_dT/2.)) THEN
7491                   x=1._r_std
7492                ELSE IF ( (temp_hydro(ji,jsl) .GE. (ZeroCelsius-fr_dT/2.)) .AND. &
7493                     (temp_hydro(ji,jsl) .LT. (ZeroCelsius+fr_dT/2.)) ) THEN
7494                   ! Factor 2.2 from the PhD of Isabelle Gouttevin
7495                   x=MIN(((mcs(ji)-mcr(njsc(ji))) &
7496                        *((2.2*1000.*avan(njsc(ji))*(ZeroCelsius+fr_dT/2.-temp_hydro(ji, jsl)) &
7497                        *lhf/ZeroCelsius/10.)**nvan(njsc(ji))+1.)**(-m)) / &
7498                        (mc(ji,jsl, ins)-mcr(njsc(ji))),1._r_std)               
7499                ELSE
7500                   x=0._r_std 
7501                ENDIF
7502             ENDIF
7503             
7504             profil_froz_hydro_ns(ji,jsl,ins) = 1._r_std-x
7505             
7506             mc_ns(ji,jsl)=mc(ji,jsl,ins)/mcs(ji)
7507
7508          ENDDO ! loop on grid
7509       ENDDO
7510   
7511       ! Applay correction on the frozen fraction
7512       froz_frac_moy(:)=zero
7513       denom=zero
7514       DO jsl=1,nslm
7515          froz_frac_moy(:)=froz_frac_moy(:)+dh(jsl)*profil_froz_hydro_ns(:,jsl,ins)
7516          denom=denom+dh(jsl)
7517       ENDDO
7518       froz_frac_moy(:)=froz_frac_moy(:)/denom
7519
7520       smtot_moy(:)=zero
7521       denom=zero
7522       DO jsl=1,nslm-1
7523          smtot_moy(:)=smtot_moy(:)+dh(jsl)*mc_ns(:,jsl)
7524          denom=denom+dh(jsl)
7525       ENDDO
7526       smtot_moy(:)=smtot_moy(:)/denom
7527
7528       DO jsl=1,nslm
7529          profil_froz_hydro_ns(:,jsl,ins)=MIN(profil_froz_hydro_ns(:,jsl,ins)* &
7530                                              (froz_frac_moy(:)**froz_frac_corr)*(smtot_moy(:)**smtot_corr), max_froz_hydro)
7531       ENDDO
7532
7533     END SUBROUTINE hydrol_soil_froz
7534     
7535
7536!! ================================================================================================================================
7537!! SUBROUTINE   : hydrol_soil_setup
7538!!
7539!>\BRIEF        This subroutine computes the matrix coef. 
7540!!
7541!! DESCRIPTION  : None
7542!!
7543!! RECENT CHANGE(S) : None
7544!!
7545!! MAIN OUTPUT VARIABLE(S) : matrix coef
7546!!
7547!! REFERENCE(S) :
7548!!
7549!! FLOWCHART    : None
7550!! \n
7551!_ ================================================================================================================================
7552
7553  SUBROUTINE hydrol_soil_setup(kjpindex,ins)
7554
7555
7556    IMPLICIT NONE
7557    !
7558    !! 0. Variable and parameter declaration
7559
7560    !! 0.1 Input variables
7561    INTEGER(i_std), INTENT(in)                        :: kjpindex          !! Domain size
7562    INTEGER(i_std), INTENT(in)                        :: ins               !! index of soil type
7563
7564    !! 0.2 Output variables
7565
7566    !! 0.3 Modified variables
7567
7568    !! 0.4 Local variables
7569
7570    INTEGER(i_std) :: jsl,ji
7571    REAL(r_std)                        :: temp3, temp4
7572
7573!_ ================================================================================================================================
7574    !-we compute tridiag matrix coefficients (LEFT and RIGHT)
7575    ! of the system to solve [LEFT]*mc_{t+1}=[RIGHT]*mc{t}+[add terms]:
7576    ! e(nslm),f(nslm),g1(nslm) for the [left] vector
7577    ! and ep(nslm),fp(nslm),gp(nslm) for the [right] vector
7578
7579    ! w_time=1 (in constantes_soil) indicates implicit computation for diffusion
7580    temp3 = w_time*(dt_sechiba/one_day)/deux
7581    temp4 = (un-w_time)*(dt_sechiba/one_day)/deux
7582
7583    ! Passage to arithmetic means for layer averages also in this subroutine : Aurelien 11/05/10
7584
7585    !- coefficient for first layer
7586    DO ji = 1, kjpindex
7587       e(ji,1) = zero
7588       f(ji,1) = trois * dz(2)/huit  + temp3 &
7589            & * ((d(ji,1)+d(ji,2))/(dz(2))+a(ji,1))
7590       g1(ji,1) = dz(2)/(huit)       - temp3 &
7591            & * ((d(ji,1)+d(ji,2))/(dz(2))-a(ji,2))
7592       ep(ji,1) = zero
7593       fp(ji,1) = trois * dz(2)/huit - temp4 &
7594            & * ((d(ji,1)+d(ji,2))/(dz(2))+a(ji,1))
7595       gp(ji,1) = dz(2)/(huit)       + temp4 &
7596            & * ((d(ji,1)+d(ji,2))/(dz(2))-a(ji,2))
7597    ENDDO
7598
7599    !- coefficient for medium layers
7600
7601    DO jsl = 2, nslm-1
7602       DO ji = 1, kjpindex
7603          e(ji,jsl) = dz(jsl)/(huit)                        - temp3 &
7604               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl))+a(ji,jsl-1))
7605
7606          f(ji,jsl) = trois * (dz(jsl)+dz(jsl+1))/huit  + temp3 &
7607               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl)) + &
7608               & (d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1)) )
7609
7610          g1(ji,jsl) = dz(jsl+1)/(huit)                     - temp3 &
7611               & * ((d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1))-a(ji,jsl+1))
7612
7613          ep(ji,jsl) = dz(jsl)/(huit)                       + temp4 &
7614               & * ((d(ji,jsl)+d(ji,jsl-1))/(dz(jsl))+a(ji,jsl-1))
7615
7616          fp(ji,jsl) = trois * (dz(jsl)+dz(jsl+1))/huit - temp4 &
7617               & * ( (d(ji,jsl)+d(ji,jsl-1))/(dz(jsl)) + &
7618               & (d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1)) )
7619
7620          gp(ji,jsl) = dz(jsl+1)/(huit)                     + temp4 &
7621               & *((d(ji,jsl)+d(ji,jsl+1))/(dz(jsl+1))-a(ji,jsl+1))
7622       ENDDO
7623    ENDDO
7624
7625    !- coefficient for last layer
7626    DO ji = 1, kjpindex
7627       e(ji,nslm) = dz(nslm)/(huit)        - temp3 &
7628            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm))+a(ji,nslm-1))
7629       f(ji,nslm) = trois * dz(nslm)/huit  + temp3 &
7630            & * ((d(ji,nslm)+d(ji,nslm-1)) / (dz(nslm)) &
7631            & -a(ji,nslm)*(un-deux*free_drain_coef(ji,ins)))
7632       g1(ji,nslm) = zero
7633       ep(ji,nslm) = dz(nslm)/(huit)       + temp4 &
7634            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm))+a(ji,nslm-1))
7635       fp(ji,nslm) = trois * dz(nslm)/huit - temp4 &
7636            & * ((d(ji,nslm)+d(ji,nslm-1)) /(dz(nslm)) &
7637            & -a(ji,nslm)*(un-deux*free_drain_coef(ji,ins)))
7638       gp(ji,nslm) = zero
7639    ENDDO
7640
7641  END SUBROUTINE hydrol_soil_setup
7642
7643 
7644!! ================================================================================================================================
7645!! SUBROUTINE   : hydrol_split_soil
7646!!
7647!>\BRIEF        Splits 2d variables into 3d variables, per soiltile (_ns suffix), at the beginning of hydrol
7648!!              At this stage, the forcing fluxes to hydrol are transformed from grid-cell averages
7649!!              to mean fluxes over vegtot=sum(soiltile) 
7650!!
7651!! DESCRIPTION  :
7652!! 1. Split 2d variables into 3d variables, per soiltile
7653!! 1.1 Throughfall
7654!! 1.2 Bare soil evaporation
7655!! 1.2.1 vevapnu_old
7656!! 1.2.2 ae_ns new
7657!! 1.3 transpiration
7658!! 1.4 root sink
7659!! 2. Verification: Check if the deconvolution is correct and conserves the fluxes
7660!! 2.1 precisol
7661!! 2.2 ae_ns and evapnu
7662!! 2.3 transpiration
7663!! 2.4 root sink
7664!!
7665!! RECENT CHANGE(S) : 2016 by A. Ducharne to match the simplification of hydrol_soil
7666!!
7667!! MAIN OUTPUT VARIABLE(S) :
7668!!
7669!! REFERENCE(S) :
7670!!
7671!! FLOWCHART    : None
7672!! \n
7673!_ ================================================================================================================================
7674!_ hydrol_split_soil
7675
7676  SUBROUTINE hydrol_split_soil (kjpindex, veget_max, soiltile, vevapnu, vevapnu_pft, transpir, humrel, evap_bare_lim, tot_bare_soil)
7677    !
7678    ! interface description
7679
7680    !! 0. Variable and parameter declaration
7681
7682    !! 0.1 Input variables
7683
7684    INTEGER(i_std), INTENT(in)                               :: kjpindex
7685    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(in)       :: veget_max        !! max Vegetation map
7686    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile         !! Fraction of each soiltile within vegtot (0-1, unitless)
7687    REAL(r_std), DIMENSION (kjpindex), INTENT (in)           :: vevapnu          !! Bare soil evaporation
7688    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT (in)      :: vevapnu_pft      !! Bare soil evaporation
7689    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: transpir         !! Transpiration
7690    REAL(r_std), DIMENSION (kjpindex,nvm), INTENT (in)       :: humrel           !! Relative humidity
7691    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evap_bare_lim    !!   
7692    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_bare_soil    !! Total evaporating bare soil fraction
7693
7694    !! 0.4 Local variables
7695
7696    INTEGER(i_std)                                :: ji, jv, jsl, jst
7697    REAL(r_std), DIMENSION (kjpindex)             :: vevapnu_old
7698    REAL(r_std), DIMENSION (kjpindex,nstm)        :: vevapnu_ns      !! Bare soil evaporation
7699    REAL(r_std), DIMENSION (kjpindex)             :: tmp_check1
7700    REAL(r_std), DIMENSION (kjpindex)             :: tmp_check2
7701    REAL(r_std), DIMENSION (kjpindex,nstm)        :: tmp_check3
7702    LOGICAL                                       :: error=.FALSE. !! If true, exit in the end of subroutine
7703
7704!_ ================================================================================================================================
7705   
7706    !! 1. Split 2d variables into 3d variables, per soiltile
7707   
7708    ! Reminders:
7709    !  corr_veg_soil(:,nvm,nstm) = PFT fraction per soiltile in each grid-cell
7710    !      corr_veg_soil(ji,jv,jst)=veget_max(ji,jv)/soiltile(ji,jst)
7711    !  soiltile(:,nstm) = fraction of vegtot covered by each soiltile (0-1, unitless)
7712    !  vegtot(:) = total fraction of grid-cell covered by PFTs (fraction with bare soil + vegetation)
7713    !  veget_max(:,nvm) = PFT fractions of vegtot+frac_nobio
7714    !  veget(:,nvm) =  fractions (of vegtot+frac_nobio) covered by vegetation in each PFT
7715    !       BUT veget(:,1)=veget_max(:,1)
7716    !  frac_bare(:,nvm) = fraction (of veget_max) with bare soil in each PFT
7717    !  tot_bare_soil(:) = fraction of grid mesh covered by all bare soil (=SUM(frac_bare*veget_max))
7718    !  frac_bare_ns(:,nstm) = evaporating bare soil fraction (of vegtot) per soiltile (defined in hydrol_vegupd)
7719   
7720    !! 1.1 Throughfall
7721    ! Transformation from precisol (flux from PFT jv in m2 of grid-mesh)
7722    ! to  precisol_ns (flux from contributing PFTs with another unit, in m2 of soiltile)
7723    precisol_ns(:,:)=zero
7724    DO jv=1,nvm
7725       DO ji=1,kjpindex
7726          jst=pref_soil_veg(jv)
7727          IF((veget_max(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT. min_sechiba)) THEN
7728             precisol_ns(ji,jst) = precisol_ns(ji,jst) + &
7729                     precisol(ji,jv) / (soiltile(ji,jst)*vegtot(ji))               
7730          ENDIF
7731       END DO
7732    END DO
7733! write(numout,*) 'hydrol.f90 7682  maxval precisol_ns =', (maxval(precisol_ns))
7734!write(numout,*) 'hydrol.f90 7682  minval precisol_ns =', (minval(precisol_ns))
7735!write(numout,*) 'hydrol.f90 5335  maxval precisol =', (maxval(precisol))
7736!write(numout,*) 'hydrol.f90 5335  minval precisol =', (minval(precisol))
7737! IF (minval(precisol_ns) .LT. zero) THEN
7738! WRITE (numout,*) 'BOOM precisol_ns LT zero, minval =', (minval(precisol_ns))
7739! WRITE (numout,*) 'BOOM precisol LT zero, minval =', (minval(precisol))
7740! ENDIF   
7741    !! 1.2 Bare soil evaporation
7742
7743
7744    vevapnu_ns(:,:) = zero
7745    DO jv = 1,nvm
7746        DO jst = 1,nstm
7747            DO ji=1,kjpindex
7748                IF (veget_max(ji,jv) .GT. min_sechiba) THEN
7749                    vevapnu_ns(ji,jst) = vevapnu_ns(ji,jst) + vevapnu_pft(ji,jv)* &
7750                            & vegetmax_soil(ji,jv,jst) / vegtot(ji) / veget_max(ji,jv)
7751                ENDIF
7752            ENDDO
7753        ENDDO
7754    ENDDO
7755   
7756    !! 1.2.1 vevapnu_old
7757! AD16*** vevapnu_old ne sert que pour le split suivant de vevapnu (issu de enerbil) en ae_ns pour hydrol_soil
7758!           mais il ne semble y avoir aucune bonne raison de contraindre ae_ns en fonction de vevapnu_old
7759    vevapnu_old(:)=zero
7760    DO jst=1,nstm
7761       DO ji=1,kjpindex
7762          IF ( vegtot(ji) .GT. min_sechiba) THEN
7763             vevapnu_old(ji)=vevapnu_old(ji)+ &
7764                  & ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
7765          ENDIF
7766       END DO
7767    END DO
7768   
7769    !! 1.2.2 ae_ns new
7770! AD16*** les lignes ci-dessous sont excessivement compliquees et ne garantissent pas que ae_ns = 0 si evap_bare_lim=0
7771!           c'est notamment le cas pour les 3emes et 6emes conditions
7772    DO jst=1,nstm
7773       DO ji=1,kjpindex
7774          IF (vevapnu_old(ji).GT.min_sechiba) THEN   
7775             IF(evap_bare_lim(ji).GT.min_sechiba) THEN       
7776                ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji) 
7777             ELSE
7778                IF(vevapnu_old(ji).GT.min_sechiba) THEN 
7779                   ae_ns(ji,jst)=ae_ns(ji,jst) * vevapnu(ji)/vevapnu_old(ji) ! 3Úme condition
7780                ELSE
7781                   ae_ns(ji,jst)=zero
7782                ENDIF
7783             ENDIF
7784          ELSEIF(frac_bare_ns(ji,jst).GT.min_sechiba) THEN
7785             IF(evap_bare_lim(ji).GT.min_sechiba) THEN 
7786                ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji)
7787             ELSE
7788                IF(tot_bare_soil(ji).GT.min_sechiba) THEN 
7789                   ae_ns(ji,jst) = vevapnu(ji) * frac_bare_ns(ji,jst)/tot_bare_soil(ji) ! 6Úme condition
7790                ELSE
7791                   ae_ns(ji,jst) = zero
7792                ENDIF
7793             ENDIF
7794          ENDIF
7795       END DO
7796    END DO
7797! ADNV27072016: we believe the following block should be used (tests needed before committ, since AD16*** had pb with it)   
7798!!$    ! given the definition of evap_bare_lim, it leads to sum(ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji))=vevapnu(ji)
7799!!$    ae_ns(:,:)=zero
7800!!$    DO jst=1,nstm
7801!!$       DO ji=1,kjpindex
7802!!$          IF(evap_bare_lim(ji).GT.min_sechiba) THEN       
7803!!$             ae_ns(ji,jst) = vevapnu(ji) * evap_bare_lim_ns(ji,jst)/evap_bare_lim(ji)
7804!            ELSE
7805!               ae_ns(ji,jst) = zero
7806!!$          ENDIF
7807!!$       ENDDO
7808!!$    ENDDO
7809   
7810    !! 1.3 transpiration
7811    ! Transformation from transpir (flux from PFT jv in m2 of grid-mesh)
7812    ! to tr_ns (flux from contributing PFTs with another unit, in m2 of soiltile)
7813    ! To do next: simplify the use of humrelv(ji,jv,jst) /humrel(ji,jv), since both are equal
7814    tr_ns(:,:)=zero
7815    DO jv=1,nvm
7816       jst=pref_soil_veg(jv)
7817       DO ji=1,kjpindex
7818          IF ((humrel(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT.min_sechiba))THEN
7819             tr_ns(ji,jst)= tr_ns(ji,jst) &
7820                  + transpir(ji,jv) * (humrelv(ji,jv,jst) / humrel(ji,jv)) &
7821                  / (soiltile(ji,jst)*vegtot(ji))
7822                     
7823                ! xuhui 20151217
7824                ! tr_ns(ji,jst)=tr_ns(ji,jst)+ vegetmax_soil(ji,jv,jst)*humrelv(ji,jv,jst)* &
7825                !       & transpir(ji,jv) / humrel(ji,jv) / veget_max(ji,jv)
7826             ENDIF
7827       END DO
7828    END DO
7829
7830    !! 1.4 root sink
7831    ! Transformation from transpir (flux from PFT jv in m2 of grid-mesh)
7832    ! to root_sink (flux from contributing PFTs and soil layer with another unit, in m2 of soiltile)
7833    rootsink(:,:,:)=zero
7834    DO jv=1,nvm
7835       jst=pref_soil_veg(jv)
7836       DO jsl=1,nslm
7837          DO ji=1,kjpindex
7838             IF ((humrel(ji,jv).GT.min_sechiba) .AND. ((soiltile(ji,jst)*vegtot(ji)) .GT.min_sechiba)) THEN
7839                rootsink(ji,jsl,jst) = rootsink(ji,jsl,jst) &
7840                        + transpir(ji,jv) * (us(ji,jv,jst,jsl) / humrel(ji,jv)) &
7841                        / (soiltile(ji,jst)*vegtot(ji))                     
7842                   ! rootsink(ji,1,jst)=0 as us(ji,jv,jst,1)=0
7843             END IF
7844          END DO
7845       END DO
7846    END DO
7847
7848
7849    !!! ADNV270716 *** we are here
7850
7851    !! 2. Verification: Check if the deconvolution is correct and conserves the fluxes (grid-cell average)
7852
7853    IF (check_cwrr) THEN
7854
7855       !! 2.1 precisol
7856
7857       tmp_check1(:)=zero
7858       DO jst=1,nstm
7859          DO ji=1,kjpindex
7860             tmp_check1(ji)=tmp_check1(ji) + precisol_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
7861          END DO
7862       END DO
7863! write(numout,*) 'hydrol.f90 7812  maxval precisol tmp_check1 =', (maxval(tmp_check1))
7864!write(numout,*) 'hydrol.f90 7812  minval precisol_ns tmp_check1 =', (minval(tmp_check1))     
7865       tmp_check2(:)=zero 
7866       DO jv=1,nvm
7867          DO ji=1,kjpindex
7868             tmp_check2(ji)=tmp_check2(ji) + precisol(ji,jv)
7869          END DO
7870       END DO
7871
7872       DO ji=1,kjpindex   
7873          IF(ABS(tmp_check1(ji) - tmp_check2(ji)).GT.allowed_err) THEN
7874             WRITE(numout,*) 'PRECISOL SPLIT FALSE:ji=',ji,tmp_check1(ji),tmp_check2(ji)
7875             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- tmp_check2(ji))
7876             WRITE(numout,*) 'vegtot',vegtot(ji)
7877             DO jv=1,nvm
7878                WRITE(numout,'(a,i2.2,"|",F13.4,"|",F13.4,"|",3(F9.6))') &
7879                     'jv,veget_max, precisol, vegetmax_soil ', &
7880                     jv,veget_max(ji,jv),precisol(ji,jv),vegetmax_soil(ji,jv,:)
7881             END DO
7882             DO jst=1,nstm
7883                WRITE(numout,*) 'jst,precisol_ns',jst,precisol_ns(ji,jst)
7884                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
7885             END DO
7886
7887            ! error=.TRUE.
7888            ! CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
7889            !      & 'check_CWRR','PRECISOL SPLIT FALSE')
7890          ENDIF
7891       END DO
7892       
7893       !! 2.2 ae_ns and evapnu
7894
7895       tmp_check1(:)=zero
7896       DO jst=1,nstm
7897          DO ji=1,kjpindex
7898             tmp_check1(ji)=tmp_check1(ji) + ae_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
7899          END DO
7900       END DO
7901
7902       DO ji=1,kjpindex   
7903
7904          IF(ABS(tmp_check1(ji) - vevapnu(ji)).GT.allowed_err) THEN
7905             WRITE(numout,*) 'VEVAPNU SPLIT FALSE:ji, Sum(ae_ns), vevapnu =',ji,tmp_check1(ji),vevapnu(ji)
7906             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- vevapnu(ji))
7907             WRITE(numout,*) 'ae_ns',ae_ns(ji,:)
7908             WRITE(numout,*) 'vegtot',vegtot(ji)
7909             WRITE(numout,*) 'evap_bare_lim, evap_bare_lim_ns',evap_bare_lim(ji), evap_bare_lim_ns(ji,:)
7910             WRITE(numout,*) 'tot_bare_soil,frac_bare_ns',tot_bare_soil(ji),frac_bare_ns(ji,:)
7911             WRITE(numout,*) 'vevapnu_old',vevapnu_old(ji)
7912             DO jst=1,nstm
7913                WRITE(numout,*) 'jst,ae_ns',jst,ae_ns(ji,jst)
7914                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
7915                WRITE(numout,*) 'veget_max/vegtot/soiltile', veget_max(ji,:)/vegtot(ji)/soiltile(ji,jst)
7916                WRITE(numout,*) "vegetmax_soil",vegetmax_soil(ji,:,jst)
7917             END DO
7918
7919           !  error=.TRUE.
7920           !  CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
7921           !       & 'check_CWRR','VEVAPNU SPLIT FALSE')
7922          ENDIF
7923       ENDDO
7924
7925    !! 2.3 transpiration
7926
7927       tmp_check1(:)=zero
7928       DO jst=1,nstm
7929          DO ji=1,kjpindex
7930             tmp_check1(ji)=tmp_check1(ji) + tr_ns(ji,jst)*soiltile(ji,jst)*vegtot(ji)
7931          END DO
7932       END DO
7933       
7934       tmp_check2(:)=zero 
7935       DO jv=1,nvm
7936          DO ji=1,kjpindex
7937             tmp_check2(ji)=tmp_check2(ji) + transpir(ji,jv)
7938          END DO
7939       END DO
7940
7941       DO ji=1,kjpindex   
7942          IF(ABS(tmp_check1(ji)- tmp_check2(ji)).GT.allowed_err) THEN
7943             WRITE(numout,*) 'TRANSPIR SPLIT FALSE:ji=',ji,tmp_check1(ji),tmp_check2(ji)
7944             WRITE(numout,*) 'err',ABS(tmp_check1(ji)- tmp_check2(ji))
7945             WRITE(numout,*) 'vegtot',vegtot(ji)
7946             DO jv=1,nvm
7947                WRITE(numout,*) 'jv,veget_max, transpir',jv,veget_max(ji,jv),transpir(ji,jv)
7948                DO jst=1,nstm
7949                   WRITE(numout,*) 'vegetmax_soil:ji,jv,jst',ji,jv,jst,vegetmax_soil(ji,jv,jst)
7950                END DO
7951             END DO
7952             DO jst=1,nstm
7953                WRITE(numout,*) 'jst,tr_ns',jst,tr_ns(ji,jst)
7954                WRITE(numout,*) 'soiltile', soiltile(ji,jst)
7955             END DO
7956
7957           !  error=.TRUE.
7958           !  CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
7959           !       & 'check_CWRR','TRANSPIR SPLIT FALSE')
7960          ENDIF
7961
7962       END DO
7963
7964    !! 2.4 root sink
7965
7966       tmp_check3(:,:)=zero
7967       DO jst=1,nstm
7968          DO jsl=1,nslm
7969             DO ji=1,kjpindex
7970                tmp_check3(ji,jst)=tmp_check3(ji,jst) + rootsink(ji,jsl,jst)
7971             END DO
7972          END DO
7973       ENDDO
7974
7975       DO jst=1,nstm
7976          DO ji=1,kjpindex
7977             IF(ABS(tmp_check3(ji,jst) - tr_ns(ji,jst)).GT.allowed_err) THEN
7978                WRITE(numout,*) 'ROOTSINK SPLIT FALSE:ji,jst=', ji,jst,&
7979                     & tmp_check3(ji,jst),tr_ns(ji,jst)
7980                WRITE(numout,*) 'err',ABS(tmp_check3(ji,jst)- tr_ns(ji,jst))
7981                WRITE(numout,*) 'HUMREL(jv=1:13)',humrel(ji,:)
7982                WRITE(numout,*) 'TRANSPIR',transpir(ji,:)
7983                DO jv=1,nvm 
7984                   WRITE(numout,*) 'jv=',jv,'us=',us(ji,jv,jst,:)
7985                ENDDO
7986
7987             !   error=.TRUE.
7988             !   CALL ipslerr_p(2, 'hydrol_split_soil', 'We will STOP in the end of this subroutine.',&
7989             !     & 'check_CWRR','ROOTSINK SPLIT FALSE')
7990             ENDIF
7991          END DO
7992       END DO
7993
7994    ENDIF ! end of check_cwrr
7995
7996!! Exit if error was found previously in this subroutine
7997    IF ( error ) THEN
7998       WRITE(numout,*) 'One or more errors have been detected in hydrol_split_soil. Model stops.'
7999       CALL ipslerr_p(3, 'hydrol_split_soil', 'We will STOP now.',&
8000                  & 'One or several fatal errors were found previously.','')
8001    END IF
8002
8003  END SUBROUTINE hydrol_split_soil
8004 
8005
8006!! ================================================================================================================================
8007!! SUBROUTINE   : hydrol_diag_soil
8008!!
8009!>\BRIEF        Calculates diagnostic variables at the grid-cell scale
8010!!
8011!! DESCRIPTION  :
8012!! - 1. Apply mask_soiltile
8013!! - 2. Sum 3d variables in 2d variables with fraction of vegetation per soil type
8014!!
8015!! RECENT CHANGE(S) : 2016 by A. Ducharne for the claculation of shumdiag_perma
8016!!
8017!! MAIN OUTPUT VARIABLE(S) :
8018!!
8019!! REFERENCE(S) :
8020!!
8021!! FLOWCHART    : None
8022!! \n
8023!_ ================================================================================================================================
8024!_ hydrol_diag_soil
8025
8026  SUBROUTINE hydrol_diag_soil (kjpindex, veget_max, soiltile, njsc, runoff, drainage, &
8027       & evapot, vevapnu, returnflow, reinfiltration, irrigation, &
8028       & shumdiag,shumdiag_perma, k_litt, litterhumdiag, humrel, vegstress, drysoil_frac, tot_melt, & !pss:+
8029       & drunoff_tot) !pss:-
8030
8031    !
8032    ! interface description
8033
8034    !! 0. Variable and parameter declaration
8035
8036    !! 0.1 Input variables
8037
8038    ! input scalar
8039    INTEGER(i_std), INTENT(in)                               :: kjpindex 
8040    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)        :: veget_max       !! Max. vegetation type
8041    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)         :: njsc            !! Index of the dominant soil textural class in the grid cell (1-nscm, unitless)
8042    REAL(r_std), DIMENSION (kjpindex,nstm), INTENT (in)      :: soiltile        !! Fraction of each soil tile within vegtot (0-1, unitless)
8043    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: evapot          !!
8044    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: returnflow      !! Water returning to the deep reservoir
8045    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: reinfiltration  !! Water returning to the top of the soil
8046    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: irrigation      !! Water from irrigation
8047    REAL(r_std), DIMENSION (kjpindex), INTENT(in)            :: tot_melt        !!
8048
8049    !! 0.2 Output variables
8050
8051    REAL(r_std), DIMENSION (kjpindex), INTENT (out)          :: drysoil_frac    !! Function of litter wetness
8052    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: runoff          !! complete runoff
8053    REAL(r_std), DIMENSION (kjpindex), INTENT(out)           :: drainage        !! Drainage
8054    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out)      :: shumdiag        !! relative soil moisture
8055    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (out)      :: shumdiag_perma  !! Percent of porosity filled with water (mc/mcs) used for the thermal computations
8056    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: k_litt          !! litter cond.
8057    REAL(r_std),DIMENSION (kjpindex), INTENT (out)           :: litterhumdiag   !! litter humidity
8058    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (out)       :: humrel          !! Relative humidity
8059    REAL(r_std), DIMENSION (kjpindex, nvm), INTENT(out)      :: vegstress       !! Veg. moisture stress (only for vegetation growth)
8060
8061!pss:+
8062    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)           :: drunoff_tot          !! Dunne runoff
8063!pss:-
8064
8065    !! 0.3 Modified variables
8066
8067    REAL(r_std), DIMENSION (kjpindex), INTENT(inout)         :: vevapnu         !!
8068
8069    !! 0.4 Local variables
8070
8071    INTEGER(i_std)                                           :: ji, jv, jsl, jst, i, jd
8072    REAL(r_std), DIMENSION (kjpindex)                        :: mask_vegtot
8073    REAL(r_std)                                              :: k_tmp, tmc_litter_ratio
8074
8075!_ ================================================================================================================================
8076    !
8077    ! Put the prognostics variables of soil to zero if soiltype is zero
8078
8079    !! 1. Apply mask_soiltile
8080   
8081    DO jst=1,nstm 
8082       IF (ok_freeze_cwrr) THEN
8083           CALL hydrol_soil_coef(kjpindex,jst,njsc)
8084       ENDIF
8085       DO ji=1,kjpindex
8086
8087             ae_ns(ji,jst) = ae_ns(ji,jst) * mask_soiltile(ji,jst)
8088             dr_ns(ji,jst) = dr_ns(ji,jst) * mask_soiltile(ji,jst)
8089             ru_ns(ji,jst) = ru_ns(ji,jst) * mask_soiltile(ji,jst)
8090             tmc(ji,jst) =  tmc(ji,jst) * mask_soiltile(ji,jst)
8091
8092             DO jv=1,nvm
8093                humrelv(ji,jv,jst) = humrelv(ji,jv,jst) * mask_soiltile(ji,jst)
8094                DO jsl=1,nslm
8095                   us(ji,jv,jst,jsl) = us(ji,jv,jst,jsl)  * mask_soiltile(ji,jst)
8096                END DO
8097             END DO
8098
8099             DO jsl=1,nslm         
8100                mc(ji,jsl,jst) = mc(ji,jsl,jst)  * mask_soiltile(ji,jst)
8101             END DO
8102!      IF (minval(mc) .LT. zero) THEN
8103!       WRITE (numout,*) 'BOOM mc LT zero 8004'
8104!      END IF
8105       END DO
8106    END DO
8107
8108    runoff(:) = zero
8109    drainage(:) = zero
8110    humtot(:) = zero
8111    shumdiag(:,:)= zero
8112    shumdiag_perma(:,:)=zero
8113    k_litt(:) = zero
8114    litterhumdiag(:) = zero
8115    tmc_litt_dry_mea(:) = zero
8116    tmc_litt_wet_mea(:) = zero
8117    tmc_litt_mea(:) = zero
8118    humrel(:,:) = zero
8119    vegstress(:,:) = zero
8120    IF (ok_freeze_cwrr) THEN
8121       profil_froz_hydro(:,:)=zero ! initialisation for the mean of profil_froz_hydro_ns
8122    ENDIF
8123   
8124    !! 2. Sum 3d variables in 2d variables with fraction of vegetation per soil type
8125
8126    DO ji = 1, kjpindex
8127       mask_vegtot(ji) = 0
8128       IF(vegtot(ji) .GT. min_sechiba) THEN
8129          mask_vegtot(ji) = 1
8130       ENDIF
8131    END DO
8132   
8133    DO ji = 1, kjpindex 
8134       ! Here we weight ae_ns by the fraction of bare evaporating soil.
8135       ! This is given by frac_bare_ns, taking into account bare soil under vegetation
8136       ae_ns(ji,:) = mask_vegtot(ji) * ae_ns(ji,:) * frac_bare_ns(ji,:)
8137    END DO
8138
8139    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
8140    DO jst = 1, nstm
8141       DO ji = 1, kjpindex 
8142          drainage(ji) = mask_vegtot(ji) * (drainage(ji) + vegtot(ji)*soiltile(ji,jst) * dr_ns(ji,jst))
8143          runoff(ji) = mask_vegtot(ji) *  (runoff(ji) +   vegtot(ji)*soiltile(ji,jst) * ru_ns(ji,jst)) &
8144               &   + (1 - mask_vegtot(ji)) * (tot_melt(ji) + irrigation(ji) + returnflow(ji) + reinfiltration(ji))
8145          humtot(ji) = mask_vegtot(ji) * (humtot(ji) + vegtot(ji)*soiltile(ji,jst) * tmc(ji,jst)) 
8146          IF (ok_freeze_cwrr) THEN 
8147             !  profil_froz_hydro_ns comes from hydrol_soil, to remain the same as in the prognotic loop
8148             profil_froz_hydro(ji,:)=mask_vegtot(ji) * &
8149                  (profil_froz_hydro(ji,:) + vegtot(ji)*soiltile(ji,jst) * profil_froz_hydro_ns(ji,:, jst))
8150          ENDIF
8151       END DO
8152    END DO
8153
8154    ! we add the excess of snow sublimation to vevapnu
8155    ! - because vevapsno is modified in hydrol_snow if subsinksoil
8156    ! - it is multiplied by vegtot because it is devided by 1-tot_frac_nobio at creation in hydrol_snow
8157
8158    DO ji = 1,kjpindex
8159       vevapnu(ji) = vevapnu (ji) + subsinksoil(ji)*vegtot(ji)
8160    END DO
8161
8162    DO jst=1,nstm
8163       DO jv=1,nvm
8164          DO ji=1,kjpindex
8165             IF(veget_max(ji,jv).GT.min_sechiba) THEN
8166                vegstress(ji,jv)=vegstress(ji,jv)+vegstressv(ji,jv,jst)
8167                vegstress(ji,jv)= MAX(vegstress(ji,jv),zero)
8168             ENDIF
8169          END DO
8170       END DO
8171    END DO
8172
8173    DO jst=1,nstm
8174       DO jv=1,nvm
8175          DO ji=1,kjpindex
8176             humrel(ji,jv)=humrel(ji,jv)+humrelv(ji,jv,jst)
8177             humrel(ji,jv)=MAX(humrel(ji,jv),zero)
8178          END DO
8179       END DO
8180    END DO
8181
8182    !! Litter... the goal is to calculate drysoil_frac, to calculate the albedo in condveg
8183    ! In condveg, drysoil_frac serve to calculate the albedo of drysoil, excluding the nobio contribution which is further added
8184    ! In conclusion, we calculate drysoil_frac based on moisture averages restricted to the soiltile (no multiplication by vegtot)
8185    !! k_litt is calculated here as a grid-cell average (for consistency with drainage)
8186    !! litterhumdiag, like shumdiag, is averaged over the soiltiles for transmission to stomate
8187    DO jst=1,nstm       
8188       DO ji=1,kjpindex
8189          ! We compute here a mean k for the 'litter' used for reinfiltration from floodplains of ponds       
8190          IF ( tmc_litter(ji,jst) < tmc_litter_res(ji,jst)) THEN
8191             i = imin
8192          ELSE
8193             tmc_litter_ratio = (tmc_litter(ji,jst)-tmc_litter_res(ji,jst)) / &
8194                  & (tmc_litter_sat(ji,jst)-tmc_litter_res(ji,jst))
8195             i= MAX(MIN(INT((imax-imin)*tmc_litter_ratio)+imin, imax-1), imin)
8196          ENDIF       
8197          k_tmp = MAX(k_lin(i,1,ji)*ks(njsc(ji)), zero)
8198          k_litt(ji) = k_litt(ji) + vegtot(ji)*soiltile(ji,jst) * SQRT(k_tmp) ! grid-cell average
8199       ENDDO     
8200       DO ji=1,kjpindex
8201          litterhumdiag(ji) = litterhumdiag(ji) + &
8202               & soil_wet_litter(ji,jst) * soiltile(ji,jst)
8203
8204          tmc_litt_wet_mea(ji) =  tmc_litt_wet_mea(ji) + & 
8205               & tmc_litter_awet(ji,jst)* soiltile(ji,jst)
8206
8207          tmc_litt_dry_mea(ji) = tmc_litt_dry_mea(ji) + &
8208               & tmc_litter_adry(ji,jst) * soiltile(ji,jst) 
8209
8210          tmc_litt_mea(ji) = tmc_litt_mea(ji) + &
8211               & tmc_litter(ji,jst) * soiltile(ji,jst) 
8212       ENDDO
8213    ENDDO
8214   
8215    DO ji=1,kjpindex
8216       IF ( tmc_litt_wet_mea(ji) - tmc_litt_dry_mea(ji) > zero ) THEN
8217          drysoil_frac(ji) = un + MAX( MIN( (tmc_litt_dry_mea(ji) - tmc_litt_mea(ji)) / &
8218               & (tmc_litt_wet_mea(ji) - tmc_litt_dry_mea(ji)), zero), - un)
8219       ELSE
8220          drysoil_frac(ji) = zero
8221       ENDIF
8222    END DO
8223   
8224    ! Calculate soilmoist, as a function of total water content (mc)
8225    ! We average the values of each soiltile and multiply by vegtot to transform to a grid-cell mean
8226    soilmoist(:,:) = zero
8227    DO jst=1,nstm
8228       DO ji=1,kjpindex
8229             soilmoist(ji,1) = soilmoist(ji,1) + soiltile(ji,jst) * &
8230                  dz(2) * ( trois*mc(ji,1,jst) + mc(ji,2,jst) )/huit
8231             DO jsl = 2,nslm-1
8232                soilmoist(ji,jsl) = soilmoist(ji,jsl) + soiltile(ji,jst) * &
8233                     ( dz(jsl) * (trois*mc(ji,jsl,jst)+mc(ji,jsl-1,jst))/huit &
8234                     + dz(jsl+1) * (trois*mc(ji,jsl,jst)+mc(ji,jsl+1,jst))/huit )
8235             END DO
8236             soilmoist(ji,nslm) = soilmoist(ji,nslm) + soiltile(ji,jst) * &
8237                  dz(nslm) * (trois*mc(ji,nslm,jst) + mc(ji,nslm-1,jst))/huit
8238       END DO
8239    END DO
8240    DO ji=1,kjpindex
8241       soilmoist(ji,:) = soilmoist(ji,:) * vegtot(ji) ! conversion to grid-cell average
8242    ENDDO
8243   
8244    ! Shumdiag: we start from soil_wet, change the range over which the relative moisture is calculated,
8245    ! convert from hydrol to diag soil layers, then do a spatial average,
8246    ! excluding the nobio fraction on which stomate doesn't act
8247    DO jst=1,nstm     
8248       DO jd=1,nbdl
8249          DO ji=1,kjpindex
8250             DO jsl=1,nslm   
8251                shumdiag(ji,jd) = shumdiag(ji,jd) + soil_wet(ji,jsl,jst) * &
8252                     soiltile(ji,jst) * frac_hydro_diag(jsl,jd) * &
8253                     ((mcs(ji)-mcw(ji))/(mcf(ji)-mcw(ji)))
8254               ENDDO
8255             shumdiag(ji,jd) = MAX(MIN(shumdiag(ji,jd), un), zero) 
8256          ENDDO
8257       ENDDO
8258    ENDDO
8259   
8260    ! Shumdiag_perma is based on soilmoist / moisture at saturation in the layer
8261    ! Her we start from grid averages by hydrol soil layer and transform it to the diag levels
8262    ! We keep a grid-cell average, like for all variables transmitted to ok_freeze
8263    DO jd=1,nbdl
8264       DO ji=1,kjpindex
8265          DO jsl=1,nslm             
8266             shumdiag_perma(ji,jd) = soilmoist(ji,jsl)*frac_hydro_diag(jsl,jd) &
8267                  /(dh(jsl)*mcs(ji))
8268          ENDDO
8269          shumdiag_perma(ji,jd) = MAX(MIN(shumdiag_perma(ji,jd), un), zero) 
8270       ENDDO
8271    ENDDO
8272   
8273  END SUBROUTINE hydrol_diag_soil 
8274
8275
8276!! ================================================================================================================================
8277!! SUBROUTINE   : hydrol_waterbal_init
8278!!
8279!>\BRIEF        Initialize variables needed for hydrol_waterbal
8280!!
8281!! DESCRIPTION  : Initialize variables needed for hydrol_waterbal
8282!!
8283!! RECENT CHANGE(S) : None
8284!!
8285!! MAIN OUTPUT VARIABLE(S) :
8286!!
8287!! REFERENCE(S) :
8288!!
8289!! FLOWCHART    : None
8290!! \n
8291!_ ================================================================================================================================
8292  SUBROUTINE hydrol_waterbal_init(kjpindex, qsintveg, snow, snow_nobio)
8293   
8294    !! 0. Variable and parameter declaration
8295    !! 0.1 Input variables
8296    INTEGER(i_std), INTENT (in)                          :: kjpindex     !! Domain size
8297    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)    :: qsintveg     !! Water on vegetation due to interception
8298    REAL(r_std),DIMENSION (kjpindex), INTENT (in)        :: snow         !! Snow mass [Kg/m^2]
8299    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio   !! Ice water balance
8300   
8301    !! 0.2 Local variables
8302    INTEGER(i_std) :: ji
8303    REAL(r_std) :: watveg
8304
8305!_ ================================================================================================================================
8306    !
8307    !
8308    !
8309    IF ( ALL( tot_water_beg(:) == val_exp ) ) THEN
8310       ! tot_water_beg was not found in restart file
8311       DO ji = 1, kjpindex
8312          watveg = SUM(qsintveg(ji,:))
8313          tot_water_beg(ji) = humtot(ji) + watveg + snow(ji) + SUM(snow_nobio(ji,:))
8314          ! all values are grid-cell averages
8315       ENDDO
8316       tot_water_end(:) = tot_water_beg(:)
8317       tot_flux(:) = zero
8318    ELSE
8319       tot_water_end(:) = tot_water_beg(:)
8320       tot_flux(:) = zero
8321    ENDIF
8322
8323  END SUBROUTINE hydrol_waterbal_init
8324!! ================================================================================================================================
8325!! SUBROUTINE   : hydrol_waterbal
8326!!
8327!>\BRIEF        Checks the water balance.
8328!!
8329!! DESCRIPTION  :
8330!! This routine checks the water balance. First it gets the total
8331!! amount of water and then it compares the increments with the fluxes.
8332!! The computation is only done over the soil area as over glaciers (and lakes?)
8333!! we do not have water conservation.
8334!! This verification does not make much sense in REAL*4 as the precision is the same as some
8335!! of the fluxes
8336!!
8337!! RECENT CHANGE(S) : None
8338!!
8339!! MAIN OUTPUT VARIABLE(S) :
8340!!
8341!! REFERENCE(S) :
8342!!
8343!! FLOWCHART    : None
8344!! \n
8345!_ ================================================================================================================================
8346!_ hydrol_waterbal
8347
8348  SUBROUTINE hydrol_waterbal (kjpindex, index, veget_max, totfrac_nobio, &
8349       & qsintveg, snow,snow_nobio, precip_rain, precip_snow, returnflow, reinfiltration, irrigation, tot_melt, &
8350       & vevapwet, transpir, vevapnu, vevapsno, vevapflo, floodout, runoff, drainage)
8351    !
8352    !! 0. Variable and parameter declaration
8353
8354    !! 0.1 Input variables
8355
8356    INTEGER(i_std), INTENT (in)                        :: kjpindex     !! Domain size
8357    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index        !! Indeces of the points on the map
8358    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: veget_max    !! Max Fraction of vegetation type
8359    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: totfrac_nobio!! Total fraction of continental ice+lakes+...
8360    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintveg     !! Water on vegetation due to interception
8361    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: snow         !! Snow mass [Kg/m^2]
8362    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio !!Ice water balance
8363    !
8364    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_rain  !! Rain precipitation
8365    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: precip_snow  !! Snow precipitation
8366    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: returnflow   !! Water to the bottom
8367    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: reinfiltration !! Water to the top
8368    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: irrigation   !! Water from irrigation
8369    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: tot_melt     !! Total melt
8370    !
8371    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: vevapwet     !! Interception loss
8372    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: transpir     !! Transpiration
8373    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: vevapnu      !! Bare soil evaporation
8374    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: vevapsno     !! Snow evaporation
8375    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: vevapflo     !! Floodplains evaporation
8376    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: floodout     !! flow out of floodplains
8377    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: runoff       !! complete runoff
8378    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: drainage     !! Drainage
8379
8380    !! 0.2 Output variables
8381
8382    !! 0.3 Modified variables
8383
8384    !! 0.4 Local variables
8385
8386    INTEGER(i_std) :: ji
8387    REAL(r_std) :: watveg, delta_water
8388    LOGICAL     :: error=.FALSE.  !! If true, exit in the end of subroutine
8389
8390!_ ================================================================================================================================
8391
8392    tot_water_end(:) = zero
8393    tot_flux(:) = zero
8394    !
8395    DO ji = 1, kjpindex
8396       !
8397       ! If the fraction of ice, lakes, etc. does not complement the vegetation fraction then we do not
8398       ! need to go any further
8399       !
8400       IF ( ABS(un - (totfrac_nobio(ji) + vegtot(ji))) .GT. allowed_err ) THEN
8401          WRITE(numout,*) 'HYDROL problem in vegetation or frac_nobio on point ', ji
8402          WRITE(numout,*) 'totfrac_nobio : ', totfrac_nobio(ji)
8403          WRITE(numout,*) 'vegetation fraction : ', vegtot(ji)
8404
8405          error=.TRUE.
8406          CALL ipslerr_p(2, 'hydrol_waterbal', 'We will STOP in the end of hydrol_waterbal.','','')
8407       ENDIF
8408    ENDDO
8409
8410    DO ji = 1, kjpindex
8411       !
8412       watveg = SUM(qsintveg(ji,:))
8413       tot_water_end(ji) = humtot(ji) + watveg + snow(ji) + SUM(snow_nobio(ji,:))
8414       !
8415       tot_flux(ji) =  precip_rain(ji) + precip_snow(ji) + irrigation (ji) - &
8416            & SUM(vevapwet(ji,:)) - SUM(transpir(ji,:)) - vevapnu(ji) - vevapsno(ji) - vevapflo(ji) + &
8417            & floodout(ji) - runoff(ji) - drainage(ji) + returnflow(ji) + reinfiltration(ji)
8418    ENDDO
8419   
8420    DO ji = 1, kjpindex
8421       !
8422       delta_water = tot_water_end(ji) - tot_water_beg(ji)
8423       !
8424       !
8425       !  Set some precision ! This is a wild guess and corresponds to what works on an IEEE machine
8426       !  under double precision (REAL*8).
8427       !
8428       !
8429       IF ( ABS(delta_water-tot_flux(ji)) .GT. deux*allowed_err ) THEN
8430          WRITE(numout,*) '------------------------------------------------------------------------- '
8431          WRITE(numout,*) 'HYDROL does not conserve water. The erroneous point is : ', ji
8432          WRITE(numout,*) 'Coord erroneous point', lalo(ji,:)
8433          WRITE(numout,*) 'The error in mm/s is :', (delta_water-tot_flux(ji))/dt_sechiba, ' and in mm/dt : ', &
8434               & delta_water-tot_flux(ji)
8435          WRITE(numout,*) 'delta_water : ', delta_water, ' tot_flux : ', tot_flux(ji)
8436          WRITE(numout,*) 'Actual and allowed error : ', ABS(delta_water-tot_flux(ji)), allowed_err
8437          WRITE(numout,*) 'vegtot : ', vegtot(ji)
8438          WRITE(numout,*) 'precip_rain : ', precip_rain(ji)
8439          WRITE(numout,*) 'precip_snow : ',  precip_snow(ji)
8440          WRITE(numout,*) 'Water from routing. Reinfiltration/returnflow/irrigation : ', reinfiltration(ji), &
8441               & returnflow(ji),irrigation(ji)
8442          WRITE(numout,*) 'Total water in soil humtot:',  humtot(ji)
8443          WRITE(numout,*) 'mc:' , mc(ji,:,:)
8444          WRITE(numout,*) 'Water on vegetation watveg:', watveg
8445          WRITE(numout,*) 'Snow mass snow:', snow(ji)
8446          WRITE(numout,*) 'Snow mass on ice snow_nobio:', SUM(snow_nobio(ji,:))
8447          WRITE(numout,*) 'Melt water tot_melt:', tot_melt(ji)
8448          WRITE(numout,*) 'evapwet : ', vevapwet(ji,:)
8449          WRITE(numout,*) 'transpir : ', transpir(ji,:)
8450          WRITE(numout,*) 'evapnu, evapsno, evapflo: ', vevapnu(ji), vevapsno(ji), vevapflo(ji)
8451          WRITE(numout,*) 'drainage,runoff,floodout : ', drainage(ji),runoff(ji),floodout(ji)
8452         ! error=.TRUE.
8453         ! CALL ipslerr_p(2, 'hydrol_waterbal', 'We will STOP in the end of hydrol_waterbal.','','')
8454       ENDIF
8455       !
8456    ENDDO
8457    !
8458    ! Transfer the total water amount at the end of the current timestep top the begining of the next one.
8459    !
8460    tot_water_beg = tot_water_end
8461    !
8462   
8463    ! Exit if one or more errors were found
8464    IF ( error ) THEN
8465       WRITE(numout,*) 'One or more errors have been detected in hydrol_waterbal. Model stops.'
8466       CALL ipslerr_p(3, 'hydrol_waterbal', 'We will STOP now.',&
8467            'One or several fatal errors were found previously.','')
8468    END IF
8469   
8470  END SUBROUTINE hydrol_waterbal
8471
8472
8473!! ================================================================================================================================
8474!! SUBROUTINE   : hydrol_alma
8475!!
8476!>\BRIEF        This routine computes the changes in soil moisture and interception storage for the ALMA outputs. 
8477!!
8478!! DESCRIPTION  : None
8479!!
8480!! RECENT CHANGE(S) : None
8481!!
8482!! MAIN OUTPUT VARIABLE(S) :
8483!!
8484!! REFERENCE(S) :
8485!!
8486!! FLOWCHART    : None
8487!! \n
8488!_ ================================================================================================================================
8489!_ hydrol_alma
8490
8491  SUBROUTINE hydrol_alma (kjpindex, index, lstep_init, qsintveg, snow, snow_nobio, soilwet)
8492    !
8493    !! 0. Variable and parameter declaration
8494
8495    !! 0.1 Input variables
8496
8497    INTEGER(i_std), INTENT (in)                        :: kjpindex     !! Domain size
8498    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)   :: index        !! Indeces of the points on the map
8499    LOGICAL, INTENT (in)                               :: lstep_init   !! At which time is this routine called ?
8500    REAL(r_std),DIMENSION (kjpindex,nvm), INTENT (in)  :: qsintveg     !! Water on vegetation due to interception
8501    REAL(r_std),DIMENSION (kjpindex), INTENT (in)      :: snow         !! Snow water equivalent
8502    REAL(r_std),DIMENSION (kjpindex,nnobio), INTENT (in) :: snow_nobio !! Water balance on ice, lakes, .. [Kg/m^2]
8503
8504    !! 0.2 Output variables
8505
8506    REAL(r_std),DIMENSION (kjpindex), INTENT (out)      :: soilwet     !! Soil wetness
8507
8508    !! 0.3 Modified variables
8509
8510    !! 0.4 Local variables
8511
8512    INTEGER(i_std) :: ji
8513    REAL(r_std) :: watveg
8514
8515!_ ================================================================================================================================
8516    !
8517    !
8518    IF ( lstep_init ) THEN
8519       ! Initialize variables if they were not found in the restart file
8520
8521       DO ji = 1, kjpindex
8522          watveg = SUM(qsintveg(ji,:))
8523          tot_watveg_beg(ji) = watveg
8524          tot_watsoil_beg(ji) = humtot(ji)
8525          snow_beg(ji)        = snow(ji) + SUM(snow_nobio(ji,:))
8526       ENDDO
8527
8528       RETURN
8529
8530    ENDIF
8531    !
8532    ! Calculate the values for the end of the time step
8533    !
8534    DO ji = 1, kjpindex
8535       watveg = SUM(qsintveg(ji,:)) ! average within the mesh
8536       tot_watveg_end(ji) = watveg
8537       tot_watsoil_end(ji) = humtot(ji) ! average within the mesh
8538       snow_end(ji) = snow(ji)+ SUM(snow_nobio(ji,:)) ! average within the mesh
8539
8540       delintercept(ji) = tot_watveg_end(ji) - tot_watveg_beg(ji) ! average within the mesh
8541       delsoilmoist(ji) = tot_watsoil_end(ji) - tot_watsoil_beg(ji)
8542       delswe(ji)       = snow_end(ji) - snow_beg(ji) ! average within the mesh
8543    ENDDO
8544    !
8545    !
8546    ! Transfer the total water amount at the end of the current timestep top the begining of the next one.
8547    !
8548    tot_watveg_beg = tot_watveg_end
8549    tot_watsoil_beg = tot_watsoil_end
8550    snow_beg(:) = snow_end(:)
8551    !
8552    DO ji = 1,kjpindex
8553       IF ( mx_eau_var(ji) > 0 ) THEN
8554          soilwet(ji) = tot_watsoil_end(ji) / mx_eau_var(ji)
8555       ELSE
8556          soilwet(ji) = zero
8557       ENDIF
8558    ENDDO
8559    !
8560  END SUBROUTINE hydrol_alma
8561  !
8562
8563
8564!! ================================================================================================================================
8565!! SUBROUTINE   : hydrol_calculate_temp_hydro
8566!!
8567!>\BRIEF         Calculate the temperature at hydrological levels 
8568!!
8569!! DESCRIPTION  : None
8570!!
8571!! RECENT CHANGE(S) : None
8572!!
8573!! MAIN OUTPUT VARIABLE(S) :
8574!!
8575!! REFERENCE(S) :
8576!!
8577!! FLOWCHART    : None
8578!! \n
8579!_ ================================================================================================================================
8580
8581
8582  SUBROUTINE hydrol_calculate_temp_hydro(kjpindex, stempdiag, snow,snowdz)
8583
8584    !! 0.1 Input variables
8585
8586    INTEGER(i_std), INTENT(in)                             :: kjpindex 
8587    REAL(r_std),DIMENSION (kjpindex,nbdl), INTENT (in)     :: stempdiag
8588    REAL(r_std),DIMENSION (kjpindex), INTENT (in)          :: snow
8589    REAL(r_std),DIMENSION (kjpindex,nsnow), INTENT (in)    :: snowdz
8590
8591
8592    !! 0.2 Local variables
8593   
8594    INTEGER jh, jd, ji
8595    REAL(r_std) :: snow_h
8596    REAL(r_std)  :: lev_diag, prev_diag, lev_prog, prev_prog
8597    REAL(r_std), DIMENSION(nslm,nbdl) :: intfactt
8598   
8599   
8600    DO ji=1,kjpindex
8601       IF (ok_explicitsnow) THEN 
8602          !The snow pack is above the surface soil in the new snow model.
8603          snow_h=0
8604       ELSE 
8605          snow_h=snow(ji)/sn_dens
8606       ENDIF
8607       
8608       intfactt(:,:)=0.
8609       prev_diag = snow_h
8610       DO jh = 1, nslm
8611          IF (jh.EQ.1) THEN
8612             lev_diag = zz(2)/1000./2.+snow_h
8613          ELSEIF (jh.EQ.nslm) THEN
8614             lev_diag = zz(nslm)/1000.+snow_h
8615             
8616          ELSE
8617             lev_diag = zz(jh)/1000. &
8618                  & +(zz(jh+1)-zz(jh))/1000./2.+snow_h
8619             
8620          ENDIF
8621          prev_prog = 0.0
8622          DO jd = 1, nbdl
8623             lev_prog = diaglev(jd)
8624             IF ((lev_diag.GT.diaglev(nbdl).AND. &
8625                  & prev_diag.LT.diaglev(nbdl)-min_sechiba)) THEN
8626                lev_diag=diaglev(nbdl)         
8627             ENDIF
8628             intfactt(jh,jd) = MAX(MIN(lev_diag,lev_prog)-MAX(prev_diag, prev_prog),&
8629                  & 0.0)/(lev_diag-prev_diag)
8630             prev_prog = lev_prog
8631          ENDDO
8632          IF (lev_diag.GT.diaglev(nbdl).AND. &
8633               & prev_diag.GE.diaglev(nbdl)-min_sechiba) intfactt(jh,nbdl)=1.
8634          prev_diag = lev_diag
8635       ENDDO
8636    ENDDO
8637   
8638    temp_hydro(:,:)=0.
8639    DO jd= 1, nbdl
8640       DO jh= 1, nslm
8641          DO ji = 1, kjpindex
8642             temp_hydro(ji,jh) = temp_hydro(ji,jh) + stempdiag(ji,jd)*intfactt(jh,jd)
8643          ENDDO
8644       ENDDO
8645    ENDDO
8646   
8647  END SUBROUTINE hydrol_calculate_temp_hydro
8648
8649
8650!! ================================================================================================================================
8651!! SUBROUTINE   : hydrol_calculate_frac_hydro_diag
8652!!
8653!>\BRIEF         Caluculate frac_hydro_diag for interpolation between hydrological and diagnostic axes
8654!!
8655!! DESCRIPTION  : None
8656!!
8657!! RECENT CHANGE(S) : None
8658!!
8659!! MAIN OUTPUT VARIABLE(S) :
8660!!
8661!! REFERENCE(S) :
8662!!
8663!! FLOWCHART    : None
8664!! \n
8665!_ ================================================================================================================================
8666
8667  SUBROUTINE hydrol_calculate_frac_hydro_diag
8668
8669    !! 0.1 Local variables
8670
8671    INTEGER(i_std) :: jd, jh
8672    REAL(r_std)    :: prev_hydro, next_hydro, prev_diag, next_diag
8673   
8674
8675    frac_hydro_diag(:,:)=0.
8676    prev_diag = 0.0
8677   
8678    DO jd = 1, nbdl 
8679       
8680       next_diag = diaglev(jd)
8681       prev_hydro = 0.0
8682       DO jh = 1, nslm
8683          IF (jh.EQ.1) THEN
8684             next_hydro = zz(2)/1000./2.
8685          ELSEIF (jh.EQ.nslm) THEN
8686             next_hydro = zz(nslm)/1000.
8687          ELSE
8688             next_hydro = zz(jh)/1000.+(zz(jh+1)-zz(jh))/1000./2.
8689          ENDIF
8690          frac_hydro_diag(jh,jd) = MAX(MIN(next_hydro, next_diag)-MAX(prev_hydro, prev_diag), 0.)/(next_diag - prev_diag)
8691          prev_hydro=next_hydro
8692       ENDDO
8693       
8694       prev_diag = next_diag
8695    ENDDO
8696
8697  END SUBROUTINE hydrol_calculate_frac_hydro_diag
8698
8699!!
8700!================================================================================================================================
8701!! SUBROUTINE   : read_refSOC_1dfile
8702!!
8703!>\BRIEF         
8704!!
8705!! DESCRIPTION  : Read file of soil organic carbon to be used in thermix
8706!! (insulating effect)
8707!!               
8708!!
8709!! RECENT CHANGE(S) : None
8710!!
8711!! MAIN OUTPUT VARIABLE(S): refSOC : soil organic carbon from data
8712!!                         
8713!! REFERENCE(S) :
8714!!
8715!! FLOWCHART    : None
8716!! \n
8717!_
8718!================================================================================================================================
8719
8720  SUBROUTINE read_refSOC_1dfile(nbpt, lalo, neighbours, resolution, contfrac)
8721
8722    !! 0. Variable and parameter declaration
8723
8724    !! 0.1 Input variables
8725
8726    INTEGER(i_std), INTENT(in)                    :: nbpt                  !! Number of points for which the data needs to be interpolated (unitless)             
8727    REAL(r_std), INTENT(in)                       :: lalo(nbpt,2)          !! Vector of latitude and longitudes (degree)       
8728    INTEGER(i_std), INTENT(in)                    :: neighbours(nbpt,NbNeighb)!! Vector of neighbours for each grid point (1=N,2=E,3=S,4=W) 
8729    REAL(r_std), INTENT(in)                       :: resolution(nbpt,2)    !! The size of each grid cell in X and Y (km)
8730    REAL(r_std), INTENT(in)                       :: contfrac(nbpt)        !! Fraction of land in each grid cell (unitless)   
8731
8732    !! 0.4 Local variables
8733    INTEGER(i_std)                                :: nbvmax                !! nbvmax for interpolation (unitless)
8734    CHARACTER(LEN=80)                             :: filename
8735    INTEGER(i_std)                                :: iml, jml, lml, tml    !! Indices
8736    INTEGER(i_std)                                :: fid, ib, ip, jp, fopt !! Indices
8737    INTEGER(i_std)                                :: ilf, ks               !! Indices
8738    REAL(r_std)                                   :: totarea               !! Help variable to compute average SOC
8739    REAL(r_std), ALLOCATABLE, DIMENSION(:)        :: lat_lu, lon_lu        !! Latitudes and longitudes read from input file
8740    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: lat_rel, lon_rel      !! Help variable to read file data and allocate memory
8741    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: mask_lu               !! Help variable to read file data and allocate memory
8742    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:)   :: mask
8743    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: refSOC_1d_file
8744    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)      :: sub_area              !! Help variable to read file data and allocate memory
8745    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:) :: sub_index             !! Help variable to read file data and allocate memory
8746    CHARACTER(LEN=30)                             :: callsign              !! Help variable to read file data and allocate memory
8747    LOGICAL                                       :: ok_interpol           !! Optional return of aggregate_2d
8748    INTEGER                                       :: ALLOC_ERR             !! Help varialbe to count allocation error
8749!_
8750!================================================================================================================================
8751
8752  !! 1. Open file and allocate memory
8753
8754  ! Open file with SOC map
8755
8756    !Config Key   = SOIL_REFSOC_1d_FILE
8757    !Config Desc  = File with climatological soil temperature
8758    !Config If    = READ_REFTEMP
8759    !Config Def   = reftemp.nc
8760    !Config Help  =
8761    !Config Units = [FILE]
8762  filename = 'refSOC_1d.nc'
8763  CALL getin_p('SOIL_REFSOC_1d_FILE',filename)
8764
8765  ! Read data from file
8766  IF (is_root_prc) CALL flininfo(filename, iml, jml, lml, tml, fid)
8767  CALL bcast(iml)
8768  CALL bcast(jml)
8769  CALL bcast(lml)
8770  CALL bcast(tml)
8771
8772  ALLOCATE(lon_lu(iml), STAT=ALLOC_ERR)
8773  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Problem in allocation of variable lon_lu','','')
8774
8775  ALLOCATE(lat_lu(jml), STAT=ALLOC_ERR)
8776  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Problem in allocation of variable lat_lu','','')
8777
8778  ALLOCATE(mask_lu(iml,jml), STAT=ALLOC_ERR)
8779  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Pb in allocation for mask_lu','','')
8780
8781  ALLOCATE(refSOC_1d_file(iml,jml), STAT=ALLOC_ERR)
8782  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Pb in allocation for refSOC_1d_file','','')
8783
8784  IF (is_root_prc) THEN
8785     CALL flinget(fid, 'longitude', iml, 0, 0, 0, 1, 1, lon_lu)
8786     CALL flinget(fid, 'latitude', jml, 0, 0, 0, 1, 1, lat_lu)
8787     CALL flinget(fid, 'mask', iml, jml, 0, 0, 1, 1, mask_lu)
8788     CALL flinget(fid, 'soil_organic_carbon_1d', iml, jml, lml, tml, 1, 1, refSOC_1d_file)
8789
8790     CALL flinclo(fid)
8791  ENDIF
8792
8793  CALL bcast(lon_lu)
8794  CALL bcast(lat_lu)
8795  CALL bcast(mask_lu)
8796  CALL bcast(refSOC_1d_file)
8797
8798  ALLOCATE(lon_rel(iml,jml), STAT=ALLOC_ERR)
8799  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Pb in allocation for lon_rel','','')
8800
8801  ALLOCATE(lat_rel(iml,jml), STAT=ALLOC_ERR)
8802  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Pb in allocation for lat_rel','','')
8803
8804  ALLOCATE(mask(iml,jml), STAT=ALLOC_ERR)
8805  IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Problem in allocation of variable mask','','')
8806
8807  DO jp=1,jml
8808     lon_rel(:,jp) = lon_lu(:)
8809  ENDDO
8810  DO ip=1,iml
8811     lat_rel(ip,:) = lat_lu(:)
8812  ENDDO
8813
8814  mask(:,:) = zero
8815  WHERE (mask_lu(:,:) > zero )
8816     mask(:,:) = un
8817  ENDWHERE
8818
8819  ! Set nbvmax to 200 for interpolation
8820  ! This number is the dimension of the variables in which we store
8821  ! the list of points of the source grid which fit into one grid box of the
8822  ! target.
8823  nbvmax = 16
8824  callsign = 'soil organic carbon 1d'
8825
8826  ! Start interpolation
8827  ok_interpol=.FALSE.
8828  DO WHILE ( .NOT. ok_interpol )
8829     WRITE(numout,*) "Projection arrays for ",callsign," : "
8830     WRITE(numout,*) "nbvmax = ",nbvmax
8831
8832     ALLOCATE(sub_area(nbpt,nbvmax), STAT=ALLOC_ERR)
8833     IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Pb in allocation for sub_area','','')
8834     sub_area(:,:)=zero
8835
8836     ALLOCATE(sub_index(nbpt,nbvmax,2), STAT=ALLOC_ERR)
8837     IF (ALLOC_ERR /= 0) CALL ipslerr_p(3,'read_refSOC_1dfile','Pb in allocation for sub_index','','')
8838     sub_index(:,:,:)=0
8839
8840     CALL aggregate_p(nbpt, lalo, neighbours, resolution, contfrac, &
8841          iml, jml, lon_rel, lat_rel, mask, callsign, &
8842          nbvmax, sub_index, sub_area, ok_interpol)
8843
8844     IF ( .NOT. ok_interpol ) THEN
8845        DEALLOCATE(sub_area)
8846        DEALLOCATE(sub_index)
8847        nbvmax = nbvmax * 2
8848     ENDIF
8849  ENDDO
8850
8851  ! Compute the average
8852  refSOC_1d(:) = zero
8853  DO ib = 1, nbpt
8854     fopt = COUNT(sub_area(ib,:) > zero)
8855     IF ( fopt > 0 ) THEN
8856        totarea = zero
8857        DO ilf = 1, fopt
8858           ip = sub_index(ib,ilf,1)
8859           jp = sub_index(ib,ilf,2)
8860           refSOC_1d(ib) = refSOC_1d(ib) + refSOC_1d_file(ip,jp) * sub_area(ib,ilf)
8861           totarea = totarea + sub_area(ib,ilf)
8862        ENDDO
8863        ! Normalize
8864        refSOC_1d(ib) = refSOC_1d(ib)/totarea
8865     ELSE
8866        ! Set defalut value for points where the interpolation fail
8867        WRITE(numout,*) 'On point ', ib, ' no points were found for interpolation data. Mean value is used.'
8868        WRITE(numout,*) 'Location : ', lalo(ib,2), lalo(ib,1)
8869        refSOC_1d(ib) = 0.
8870     ENDIF
8871  ENDDO
8872
8873  DEALLOCATE (lat_lu)
8874  DEALLOCATE (lat_rel)
8875  DEALLOCATE (lon_lu)
8876  DEALLOCATE (lon_rel)
8877  DEALLOCATE (mask_lu)
8878  DEALLOCATE (mask)
8879  DEALLOCATE (refSOC_1d_file)
8880  DEALLOCATE (sub_area)
8881  DEALLOCATE (sub_index)
8882
8883  END SUBROUTINE read_refSOC_1dfile
8884
8885 
8886END MODULE hydrol
Note: See TracBrowser for help on using the repository browser.