SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
isba.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE isba(HISBA, HPHOTO, OTR_ML, HRUNOFF, HKSAT, HRAIN, HHORT, &
7  hc1dry, hscond, hsnow_isba, hsnowres, hcpsurf, hsoilfrz, &
8  hdifsfcond, tptime, oflood, otemp_arp, oglacier, &
9  omeb, oforc_measure, omeb_litter, omeb_gndres, &
10  ptstep, himplicit_wind, oagri_to_grass, osnowdrift, &
11  osnowdrift_sublim, osnow_abs_zenith,hsnowmetamo,hsnowrad, &
12  pcgmax, pzref, puref, pdircoszw, &
13  pta, pqa, pexna, prhoa, pps, pexns, prr, psr, pzenith, &
14  psca_sw, psw_rad, plw_rad, pvmod, ppew_a_coef, ppew_b_coef,&
15  ppet_a_coef, ppeq_a_coef, ppet_b_coef, ppeq_b_coef, prsmin,&
16  prgl, pgamma, pcv, prunoffd, psoilwght, klayer_hort, &
17  klayer_dun, palbnir_tveg, palbvis_tveg, palbnir_tsoil, &
18  palbvis_tsoil, palb, pwrmax_cf, pveg, plai, pemis, &
19  pz0_with_snow, pz0h_with_snow, pvegtype, pz0eff, &
20  prglcv, pgammacv, prsmincv, &
21  prootfraccv, pwrmax_cfcv, plaiv, &
22  pbslai,plaimin,ph_veg,ppalphan, &
23  pz0g_without_snow, &
24  pz0_mebv,pz0h_mebv,pz0eff_mebv, &
25  pz0_mebn,pz0h_mebn,pz0eff_mebn, &
26  pgndlitter, prunoffb, &
27  pcgsat, pc1sat, pc2ref, pc3, pc4b, pc4ref, pacoef, ppcoef, &
28  ptauice, pwdrain, ptdeep_a, ptdeep_b, pgammat, &
29  ppsn, ppsng, ppsnv, &
30  ppsnv_a, psnowfree_alb_veg, psnowfree_alb_soil, pirrig, &
31  pwatsup, pthreshold, lirrigate, lirriday, ostressdef, pgc, &
32  pf2i, pdmax, pah, pbh, pcsp, pgmes, ppoi, pfzero, pepso, &
33  pgamm, pqdgamm, pqdgmes, pt1gmes, pt2gmes, pamax, pqdamax, &
34  pt1amax, pt2amax, pabc, pd_g, pdzg, pdzdif, kwg_layer, &
35  prootfrac, pwfc, pwwilt, pwsat, pbcoef, pcondsat, &
36  pmpotsat, phcapsoil, pconddry, pcondsld, pd_ice, pksat_ice,&
37  pmuf, pff, pffg, pffv, pffg_nosnow, pffv_nosnow, pffrozen, &
38  pfalb, pfemis, pfflood, ppiflood, piflood, ppflood, &
39  ple_flood, plei_flood, psodelx, plat, plon, ptg, pwg, &
40  pwgi, pcps, plvtt, plstt, pwr, &
41  pwrl,pwrli,pwrvn,ptv, ptl, &
42  presa, panfm, pfsat, &
43  psnowalb, psnowalbvis, psnowalbnir, psnowalbfir, &
44  psnowswe, psnowheat, psnowrho, psnowgran1, &
45  psnowgran2, psnowhist, psnowage, pgrndflux, phpsnow, &
46  psnowhmass, prnsnow, phsnow, pgfluxsnow, &
47  pustarsnow, psrsfc, prrsfc, plesl, pemisnow, pcdsnow, &
48  pchsnow, pts_rad, pts, phv, pqs, psnowtemp, psnowliq, &
49  psnowdz, pcg, pc1, pc2, pwgeq, pct, pch, pcd, pcdn, pri, &
50  phu, phug, pemist, palbt, prs, ple, prn, ph, plei, plegi, &
51  pleg, plev, ples, pler, pletr, pevap, pgflux, prestore, &
52  pustar, pdrain, prunoff, pmelt, pmeltadv, &
53  ptc, pqc, prn_isba, &
54  ph_isba, pleg_isba, plegi_isba, plev_isba, pletr_isba, &
55  pustar_isba, pler_isba, ple_isba, plei_isba, pgflux_isba, &
56  phort, pdrip, prrveg, pac_agg, phu_agg, pfaparc, pfapirc, &
57  pmus, plai_effc, pan, panday, presp_biomass_inst, piacan, &
58  panf, pgpp, pfapar, pfapir, pfapar_bs, pfapir_bs, &
59  pirrig_flux, pdeep_flux, &
60  pswnet_v, pswnet_g, pswnet_n, pswnet_ns, &
61  plwnet_v, plwnet_g, plwnet_n, &
62  plev_v_c, ples_v_c, ph_v_c, ph_g_c, &
63  pletr_g_c, pletr_v_c, pler_g_c, plelitter,plelitteri, &
64  pdriplit,prrlit, pler_v_c, ph_c_a, ph_n_c, &
65  ple_c_a, ple_v_c, ple_g_c, ple_n_c, &
66  pevap_n_c, pevap_g_c, &
67  psr_gn, pmeltcv, pfrzcv, &
68  pswdown_gn, plwdown_gn, &
69  pirrig_gr, ptopqs, pqsb, psubl, &
70  pfwtd, pwtd, psndrift )
71 ! ##########################################################################
72 !
73 !
74 !!**** *ISBA*
75 !!
76 !! PURPOSE
77 !! -------
78 ! Monitor for the calculation of the surface fluxes and of the
79 ! prognostic variables of the surface over natural areas
80 !
81 !!** METHOD
82 !! ------
83 !
84 !! EXTERNAL
85 !! --------
86 !!
87 !! IMPLICIT ARGUMENTS
88 !! ------------------
89 !!
90 !!
91 !! REFERENCE
92 !! ---------
93 !!
94 !! Noilhan and Planton (1989)
95 !!
96 !! AUTHOR
97 !! ------
98 !! S. Belair * Meteo-France *
99 !!
100 !! MODIFICATIONS
101 !! -------------
102 !! Original 10/03/95
103 !! (J.Stein) 25/10/95 add the rain flux computation at the ground
104 !! and the lbc
105 !! (J.Stein) 15/11/95 include the strong slopes cases
106 !! (J.Stein) 06/02/96 bug correction for the precipitation flux writing
107 !! (J.Stein) 20/05/96 set the right IGRID value for the rain rate
108 !! (J.Viviand) 04/02/97 add cold and convective precipitation rate
109 !! (J.Stein) 22/06/97 use the absolute pressure
110 !! (V.Masson) 09/07/97 add directional z0 computations and RESA correction
111 !! (V.Masson) 13/02/98 simplify the routine: only vegetation computation
112 !! are now made here.
113 !! (A.Boone) 05/10/98 add: Boone et al. (1999) 3 soil-water Layers version
114 !! (V.Masson) Dumenil and Todini (1992) runoff
115 !! Calvet (1998) biomass and CO2 assimilation
116 !! Calvet (1998) LAI evolution
117 !! (A.Boone) 03/15/99 Soil ice scheme: modify CG, C1, C2, WSAT, WFC, WILT,
118 !! LEG (add soil ice sublimation); Can modify TS and T2.
119 !! New variables WGI1, WGI2
120 !! (A.Boone) 18/01/00 ISBA-ES (3-layer explicit snow scheme option)
121 !! (Boone and Etchevers 2000)
122 !! New variable PSNOWHEAT
123 !! (V. Masson) 01/2004 wet leaves fraction computed in separate routine
124 !! all vegetation stress (ISBA, AGS, AST) routines
125 !! called at the same point
126 !! (P. LeMoigne) 03/2004 computation of QSAT
127 !! (P. LeMoigne) 10/2004 halstead coefficient as diagnostic for isba
128 !! (A. Bogatchev)09/2005 EBA snow option
129 !! (P. LeMoigne) 02/2006 z0h and snow
130 !! (B. Decharme) 05/2008 Add floodplains scheme
131 !! (R. Hamdi) 01/09 Cp and L are not constants (As in ALADIN)
132 !! (A.L. Gibelin) 03/2009 : Add respiration diagnostics
133 !! A.L. Gibelin 06/09 : move calculations of CO2 fluxes
134 !! A.L. Gibelin 07/2009 : Suppress PPST and PPSTF as outputs
135 !! (A. Boone) 11/2009 Add local variable: total soil temperature change (before
136 !! phase change) for use by LWT scheme in ISBA-DIF.
137 !! (A. Boone) 03/2010 Add local variable: delta functions for LEG and LEGI
138 !! to numerically correct for when they should be
139 !! zero when hug(i) Qsat < Qa and Qsat > Qa
140 !! (A. Carrer) 04/2011 : new radiative transfert (AGS)
141 !! (B. Decharme) 09/2012 Bug : Save snow albedo values at beginning
142 !! of time step for total albedo calculation
143 !! Bug : flood fraction in COTWORES
144 !! new wind implicitation
145 !! Irrigation rate diag
146 !! (C. de Munck) 03/2013 Specified irrigation for ground
147 !! (B. Decharme) 04/2013 Bug : Wrong radiative temperature
148 !! DIF lateral subsurface drainage
149 !! Sublimation diag flux
150 !! Qs for 3l or crocus (needed for coupling with atm)
151 !! water table / surface coupling
152 !! Routines drag, e_budget and isba_fluxes now in isba_ceb
153 !! (A. Boone & P. Samuelsson) (10/2014) Added MEB v1
154 !! (P. LeMoigne) 12/2014 EBA scheme update
155 !! (A. Boone) 02/2015 Consider spectral band dependence of snow for OTR_ML radiation option
156 !! B. Decharme 01/16 : Bug with flood budget
157 !-------------------------------------------------------------------------------
158 !
159 !* 0. DECLARATIONS
160 ! ------------
161 USE modd_co2v_par, ONLY : xmc, xmco2, xpcco2
162 USE modd_surf_par, ONLY : xundef
163 !
164 USE modd_csts, ONLY : xtt
165 USE modd_co2v_par, ONLY : xmc, xmco2, xpcco2
166 USE modd_surf_par, ONLY : xundef
167 USE modd_data_cover_par, ONLY : nvt_snow
168 USE modd_meb_par, ONLY : xsw_wght_vis, xsw_wght_nir
169 !
170 USE modd_type_date_surf, ONLY : date_time
171 !
172 USE modi_soil
173 USE modi_soildif
174 USE modi_soilstress
175 USE modi_wet_leaves_frac
176 USE modi_veg
177 USE modi_snow3l_isba
178 USE modi_hydro
179 USE modi_isba_snow_agr
180 !
181 USE modi_radiative_transfert
182 USE modi_cotwores
183 !
184 !
185 USE modi_isba_ceb
186 USE modi_isba_meb
187 !
188 USE mode_thermos
189 !
190 USE yomhook ,ONLY : lhook, dr_hook
191 USE parkind1 ,ONLY : jprb
192 !
193 IMPLICIT NONE
194 !
195 !* 0.1 declarations of arguments
196 ! -------------------------
197 !
198 !
199 !* general variables
200 ! -----------------
201 !
202  CHARACTER(LEN=*), INTENT(IN) :: hisba ! type of ISBA version:
203 ! ! '2-L' (default)
204 ! ! '3-L'
205 ! ! 'DIF'
206  CHARACTER(LEN=*), INTENT(IN) :: hphoto ! Kind of photosynthesis
207 ! ! 'NON'
208 ! ! 'AGS'
209 ! ! 'LAI'
210 ! ! 'AST'
211 ! ! 'LST'
212 LOGICAL, INTENT(IN) :: otr_ml ! new TR
213  CHARACTER(LEN=*), INTENT(IN) :: hrunoff ! surface runoff formulation
214 ! ! 'WSAT'
215 ! ! 'DT92'
216 ! ! 'SGH ' Topmodel
217  CHARACTER(LEN=*), INTENT(IN) :: hksat ! soil hydraulic profil option
218 ! ! 'DEF' = ISBA homogenous soil
219 ! ! 'SGH' = ksat exponential decay
220  CHARACTER(LEN=*), INTENT(IN) :: hrain ! Rainfall spatial distribution
221  ! 'DEF' = No rainfall spatial distribution
222  ! 'SGH' = Rainfall exponential spatial distribution
223  CHARACTER(LEN=*), INTENT(IN) :: hhort ! Horton runoff
224  ! 'DEF' = no Horton runoff
225  ! 'SGH' = Horton runoff
226  CHARACTER(LEN=*), INTENT(IN) :: hc1dry ! C1 for dry soil formulation
227 ! ! 'DEF' Default: Giard and Bazile
228 ! ! 'GB93' Giordani 1993, Braud 1993
229 ! ! (discontinuous at WILT)
230  CHARACTER(LEN=*), INTENT(IN) :: hscond ! Thermal conductivity
231 ! ! 'NP89' = NP89 implicit method
232 ! ! 'PL98' = Peters-Lidard et al. 1998 used
233 ! ! for explicit computation of CG
234  CHARACTER(LEN=*), INTENT(IN) :: hsnow_isba ! 'DEF' = Default F-R snow scheme
235 ! ! (Douville et al. 1995)
236 ! ! '3-L' = 3-L snow scheme (option)
237 ! ! (Boone and Etchevers 2000)
238  CHARACTER(LEN=*), INTENT(IN) :: hsnowres ! 'DEF' = Default: Louis (ISBA)
239 ! ! 'RIL' = CROCUS (Martin) method
240 ! ! ISBA-SNOW3L turbulant exchange option
241  CHARACTER(LEN=*), INTENT(IN) :: hcpsurf ! Specific heat
242 ! ! 'DRY' = dry Cp
243 ! ! 'HUM' = humid Cp fct of qs
244  CHARACTER(LEN=*), INTENT(IN) :: hsoilfrz ! soil freezing-physics option
245 ! ! 'DEF' Default (Boone et al. 2000; Giard and Bazile 2000)
246 ! ! 'LWT' phase changes as above, but relation between unfrozen
247 ! water and temperature considered
248  CHARACTER(LEN=*), INTENT(IN) :: hdifsfcond ! NOTE: Only used when HISBA = DIF
249 ! ! MLCH' = include the insulating effect of leaf
250 ! ! litter/mulch on the surface thermal cond.
251 ! ! 'DEF' = no mulch effect
252 !
253 TYPE(date_time), INTENT(IN) :: tptime ! current date and time
254 !
255 LOGICAL, INTENT(IN) :: oflood ! Activation of the flooding scheme
256 LOGICAL, INTENT(IN) :: otemp_arp ! True = time-varying force-restore soil temperature (as in ARPEGE)
257  ! False = No time-varying force-restore soil temperature (Default)
258 LOGICAL, INTENT(IN) :: oglacier ! True = Over permanent snow and ice,
259 ! initialise WGI=WSAT,
260 ! Hsnow>=10m and allow 0.8<SNOALB<0.85
261  ! False = No specific treatment
262 LOGICAL, INTENT(IN) :: omeb ! True = patch with multi-energy balance
263 ! ! False = patch with classical ISBA
264 LOGICAL, INTENT(IN) :: omeb_litter ! explicit litter layer (MEB option)
265 LOGICAL, INTENT(IN) :: omeb_gndres ! ground resistance (MEB option)
266 LOGICAL, INTENT(IN) :: oforc_measure
267 !
268  CHARACTER(LEN=*), INTENT(IN) :: himplicit_wind ! wind implicitation option
269 ! ! 'OLD' = direct
270 ! ! 'NEW' = Taylor serie, order 1
271 !
272 LOGICAL, INTENT(IN) :: oagri_to_grass
273 LOGICAL, INTENT(IN) :: osnowdrift ! activate snowdrift
274 LOGICAL, INTENT(IN) :: osnowdrift_sublim ! activate sublimation during drift
275 LOGICAL, INTENT(IN) :: osnow_abs_zenith ! activate parametrization of solar absorption for polar regions
276  CHARACTER(3), INTENT(IN) :: hsnowmetamo
277  !-----------------------
278  ! Crocus metamorphism scheme
279  ! HSNOWMETAMO=B92 Brun et al 1992
280  ! HSNOWMETAMO=C13 Carmagnola et al 2014
281  ! HSNOWMETAMO=T07 Taillandier et al 2007
282  ! HSNOWMETAMO=F06 Flanner et al 2006
283  CHARACTER(3), INTENT(IN) :: hsnowrad
284  !-----------------------
285  ! Crocus radiative transfer scheme
286  ! HSNOWRAD=B92 Brun et al 1992
287  ! HSNOWRAD=TAR TARTES (Libois et al 2013)
288  ! HSNOWRAD=TA1 TARTES with constant impurities
289  ! HSNOWRAD=TA2 TARTES with constant impurities as function of ageing
290 !
291 REAL, INTENT(IN) :: ptstep ! timestep of the integration
292 !
293 REAL, INTENT(IN) :: pcgmax ! maximum soil heat capacity
294 !
295 REAL, DIMENSION(:), INTENT(IN) :: pzref ! normal distance of the first
296 ! ! atmospheric level to the
297 ! ! orography
298 REAL, DIMENSION(:), INTENT(IN) :: puref ! reference height of the wind
299 ! ! NOTE this is different from ZZREF
300 ! ! ONLY in stand-alone/forced mode,
301 ! ! NOT when coupled to a model (MesoNH)
302 REAL, DIMENSION(:), INTENT(IN) :: pdircoszw ! Director Cosinus along z
303 ! ! directions at surface w-point
304 !
305 REAL, DIMENSION(:), INTENT(IN) :: plat ! Latitude
306 REAL, DIMENSION(:), INTENT(IN) :: plon ! Longitude
307 !
308 !* atmospheric variables
309 ! ---------------------
310 !
311 ! suffix 'A' stands for atmospheric variable at first model level
312 ! suffix 'S' stands for atmospheric variable at ground level
313 !
314 REAL, DIMENSION(:), INTENT(IN) :: pta ! Temperature
315 REAL, DIMENSION(:), INTENT(IN) :: pqa ! specific humidity
316 REAL, DIMENSION(:), INTENT(IN) :: pexna ! Exner function
317 REAL, DIMENSION(:), INTENT(IN) :: prhoa ! air density
318 !
319 REAL, DIMENSION(:), INTENT(IN) :: pps ! Pressure
320 REAL, DIMENSION(:), INTENT(IN) :: pexns ! Exner function
321 !
322 REAL, DIMENSION(:), INTENT(IN) :: prr ! Rain rate (in kg/m2/s)
323 REAL, DIMENSION(:), INTENT(IN) :: psr ! Snow rate (in kg/m2/s)
324 !
325 REAL, DIMENSION(:), INTENT(IN) :: pzenith ! solar zenith angle
326 REAL, DIMENSION(:), INTENT(IN) :: psw_rad ! solar incoming radiation
327 REAL, DIMENSION(:), INTENT(IN) :: psca_sw ! solar diffuse incoming radiation
328 REAL, DIMENSION(:), INTENT(IN) :: plw_rad ! thermal incoming radiation
329 !
330 REAL, DIMENSION(:), INTENT(IN) :: pvmod ! modulus of the wind
331 ! ! parallel to the orography
332 !
333 ! implicit coupling coefficients:
334 !
335 REAL, DIMENSION(:), INTENT(IN) :: ppew_a_coef, ppew_b_coef, &
336  ppet_a_coef, ppeq_a_coef, &
337  ppet_b_coef, ppeq_b_coef
338 ! PPEW_A_COEF ! A-wind coefficient
339 ! PPEW_B_COEF ! B-wind coefficient
340 ! PPET_A_COEF ! A-air temperature coefficient
341 ! PPET_B_COEF ! B-air temperature coefficient
342 ! PPEQ_A_COEF ! A-air specific humidity coefficient
343 ! PPEQ_B_COEF ! B-air specific humidity coefficient
344 !
345 !* vegetation parameters
346 ! ---------------------
347 !
348 REAL, DIMENSION(:), INTENT(IN) :: prsmin ! minimum stomatal resistance
349 REAL, DIMENSION(:), INTENT(IN) :: prgl ! maximum solar radiation
350 ! ! usable in photosynthesis
351 REAL, DIMENSION(:), INTENT(IN) :: pgamma ! coefficient for the calculation
352 ! ! of the surface stomatal
353 ! ! resistance
354 REAL, DIMENSION(:), INTENT(IN) :: pcv ! 2*sqrt(pi/day)/sqrt(Cveg*hveg)
355 ! ! where Cveg and hveg are the
356 ! ! heat capacity and conductivity
357 ! ! of the vegetation
358 REAL, DIMENSION(:), INTENT(IN) :: prunoffd ! depth over which sub-grid runoff computed (m)
359 REAL, DIMENSION(:,:),INTENT(IN) :: psoilwght ! ISBA-DIF: weights for vertical
360 ! ! integration of soil water and properties
361 INTEGER, INTENT(IN) :: klayer_hort! DIF optimization
362 INTEGER, INTENT(IN) :: klayer_dun ! DIF optimization
363 !
364 REAL, DIMENSION(:), INTENT(IN) :: palbnir_tveg ! tot albedo of vegetation in NIR (needed for LM_TR)
365 REAL, DIMENSION(:), INTENT(IN) :: palbvis_tveg ! tot albedo of vegetation in VIS
366 REAL, DIMENSION(:), INTENT(IN) :: palbnir_tsoil ! tot albedo of bare soil in NIR
367 REAL, DIMENSION(:), INTENT(IN) :: palbvis_tsoil ! tot albedo of bare soil in VIS
368 REAL, DIMENSION(:), INTENT(IN) :: palb ! albedo of vegetation
369 REAL, DIMENSION(:), INTENT(IN) :: pwrmax_cf ! coefficient for maximum water interception
370 ! ! storage capacity on the vegetation (-)
371 REAL, DIMENSION(:), INTENT(IN) :: pveg ! fraction of vegetation of the
372 ! ! mesh covered by natural or
373 ! ! agricultural areas
374 ! ! 1-PVEG --> bare soil
375 REAL, DIMENSION(:), INTENT(IN) :: pgndlitter ! litter thickness, MEB option (m)
376 REAL, DIMENSION(:), INTENT(IN) :: plai ! LAI as a function of time:
377 ! ! as a function of growth,
378 ! ! decay, assimilation.
379 REAL, DIMENSION(:), INTENT(IN) :: pemis ! emissivity of natural surfaces
380 ! ! (without prognostic snow)
381 REAL, DIMENSION(:), INTENT(IN) :: pz0_with_snow ! roughness length for momentum
382 ! ! (with snow taken into account)
383 REAL, DIMENSION(:), INTENT(IN) :: pz0h_with_snow ! roughness length for heat
384 ! ! (with snow taken into account)
385 !
386 !
387 ! For multi-energy balance
388 REAL, DIMENSION(:,:), INTENT(IN) :: prootfraccv
389 REAL, DIMENSION(:), INTENT(IN) :: prglcv
390 REAL, DIMENSION(:), INTENT(IN) :: pgammacv
391 REAL, DIMENSION(:), INTENT(IN) :: prsmincv
392 REAL, DIMENSION(:), INTENT(IN) :: pwrmax_cfcv
393 REAL, DIMENSION(:), INTENT(IN) :: plaiv ! explicit canopy overstory LAI..."PLAI" is the composite surface LAI
394 ! ! (when MEB is ON, "PLAI" corresponds to understory LAI (possibly zero),
395 ! ! while "PLAV" is the overstory LAI)
396 REAL, DIMENSION(:), INTENT(IN) :: ph_veg ! height of vegetation
397 REAL, DIMENSION(:), INTENT(IN) :: pbslai ! ratio of biomass to LAI (kg m-2)
398 REAL, DIMENSION(:), INTENT(IN) :: plaimin ! Minimum LAI (m2 m-2)
399 REAL, DIMENSION(:), INTENT(IN) :: ppalphan ! snow/canopy transition coefficient
400 REAL, DIMENSION(:), INTENT(IN) :: pz0g_without_snow ! roughness length for momentum at snow-free canopy floor
401 REAL, DIMENSION(:), INTENT(IN) :: pz0_mebv ! roughness length for momentum over MEB vegetation part of patch
402 REAL, DIMENSION(:), INTENT(IN) :: pz0h_mebv ! roughness length for heat over MEB vegetation part of path
403 REAL, DIMENSION(:), INTENT(IN) :: pz0eff_mebv ! roughness length for momentum over MEB vegetation part of patch
404 REAL, DIMENSION(:), INTENT(IN) :: pz0_mebn ! roughness length for momentum over MEB snow part of patch
405 REAL, DIMENSION(:), INTENT(IN) :: pz0h_mebn ! roughness length for heat over MEB snow part of path
406 REAL, DIMENSION(:), INTENT(IN) :: pz0eff_mebn ! roughness length for momentum over MEB snow part of patch
407 !
408 !* ISBA-Ags (with LAI evolution) parameters
409 ! ----------------------------------------
410 !
411 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! fraction of each vegetation
412 !
413 !* subgrid-scale orography parameters
414 ! ----------------------------------
415 !
416 REAL, DIMENSION(:), INTENT(IN) :: pz0eff ! roughness length for momentum
417 !
418 REAL, DIMENSION(:), INTENT(IN) :: prunoffb ! slope of the runoff curve
419 !
420 !* soil parameters
421 ! ---------------
422 !
423 REAL, DIMENSION(:), INTENT(IN) :: pcgsat ! thermal coefficient at
424 ! ! saturation
425 REAL, DIMENSION(:), INTENT(IN) :: pc1sat ! C1 coefficient at saturation
426 REAL, DIMENSION(:), INTENT(IN) :: pc2ref ! reference value of C2
427 REAL, DIMENSION(:,:), INTENT(IN):: pc3 ! C3 coefficient
428 REAL, DIMENSION(:), INTENT(IN) :: pc4b ! fiiting soil paramater for vertical diffusion (C4)
429 REAL, DIMENSION(:), INTENT(IN) :: pc4ref ! "
430 REAL, DIMENSION(:), INTENT(IN) :: pacoef ! a and p coefficients for
431 REAL, DIMENSION(:), INTENT(IN) :: ppcoef ! the wgeq calculations.
432 !
433 REAL, DIMENSION(:), INTENT(IN) :: ptauice ! characteristic time scale for phase change
434 ! ! within the soil
435 !
436 REAL, DIMENSION(:), INTENT(IN) :: pwdrain ! minimum Wg for drainage (m3/m3)
437 !
438 !
439 REAL, DIMENSION(:), INTENT(IN) :: ptdeep_a, ptdeep_b
440  ! Deep soil temperature (prescribed)
441 ! PTDEEP_A = Deep soil temperature
442 ! coefficient depending on flux
443 ! PTDEEP_B = Deep soil temperature (prescribed)
444 ! which models heating/cooling from
445 ! below the diurnal wave penetration
446 ! (surface temperature) depth. If it
447 ! is FLAGGED as undefined, then the zero
448 ! flux lower BC is applied.
449 ! Tdeep = PTDEEP_B + PTDEEP_A * PDEEP_FLUX
450 ! (with PDEEP_FLUX in W/m2)
451 REAL, DIMENSION(:), INTENT(IN) :: pgammat ! Deep soil heat transfer coefficient:
452 ! ! assuming homogeneous soil so that
453 ! ! this can be prescribed in units of
454 ! ! (1/days): associated time scale with
455 ! ! PTDEEP.
456 !
457 REAL, DIMENSION(:), INTENT(IN) :: ppsn ! fraction of the grid covered
458 ! ! by snow
459 REAL, DIMENSION(:), INTENT(IN) :: ppsng ! fraction of the the bare
460 ! ! ground covered by snow
461 REAL, DIMENSION(:), INTENT(IN) :: ppsnv ! fraction of the the veg.
462 ! ! covered by snow
463 REAL, DIMENSION(:), INTENT(IN) :: ppsnv_a ! snow free albedo of vegetation
464  ! for EBA
465 REAL, DIMENSION(:), INTENT(IN) :: psnowfree_alb_veg ! snow free albedo of vegetation
466 REAL, DIMENSION(:), INTENT(IN) :: psnowfree_alb_soil ! snow free albedo of soil
467 !
468 REAL ,DIMENSION(:),INTENT(IN) :: pirrig
469 REAL ,DIMENSION(:),INTENT(IN) :: pwatsup
470 REAL ,DIMENSION(:),INTENT(IN) :: pthreshold
471 LOGICAL,DIMENSION(:),INTENT(IN) :: lirrigate
472 LOGICAL,DIMENSION(:),INTENT(INOUT) :: lirriday
473 REAL ,DIMENSION(:),INTENT(IN) :: pirrig_gr ! ground irrigation rate (kg/m2/s)
474 !
475 !* ISBA-Ags parameters
476 ! -------------------
477 !
478 LOGICAL, DIMENSION(:), INTENT(IN) :: ostressdef ! vegetation response type to water
479 ! ! stress (true:defensive false:offensive)
480 REAL, DIMENSION(:), INTENT(IN) :: pgc ! cuticular conductance (m s-1)
481 REAL, DIMENSION(:), INTENT(IN) :: pf2i ! critical normilized soil water
482 ! ! content for stress parameterisation
483 REAL, DIMENSION(:), INTENT(IN) :: pdmax ! maximum air saturation deficit
484 ! ! tolerate by vegetation
485 REAL, DIMENSION(:), INTENT(IN) :: pah,pbh ! coefficients for herbaceous water stress
486 ! ! response (offensive or defensive)
487 !
488 REAL, DIMENSION(:), INTENT(IN) :: pcsp ! atmospheric CO2 concentration
489 ! [ppmm]=[kg CO2 / kg air]
490 REAL, DIMENSION(:), INTENT(IN) :: pgmes ! mesophyll conductance (m s-1)
491 !
492 REAL, DIMENSION(:), INTENT(IN) :: ppoi ! Gaussian weights (as above)
493 !
494 REAL, DIMENSION(:), INTENT(IN) :: pfzero ! ideal value of F, no photo-
495 ! ! respiration or saturation deficit
496 REAL, DIMENSION(:), INTENT(IN) :: pepso ! maximum initial quantum use
497 ! ! efficiency (mg J-1 PAR)
498 REAL, DIMENSION(:), INTENT(IN) :: pgamm ! CO2 conpensation concentration (ppmv)
499 REAL, DIMENSION(:), INTENT(IN) :: pqdgamm ! Log of Q10 function for CO2 conpensation
500 ! ! concentration
501 REAL, DIMENSION(:), INTENT(IN) :: pqdgmes ! Log of Q10 function for mesophyll conductance
502 REAL, DIMENSION(:), INTENT(IN) :: pt1gmes ! reference temperature for computing
503 ! ! compensation concentration function for
504 ! ! mesophyll conductance: minimum
505 ! ! temperature
506 REAL, DIMENSION(:), INTENT(IN) :: pt2gmes ! reference temperature for computing
507 ! ! compensation concentration function for
508 ! ! mesophyll conductance: maximum
509 ! ! temperature
510 REAL, DIMENSION(:), INTENT(IN) :: pamax ! leaf photosynthetic capacity (kgCO2 m-2 s-1)
511 REAL, DIMENSION(:), INTENT(IN) :: pqdamax ! Log of Q10 function for leaf photosynthetic capacity
512 REAL, DIMENSION(:), INTENT(IN) :: pt1amax ! reference temperature for computing
513 ! ! compensation concentration function for leaf
514 ! ! photosynthetic capacity: minimum
515 ! ! temperature
516 REAL, DIMENSION(:), INTENT(IN) :: pt2amax ! reference temperature for computing
517 ! ! compensation concentration function for leaf
518 ! ! photosynthetic capacity: maximum
519 ! ! temperature
520 REAL, DIMENSION(:), INTENT(INOUT) :: pabc ! abscissa needed for integration
521 ! ! of net assimilation and stomatal
522 ! ! conductance over canopy depth
523 !
524 !* Multi-energy balance variables:
525 ! ---------------------------------
526 !
527 ! diagnostic variables
528 !
529 REAL, DIMENSION(:), INTENT(INOUT) :: ptc ! Canopy air temperature
530 REAL, DIMENSION(:), INTENT(INOUT) :: pqc ! Canopy air specific humidity
531 !
532 ! Prognostic variables:
533 !
534 !* ISBA-DF variables/parameters:
535 ! ------------------------------
536 ! Parameters:
537 !
538 REAL, DIMENSION(:,:), INTENT(IN) :: pd_g ! Depth of Bottom of Soil layers (m)
539 REAL, DIMENSION(:,:), INTENT(IN) :: pdzg ! soil layers thicknesses (DIF option) (m)
540 REAL, DIMENSION(:,:), INTENT(IN) :: pdzdif ! distance between consecuative layer mid-points (DIF option) (m)
541 INTEGER, DIMENSION(:),INTENT(IN) :: kwg_layer ! Number of soil moisture layers (DIF option)
542 REAL, DIMENSION(:,:), INTENT(IN) :: prootfrac ! root fraction (-)
543 REAL, DIMENSION(:,:), INTENT(IN) :: pwfc ! field capacity profile (m3/m3)
544 REAL, DIMENSION(:,:), INTENT(IN) :: pwwilt ! wilting point profile (m3/m3)
545 REAL, DIMENSION(:,:), INTENT(IN) :: pwsat ! porosity profile (m3/m3)
546 REAL, DIMENSION(:,:), INTENT(IN) :: pbcoef ! soil water CH78 b-parameter (-)
547 REAL, DIMENSION(:,:), INTENT(IN) :: pcondsat ! hydraulic conductivity at saturation (m/s)
548 REAL, DIMENSION(:,:), INTENT(IN) :: pmpotsat ! matric potential at saturation (m)
549 REAL, DIMENSION(:,:), INTENT(IN) :: phcapsoil ! soil heat capacity [J/(K m3)]
550 REAL, DIMENSION(:,:), INTENT(IN) :: pconddry ! soil dry thermal conductivity [W/(m K)]
551 REAL, DIMENSION(:,:), INTENT(IN) :: pcondsld ! soil solids thermal conductivity [W/(m K)]
552 !
553 REAL, DIMENSION(:), INTENT(IN) :: pd_ice !depth of the soil column for the calculation
554 ! of the frozen soil fraction (m)
555 REAL, DIMENSION(:), INTENT(IN) :: pksat_ice !hydraulic conductivity at saturation (m/s)
556 !
557 REAL, DIMENSION(:), INTENT(IN) :: pmuf !fraction of the grid cell reached by the rainfall
558 !
559 REAL, DIMENSION(:), INTENT(IN) :: pff !Floodplain fraction at the surface
560 REAL, DIMENSION(:), INTENT(IN) :: pffg !Floodplain fraction over the ground
561 REAL, DIMENSION(:), INTENT(IN) :: pffv !Floodplain fraction over vegetation
562 REAL, DIMENSION(:), INTENT(IN) :: pffg_nosnow ! Without snow (ES)
563 REAL, DIMENSION(:), INTENT(IN) :: pffv_nosnow ! Without snow (ES)
564 REAL, DIMENSION(:), INTENT(IN) :: pffrozen !Fraction of frozen flood
565 REAL, DIMENSION(:), INTENT(IN) :: pfalb !Floodplain albedo
566 REAL, DIMENSION(:), INTENT(IN) :: pfemis !Floodplain emis
567 REAL, DIMENSION(:), INTENT(IN) :: pfflood !Efective floodplain fraction
568 REAL, DIMENSION(:), INTENT(IN) :: ppiflood !Floodplains potential infiltration [kg/m²/s]
569 REAL, DIMENSION(:), INTENT(INOUT):: piflood !Floodplains infiltration [kg/m²/s]
570 REAL, DIMENSION(:), INTENT(INOUT):: ppflood !Floodplains direct precipitation [kg/m²/s]
571 REAL, DIMENSION(:), INTENT(INOUT):: ple_flood, plei_flood !Floodplains latent heat flux [W/m²]
572 !
573 REAL, DIMENSION(:), INTENT(IN) :: psodelx ! Pulsation for each layer (Only used if LTEMP_ARP=True)
574 !
575 REAL, DIMENSION(:,:), INTENT(IN) :: ptopqs !Topmodel (HRUNOFF=SGH) subsurface flow by layer for DIF (m/s)
576 REAL, DIMENSION(:), INTENT(OUT) :: pqsb !Topmodel (HRUNOFF=SGH) Lateral subsurface flow for DIF [kg/m²/s]
577 !
578 REAL, DIMENSION(:), INTENT(IN) :: pfwtd ! grid-cell fraction of water table rises
579 REAL, DIMENSION(:), INTENT(IN) :: pwtd ! water table depth from hydrological model (m)
580 ! ! negative below the soil surface
581 !
582 !* prognostic variables
583 ! --------------------
584 !
585 REAL, DIMENSION(:,:), INTENT(INOUT) :: ptg, pwg, pwgi
586 ! PTG ! soil layer average temperatures (K)
587 ! PWG ! soil liquid volumetric water content (m3/m3)
588 ! PWGI ! soil frozen volumetric water content (m3/m3)
589 !
590 REAL, DIMENSION(:), INTENT(INOUT) :: pcps, plvtt, plstt
591 !
592 REAL, DIMENSION(:), INTENT(INOUT) :: pwr ! liquid water retained on the
593 ! ! foliage of the comosite vegetation
594 ! ! canopy (understory in the case of MEB)
595 ! For multi-energy balance
596 REAL, DIMENSION(:), INTENT(INOUT) :: pwrl
597 ! PWRL = litter reservoir for water
598 REAL, DIMENSION(:), INTENT(INOUT) :: pwrli
599 ! PWRLI = litter reservoir for ice
600 !
601 REAL, DIMENSION(:), INTENT(INOUT) :: pwrvn, ptv, ptl
602 ! PWRVN = snow retained on the foliage
603 ! of the canopy vegetation
604 ! PTV = canopy vegetation temperature
605 ! PTL = litter temperature
606 !
607 REAL, DIMENSION(:), INTENT(INOUT) :: presa ! aerodynamic resistance
608 !
609 REAL, DIMENSION(:), INTENT(INOUT) :: panfm ! maximum leaf assimilation
610 !
611 REAL, DIMENSION(:), INTENT(INOUT) :: pfsat ! Topmodel saturated fraction
612 !
613 !* ISBA-SNOW3L variables/parameters:
614 ! ---------------------------------
615 !
616 ! Prognostic variables:
617 !
618 REAL, DIMENSION(:), INTENT(INOUT) :: psnowalb ! Snow albedo
619 REAL, DIMENSION(:), INTENT(INOUT) :: psnowalbvis ! Snow VIS albedo
620 REAL, DIMENSION(:), INTENT(INOUT) :: psnowalbnir ! Snow NIR albedo
621 REAL, DIMENSION(:), INTENT(INOUT) :: psnowalbfir ! Snow FIR albedo
622 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowswe ! Snow model layer liquid water equivalent or SWE (kg m-2)
623 ! ! NOTE for 'DEF' snow option, only uppermost element
624 ! ! of this array is non-zero (as it's a one layer scheme)
625 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowheat ! Snow layer heat content (J/m3)
626 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowrho ! Snow layer average density (kg/m3)
627 ! ! NOTE for 'DEF' snow option, only uppermost element
628 ! ! of this array is used (as it's a one layer scheme)
629 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowgran1 ! Snow grain parameter 1
630 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowgran2 ! Snow grain parameter 2
631 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowhist ! Snow grain historical parameter
632 REAL, DIMENSION(:,:), INTENT(INOUT) :: psnowage ! Snow grain age
633 ! NOTE : methamorphism is only activated if the flag
634 ! OSNOW_METAMO=TRUE
635 !
636 ! Diagnostics:
637 !
638 REAL, DIMENSION(:), INTENT(OUT) :: pgrndflux ! snow/soil-biomass interface flux (W/m2)
639 !
640 REAL, DIMENSION(:), INTENT(OUT) :: phpsnow ! heat release from rainfall (W/m2)
641 REAL, DIMENSION(:), INTENT(OUT) :: psnowhmass ! snow heat content change from mass changes (J/m2)
642 REAL, DIMENSION(:), INTENT(OUT) :: prnsnow ! net radiative flux from snow (W/m2)
643 REAL, DIMENSION(:), INTENT(OUT) :: phsnow ! sensible heat flux from snow (W/m2)
644 REAL, DIMENSION(:), INTENT(OUT) :: pgfluxsnow ! net heat flux from snow (W/m2)
645 REAL, DIMENSION(:), INTENT(OUT) :: pustarsnow ! friction velocity
646 REAL, DIMENSION(:), INTENT(OUT) :: psrsfc ! Snow rate falling outside of snow
647 ! covered grid area [kg/(m2 s)]
648 REAL, DIMENSION(:), INTENT(OUT) :: prrsfc ! Rain rate falling outside of snow and flood
649 ! covered grid area [kg/(m2 s)]
650 REAL, DIMENSION(:), INTENT(OUT) :: plesl ! Evaporation (liquid) from wet snow (W/m2)
651 REAL, DIMENSION(:), INTENT(OUT) :: pemisnow ! snow surface emissivity
652 REAL, DIMENSION(:), INTENT(OUT) :: pcdsnow ! drag coefficient for momentum over snow
653 REAL, DIMENSION(:), INTENT(OUT) :: pchsnow ! drag coefficient for heat over snow
654 REAL, DIMENSION(:), INTENT(OUT) :: pts_rad ! effective radiative temperature
655 ! of the natural surface (K)
656 REAL, DIMENSION(:), INTENT(OUT) :: pts ! effective surface temperature (K)
657 REAL, DIMENSION(:), INTENT(OUT) :: phv ! Halstead coefficient
658 REAL, DIMENSION(:,:), INTENT(OUT) :: psnowtemp ! snow layer temperatures (K)
659 REAL, DIMENSION(:,:), INTENT(OUT) :: psnowliq ! snow layer liquid water content (m)
660 REAL, DIMENSION(:,:), INTENT(OUT) :: psnowdz ! snow layer thickness (m)
661 !
662 !
663 !* output soil parameters
664 ! ----------------------
665 !
666 REAL, DIMENSION(:), INTENT(OUT) :: pcg ! heat capacity of the ground
667 REAL, DIMENSION(:), INTENT(OUT) :: pc1 ! coefficients for the moisure
668 REAL, DIMENSION(:), INTENT(OUT) :: pc2 ! equation.
669 REAL, DIMENSION(:), INTENT(OUT) :: pwgeq ! equilibrium volumetric water
670 ! ! content
671 REAL, DIMENSION(:), INTENT(OUT) :: pct ! area-averaged heat capacity
672 !
673 !
674 !* diagnostic variables
675 ! --------------------
676 !
677 REAL, DIMENSION(:), INTENT(OUT) :: pch ! grid-area drag coefficient for heat
678 REAL, DIMENSION(:), INTENT(OUT) :: pcd ! grid-area drag coefficient for momentum
679 REAL, DIMENSION(:), INTENT(OUT) :: pcdn ! grid-area neutral drag coefficient for momentum
680 REAL, DIMENSION(:), INTENT(OUT) :: pri ! grid-area Richardson number
681 REAL, DIMENSION(:), INTENT(OUT) :: pqs ! grid-area surface humidity (kg/kg)
682 REAL, DIMENSION(:), INTENT(OUT) :: phu ! grid-area humidity of the soil
683 REAL, DIMENSION(:), INTENT(OUT) :: pemist ! grid-area surface emissivity
684 REAL, DIMENSION(:), INTENT(OUT) :: palbt ! grid-area surface albedo
685 !
686 REAL, DIMENSION(:), INTENT(OUT) :: phug ! ground relative humidity
687 REAL, DIMENSION(:), INTENT(OUT) :: prs ! surface stomatal resistance
688 !
689 !* surface fluxes
690 ! --------------
691 !
692 REAL, DIMENSION(:), INTENT(INOUT) :: ple ! total latent heat flux
693 REAL, DIMENSION(:), INTENT(OUT) :: prn ! net radiation
694 REAL, DIMENSION(:), INTENT(OUT) :: ph ! sensible heat flux
695 REAL, DIMENSION(:), INTENT(OUT) :: plei ! sublimation latent heat flux
696 REAL, DIMENSION(:), INTENT(OUT) :: plegi ! latent heat of sublimation over frozen soil
697 REAL, DIMENSION(:), INTENT(OUT) :: plelitter ! evapaporation of litter in litter reservoir
698 REAL, DIMENSION(:), INTENT(OUT) :: plelitteri ! sublimation of water in litter reservoir
699 REAL, DIMENSION(:), INTENT(OUT) :: pdriplit !
700 REAL, DIMENSION(:), INTENT(OUT) :: prrlit !
701 REAL, DIMENSION(:), INTENT(OUT) :: pleg ! latent heat of evaporation
702 ! ! over the ground
703 REAL, DIMENSION(:), INTENT(OUT) :: plev ! latent heat of evaporation
704 ! ! over the vegetation
705 REAL, DIMENSION(:), INTENT(OUT) :: ples ! latent heat of sublimation
706 ! ! over the snow
707 REAL, DIMENSION(:), INTENT(OUT) :: pler ! latent heat of the fraction
708 ! ! delta of water retained on the
709 ! ! foliage of the vegetation
710 REAL, DIMENSION(:), INTENT(OUT) :: pletr ! evapotranspiration of the rest
711 ! ! of the vegetation
712 REAL, DIMENSION(:), INTENT(OUT) :: pevap ! total evaporative flux (kg/m2/s)
713 REAL, DIMENSION(:), INTENT(OUT) :: psubl ! sublimation flux (kg/m2/s)
714 REAL, DIMENSION(:), INTENT(OUT) :: pgflux ! flux through the ground
715 REAL, DIMENSION(:), INTENT(OUT) :: prestore ! surface restore flux (W m-2)
716 REAL, DIMENSION(:), INTENT(OUT) :: pustar ! friction velocity
717 REAL, DIMENSION(:), INTENT(OUT) :: pdrain ! drainage
718 REAL, DIMENSION(:), INTENT(OUT) :: prunoff ! runoff
719 REAL, DIMENSION(:), INTENT(OUT) :: pmelt ! melting rate of the snow (kg/m2/s)
720 REAL, DIMENSION(:), INTENT(OUT) :: pmeltadv ! advection heat flux from snowmelt (W/m2)
721 REAL ,DIMENSION(:), INTENT(OUT) :: pirrig_flux! irrigation rate (kg/m2/s)
722 REAL ,DIMENSION(:), INTENT(OUT) :: psndrift ! blowing snow sublimation (kg/m2/s)
723 !
724 ! The following surface fluxes are from snow-free portion of grid
725 ! box when the ISBA-ES option is ON. Otherwise, they are equal
726 ! to the same variables without the _ISBA extension.
727 !
728 REAL, DIMENSION(:), INTENT(OUT) :: prn_isba ! net radiation
729 REAL, DIMENSION(:), INTENT(OUT) :: ph_isba ! sensible heat flux
730 REAL, DIMENSION(:), INTENT(OUT) :: pleg_isba ! latent heat of evaporation (ground)
731 REAL, DIMENSION(:), INTENT(OUT) :: plegi_isba ! latent heat of sublimation (ground)
732 REAL, DIMENSION(:), INTENT(OUT) :: plev_isba ! latent heat of evaporation (vegetation)
733 REAL, DIMENSION(:), INTENT(OUT) :: pletr_isba ! latent heat of evaporation (transpiration)
734 REAL, DIMENSION(:), INTENT(OUT) :: pustar_isba! friction velocity
735 REAL, DIMENSION(:), INTENT(OUT) :: pler_isba ! latent heat of evaporation (plant interception)
736 REAL, DIMENSION(:), INTENT(OUT) :: ple_isba ! total latent heat flux
737 REAL, DIMENSION(:), INTENT(OUT) :: plei_isba ! sublimation latent heat flux
738 REAL, DIMENSION(:), INTENT(OUT) :: pgflux_isba! flux through the ground
739 !
740 REAL, DIMENSION(:), INTENT(OUT) :: phort !Horton runoff (kg/m2/s)
741 !
742 REAL, DIMENSION(:), INTENT(OUT) :: pdrip !Dripping from the vegetation (kg/m2/s)
743 REAL, DIMENSION(:), INTENT(OUT) :: prrveg !Precip. intercepted by vegetation (kg/m2/s)
744 !
745 REAL, DIMENSION(:), INTENT(OUT) :: pac_agg ! aggregated aerodynamic conductance
746  ! for evaporative flux calculations
747 REAL, DIMENSION(:), INTENT(OUT) :: phu_agg ! aggregated relative humidity
748  ! for evaporative flux calculations
749 !
750 !
751 !* diagnostic variables for Carbon assimilation
752 ! --------------------------------------------
753 !
754 REAL, DIMENSION(:), INTENT(INOUT) :: pan ! net CO2 assimilation ( kgCO2/kgair * m/s)
755 REAL, DIMENSION(:), INTENT(INOUT) :: panday ! daily net CO2 assimilation (kgCO2/m2/day)
756 REAL, DIMENSION(:,:), INTENT(OUT) :: presp_biomass_inst ! instantaneous biomass respiration (kgCO2/kgair m/s)
757 REAL, DIMENSION(:), INTENT(INOUT) :: pfaparc ! Fapar of vegetation (cumul)
758 REAL, DIMENSION(:), INTENT(INOUT) :: pfapirc ! Fapir of vegetation (cumul)
759 REAL, DIMENSION(:), INTENT(INOUT) :: pmus
760 REAL, DIMENSION(:), INTENT(INOUT) :: plai_effc ! Effective LAI (cumul)
761 REAL, DIMENSION(:,:), INTENT(OUT) :: piacan ! PAR in the canopy at different gauss level
762 REAL, DIMENSION(:), INTENT(OUT) :: panf ! total assimilation over canopy
763 REAL, DIMENSION(:), INTENT(OUT) :: pgpp ! Gross Primary Production
764 REAL, DIMENSION(:), INTENT(OUT) :: pfapar ! Fapar of vegetation
765 REAL, DIMENSION(:), INTENT(OUT) :: pfapir ! Fapir of vegetation
766 REAL, DIMENSION(:), INTENT(OUT) :: pfapar_bs ! Fapar of bare soil
767 REAL, DIMENSION(:), INTENT(OUT) :: pfapir_bs ! Fapir of bare soil
768 !
769 !* diagnostic variables for multi-energy balance (MEB)
770 ! ---------------------------------------------------
771 !
772 REAL, DIMENSION(:), INTENT(OUT) :: pswnet_v ! MEB: net vegetation canopy shortwave radiation [W/m2]
773 REAL, DIMENSION(:), INTENT(OUT) :: pswnet_g ! MEB: net ground shortwave radiation [W/m2]
774 REAL, DIMENSION(:), INTENT(OUT) :: pswnet_n ! MEB: net snow shortwave radiation [W/m2]
775 REAL, DIMENSION(:), INTENT(OUT) :: pswnet_ns ! MEB: net snow shortwave radiation for *surface* layer
776  ! (i.e. net snow shortwave radiation less absorbed radiation) [W/m2]
777 REAL, DIMENSION(:), INTENT(OUT) :: plwnet_v ! MEB: net vegetation canopy longwave radiation [W/m2]
778 REAL, DIMENSION(:), INTENT(OUT) :: plwnet_g ! MEB: net ground longwave radiation [W/m2]
779 REAL, DIMENSION(:), INTENT(OUT) :: plwnet_n ! MEB: net snow longwave radiation [W/m2]
780 REAL, DIMENSION(:), INTENT(OUT) :: plev_v_c ! MEB: total evapotranspiration (no sublim) from vegetation canopy overstory [W/m2]
781 REAL, DIMENSION(:), INTENT(OUT) :: ples_v_c ! MEB: total snow sublimation from vegetation canopy overstory [W/m2]
782 REAL, DIMENSION(:), INTENT(OUT) :: ph_v_c ! MEB: sensible heat flux from vegetation canopy overstory [W/m2]
783 REAL, DIMENSION(:), INTENT(OUT) :: ph_g_c ! MEB: sensible heat flux from understory [W/m2]
784 REAL, DIMENSION(:), INTENT(OUT) :: pletr_g_c ! MEB: transpiration from understory vegetation [W/m2]
785 REAL, DIMENSION(:), INTENT(OUT) :: pletr_v_c ! MEB: transpiration from overstory canopy vegetation [W/m2]
786 REAL, DIMENSION(:), INTENT(OUT) :: pler_g_c ! MEB: interception evaporation from understory vegetation [W/m2]
787 REAL, DIMENSION(:), INTENT(OUT) :: pler_v_c ! MEB: interception evaporation from overstory canopy vegetation [W/m2]
788 REAL, DIMENSION(:), INTENT(OUT) :: ph_c_a ! MEB: sensible heat flux from canopy air space to the atmosphere [W/m2]
789  ! NOTE total sensible heat flux to the atmosphere also possibly
790  ! includes a contribution from snow covering the canopy
791 REAL, DIMENSION(:), INTENT(OUT) :: ph_n_c ! MEB: sensible heat flux from the snow on the ground [W/m2]
792  ! NOTE total sensible heat flux from the snowpack
793  ! possibly includes a contribution from snow covering the canopy
794 REAL, DIMENSION(:), INTENT(OUT) :: ple_v_c ! MEB: latent heat flux from vegetation canopy overstory [W/m2]
795 REAL, DIMENSION(:), INTENT(OUT) :: ple_g_c ! MEB: latent heat flux from understory [W/m2]
796 REAL, DIMENSION(:), INTENT(OUT) :: ple_c_a ! MEB: latent heat flux from canopy air space to the atmosphere [W/m2]
797  ! NOTE total latent heat flux to the atmosphere also possibly
798  ! includes a contribution from snow covering the canopy
799 REAL, DIMENSION(:), INTENT(OUT) :: ple_n_c ! MEB: latent heat flux from the snow on the ground [W/m2]
800  ! NOTE total latent heat flux from the snowpack
801  ! possibly includes a contribution from snow covering the canopy
802 REAL, DIMENSION(:), INTENT(OUT) :: pevap_n_c ! MEB: Total evap from snow on the ground to canopy air space [kg/m2/s]
803 REAL, DIMENSION(:), INTENT(OUT) :: pevap_g_c ! MEB: Total evap from ground to canopy air space [kg/m2/s]
804 REAL, DIMENSION(:), INTENT(OUT) :: psr_gn ! MEB: total snow reaching the ground snow [kg/m2/s]
805 REAL, DIMENSION(:), INTENT(OUT) :: pmeltcv ! MEB: snow melt rate from the overstory snow reservoir [kg/m2/s]
806 REAL, DIMENSION(:), INTENT(OUT) :: pfrzcv ! MEB: snow refreeze rate from the overstory snow reservoir [kg/m2/s]
807 REAL, DIMENSION(:), INTENT(OUT) :: pswdown_gn ! MEB: total shortwave radiation transmitted through the canopy
808  ! reaching the snowpack/ground understory [W/m2]
809 REAL, DIMENSION(:), INTENT(OUT) :: plwdown_gn ! MEB: total shortwave radiation transmitted through and emitted by the canopy
810  ! reaching the snowpack/ground understory (explicit part) [W/m2]
811 !
812 !
813 REAL, DIMENSION(:), INTENT(OUT) :: pdeep_flux ! Heat flux at bottom of ISBA (W/m2)
814 
815 !
816 !* 0.2 declarations of local variables
817 !
818 REAL, DIMENSION(SIZE(PWR)) :: zcs ! heat capacity of the snow
819 REAL, DIMENSION(SIZE(PWR)) :: zfrozen1 ! ice fraction in superficial soil
820 REAL, DIMENSION(SIZE(PWR)) :: zdelta ! fraction of the foliage
821 ! ! covered with intercepted
822 ! ! water
823 REAL, DIMENSION(SIZE(PWR)) :: zqsat ! expression for the saturation
824 ! ! specific humidity
825 !
826 REAL, DIMENSION(SIZE(PWR)) :: zwrmax ! maximum canopy water interception
827 !
828 REAL, DIMENSION(SIZE(PWR)) :: zf2 ! water stress coefficient
829 !
830 REAL, DIMENSION(SIZE(PWR)) :: zf5 ! water stress coefficient (based on F2)
831 ! ! to enforce Etv=>0 as F2=>0
832 !
833 REAL, DIMENSION(SIZE(PWR)) :: zhugi ! humidity over frozen bare ground
834 !
835 REAL, DIMENSION(SIZE(PWR)) :: zevapcor ! evaporation correction as last traces of snow
836 ! ! cover ablate
837 REAL, DIMENSION(SIZE(PWR)) :: zles3l ! sublimation from ISBA-ES(3L)
838 REAL, DIMENSION(SIZE(PWR)) :: zlel3l ! evaporation heat flux of water in the snow (W/m2)
839 REAL, DIMENSION(SIZE(PWR)) :: zevap3l ! evaporation flux over snow from ISBA-ES (kg/m2/s)
840 REAL, DIMENSION(SIZE(PWR)) :: zsnow_thrufal !rate that liquid water leaves snow pack:
841 ! ISBA-ES [kg/(m2 s)]
842 REAL, DIMENSION(SIZE(PWR)) :: zsnow_thrufal_soil !liquid water leaving the snowpack directly to the
843 ! !soil, ISBA-ES: [kg/(m2 s)] (equal to ZSNOW_THRUFAL
844 ! !if OMEB_LITTER=False and zero if OMEB_LITTER=True)
845 REAL, DIMENSION(SIZE(PWR)) :: zalb3l !Snow albedo at t-dt for total albedo calculation (ES/CROCUS)
846 REAL, DIMENSION(SIZE(PWR)) :: zri3l !Snow Ridcharson number (ES/CROCUS)
847 REAL, DIMENSION(SIZE(PWR)) :: zqs3l ! surface humidity (kg/kg) (ES/CROCUS)
848 !
849 REAL, DIMENSION(SIZE(PWR)) :: zveg
850 !
851 REAL, DIMENSION(SIZE(PWR),SIZE(PABC)) :: ziacan_shade, ziacan_sunlit
852 ! ! absorbed PAR of each level within the
853 ! ! canopy - Split into shaded and SUNLIT
854 REAL, DIMENSION(SIZE(PWR),SIZE(PABC)) :: zfrac_sun ! fraction of sunlit leaves
855 !
856 ! ISBA-DF:
857 !
858 REAL, DIMENSION(SIZE(PWG,1),SIZE(PWG,2)) :: zsoilhcapz ! ISBA-DF Soil heat capacity
859 ! ! profile [J/(m3 K)]
860 REAL, DIMENSION(SIZE(PWG,1),SIZE(PWG,2)) :: zsoilcondz ! ISBA-DF Soil conductivity
861 ! ! profile [W/(m K)]
862 !
863 REAL, DIMENSION(SIZE(PWG,1),SIZE(PWG,2)) :: zf2wght ! water stress factor
864 !
865 REAL, DIMENSION(SIZE(PWR)) :: zgrndflux ! snow/soil-biomass interface flux (W/m2)
866 REAL, DIMENSION(SIZE(PWR)) :: zflsn_cor ! snow/soil-biomass correction flux (W/m2)
867 !
868 ! MEB:
869 !
870 REAL, DIMENSION(SIZE(PWR)) :: zsubvcor ! A possible snow (intercepted by the canopy) mass correction
871 ! (to be potentially removed from soil) when MEB activated (kg/m2/s)
872 REAL, DIMENSION(SIZE(PWR)) :: zlitcor ! A possible ice (in litter layer) mass correction
873 ! (to be potentially removed from soil) when litter activated (kg/m2/s)
874 !
875 ! Misc :
876 !
877 ! -----------------------------------------------------------------------------------------------------------------------------------------------------
878 ! Budget: Add to arguments, diags
879 
880 REAL, DIMENSION(SIZE(PWR)) :: zdelheatv_sfc ! Change in heat storage of the explicit vegetation (MEB) layer over the current time step (W m-2)
881 REAL, DIMENSION(SIZE(PWR)) :: zdelheatg ! change in heat storage of the entire soil column over the current time step (W m-2)
882 REAL, DIMENSION(SIZE(PWR)) :: zdelheatg_sfc ! change in heat storage of the surface soil layer over the current time step (W m-2)
883 REAL, DIMENSION(SIZE(PWR)) :: zdelphaseg ! latent heating due to soil freeze-thaw in the entire soil column (W m-2)
884 REAL, DIMENSION(SIZE(PWR)) :: zdelphaseg_sfc ! latent heating due to soil freeze-thaw in the surface soil layer (W m-2)
885 REAL, DIMENSION(SIZE(PWR)) :: zdelheatn ! change in heat storage of the entire snow column over the current time step (W m-2)
886 REAL, DIMENSION(SIZE(PWR)) :: zdelheatn_sfc ! change in heat storage of the surface snow layer over the current time step (W m-2)
887 REAL, DIMENSION(SIZE(PWR)) :: zsnowsfch ! snow surface layer pseudo-heating term owing to
888 ! ! changes in grid thickness (W m-2)
889 REAL, DIMENSION(SIZE(PWR)) :: zgsfcsnow ! conductive heat flux between the surface and sub-surface soil layers
890 ! ! for the multi-layer snow schemes..for composite snow, it is
891 ! ! equal to PRESTORE (W m-2)
892 !
893 !
894 ! Necessary to close the energy budget between surfex and the atmosphere:
895 !
896 REAL, DIMENSION(SIZE(PWR)) :: zemist, zzhv
897 REAL, DIMENSION(SIZE(PWR)) :: zalbt, zev, zetr, zer
898 !
899 LOGICAL, DIMENSION(SIZE(PTG,1)) :: gshade ! mask where evolution occurs
900 !
901 !
902 REAL(KIND=JPRB) :: zhook_handle
903 !
904 !-------------------------------------------------------------------------------
905 !
906 !* 1.0 Preliminaries
907 ! -------------
908 !
909 IF (lhook) CALL dr_hook('ISBA',0,zhook_handle)
910 !
911 pc1(:) = xundef
912 pc2(:) = xundef
913 pwgeq(:) = xundef
914 zcs(:) = xundef
915 !
916 zemist(:) = xundef
917 zalbt(:) = xundef
918 zri3l(:) = xundef
919 !
920 zsoilhcapz(:,:) = xundef
921 zsoilcondz(:,:) = xundef
922 zf2wght(:,:) = xundef
923 zevap3l(:) = xundef
924 !
925 prs(:) = 0.0
926 pac_agg(:) = 0.0
927 phu_agg(:) = 0.0
928 psnowtemp(:,:) = xtt
929 pmelt(:) = 0.0
930 !
931 !
932 !
933 ! MEB:
934 !
935 zdelheatv_sfc(:) = 0.0
936 zdelheatg(:) = 0.0
937 zdelheatg_sfc(:) = 0.0
938 zdelphaseg(:) = 0.0
939 zdelphaseg_sfc(:) = 0.0
940 zdelheatn(:) = 0.0
941 zdelheatn_sfc(:) = 0.0
942 zsnowsfch(:) = 0.0
943 zgsfcsnow(:) = 0.0
944 zsnow_thrufal(:) = 0.0
945 !
946 zsubvcor(:) = 0.0
947 zlitcor(:) = 0.0
948 zles3l = 0.0
949 zlel3l = 0.0
950 !
951 IF(omeb)THEN
952  zveg(:) = 0.0
953  pleg(:) = 0.0
954  plegi(:) = 0.0
955  plelitter(:) = 0.0
956  plelitteri(:) = 0.0
957 ELSE
958  zveg(:) = pveg(:)
959  ples_v_c(:) = 0.0
960  pwrvn(:) = 0.0
961 ENDIF
962 !
963 ! Save snow albedo values at beginning of time step for total albedo calculation
964 !
965 zalb3l(:)=psnowalb(:)
966 !
967 !-------------------------------------------------------------------------------
968 !
969 !* 2.0 Soil parameters
970 ! ---------------
971 !
972 IF(hisba =='2-L' .OR. hisba == '3-L')THEN
973 !
974  CALL soil(hc1dry, hscond, hsnow_isba, oglacier, psnowrho(:,1), zveg, pcgsat,&
975  pcgmax, pc1sat, pc2ref, pacoef, ppcoef, pcv, ppsn, ppsng, ppsnv, pffg, &
976  pffv, pff, pcg, pc1, pc2, pwgeq, pct, zcs, zfrozen1, ptg(:,1), pwg, pwgi, &
977  phcapsoil(:,1), pconddry(:,1), pcondsld(:,1), pbcoef(:,1), pwsat(:,1), &
978  pwwilt(:,1), hksat,pcondsat,pffg_nosnow,pffv_nosnow )
979 !
980 ELSE
981 !
982  CALL soildif(hdifsfcond, oflood, zveg, pcv, pffg_nosnow, pffv_nosnow, &
983  pcg, pct, zfrozen1, pd_g, pdzg, ptg, pwg, pwgi, kwg_layer, &
984  phcapsoil, pconddry, pcondsld, pbcoef, pwsat, pmpotsat, zsoilcondz, &
985  zsoilhcapz, pfwtd, pwtd, pwr )
986 !
987 ENDIF
988 !
989 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
990 !
991 !* 3.0 Plant stress due to soil water deficit
992 ! --------------------------------------
993 !
994  CALL soilstress(hisba, zf2, &
995  prootfrac, pwsat, pwfc, pwwilt, &
996  pwg, pwgi, kwg_layer, zf2wght, zf5 )
997 !
998 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
999 !
1000 !* 4.0 Explicit Canopy Vegetation Option
1001 ! ---------------------------------
1002 !
1003 IF(omeb)THEN
1004  CALL isba_meb(tptime, omeb, omeb_litter, omeb_gndres,pgndlitter, &
1005  oforc_measure, oglacier,&
1006  otr_ml, oagri_to_grass, gshade, ostressdef, &
1007  osnowdrift, osnowdrift_sublim, osnow_abs_zenith, lirrigate, lirriday, &
1008  hsnowmetamo, hsnowrad, hphoto, &
1009  hisba, hcpsurf, hrain, hsnow_isba, hsnowres, himplicit_wind, &
1010  kwg_layer, ptstep, pvegtype, plat, plon, &
1011  pthreshold, pwatsup, pirrig, pirrig_flux, &
1012  zsoilhcapz, zsoilcondz, zfrozen1, &
1013  pps, pzenith, psca_sw, psw_rad, pvmod, prr, psr, prhoa, pta, pqa, &
1014  ph_veg, pdircoszw, &
1015  pexns, pexna, ppet_a_coef, ppet_b_coef, ppeq_a_coef, ppeq_b_coef, &
1016  ppew_a_coef, ppew_b_coef, &
1017  pzref, puref, pch, pcd, pcdn, pri, presa, phug, phv, phu, pqs, &
1018  pz0g_without_snow, &
1019  pz0_mebv, pz0h_mebv, pz0eff_mebv, &
1020  pz0_mebn, pz0h_mebn, pz0eff_mebn, &
1021  pz0_with_snow, pz0h_with_snow, pz0eff, &
1022  ptv, ptl, ptg, ptc, pqc, pwr, pwrl,pwrli, pwrvn, pwg, pwgi, &
1023  pwrmax_cf, prgl, prsmin, pgamma, prs, &
1024  palbnir_tveg, palbvis_tveg,palbnir_tsoil, palbvis_tsoil, pfalb, &
1025  psnowalb, psnowalbvis, psnowalbnir, psnowalbfir, &
1026  pabc, pfaparc, pfapirc, pmus, plai_effc, &
1027  piacan, pfapar, pfapir, pfapar_bs, pfapir_bs, &
1028  pah, pbh, pf2i, pdmax, ppoi, pcsp, pfzero, pepso, &
1029  pgamm, pqdgamm, pgmes, pgc, pqdgmes, pt1gmes, pt2gmes, &
1030  pamax, pqdamax, pt1amax, pt2amax, &
1031  pan, panday, panfm, pgpp, panf, presp_biomass_inst, &
1032  pff, ppsn, ppalphan, plai, zf2, &
1033  pwsat, pwfc, &
1034  psnowgran1, psnowgran2, psnowhist,psnowage, &
1035  psnowrho, psnowswe, psnowheat, psnowtemp, psnowdz, psnowliq, pfemis, &
1036  pswnet_n, pswnet_v, pswnet_g, pswnet_ns, palbt, pswdown_gn, &
1037  plw_rad, plwnet_n, plwnet_v, plwnet_g, plwdown_gn, &
1038  plev_v_c, ples_v_c, ph_v_c, ph_g_c, pletr_v_c, pler_v_c, ph_c_a, &
1039  ph_n_c, ple_v_c, ple_g_c, ple_c_a, ple_n_c, pevap_n_c, pevap_g_c, &
1040  psr_gn, pmeltcv, pfrzcv, pmeltadv, &
1041  ple_flood, plei_flood, &
1042  ple, ph, prn, plei, plegi, pleg,plelitteri,plelitter,pdriplit,prrlit, &
1043  plev, pler, pletr, pevap, ples, plesl, &
1044  psubl, prestore, zgrndflux, zflsn_cor, pustar, &
1045  phpsnow, psnowhmass, prnsnow, phsnow, pgfluxsnow, &
1046  pustarsnow, psrsfc, prrsfc, pemisnow, pcdsnow, pchsnow, &
1047  zemist, pts_rad, phu_agg, pac_agg, &
1048  zdelheatv_sfc, zdelheatg_sfc, zdelheatg, &
1049  zdelheatn, zdelheatn_sfc, zgsfcsnow, &
1050  pd_g, pdzg, pcps, plvtt, plstt, pct, pcv, pcg, pffrozen, &
1051  ptdeep_a, ptdeep_b, pdeep_flux, pmuf, pdrip, prrveg, &
1052  zri3l, zsnow_thrufal,zsnow_thrufal_soil, zevapcor, zsubvcor,zlitcor, &
1053  zsnowsfch, psndrift, zqs3l )
1054 ELSE
1055 !
1056 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1057 !
1058 !* 5.0 Radiative transfert
1059 ! -------------------
1060 !
1061  IF (otr_ml) THEN
1062  CALL radiative_transfert(oagri_to_grass, pvegtype, &
1063  palbvis_tveg, palbvis_tsoil, palbnir_tveg, palbnir_tsoil, &
1064  psw_rad, plai, pzenith, pabc, &
1065  pfaparc, pfapirc, pmus, plai_effc, gshade, piacan, &
1066  ziacan_sunlit, ziacan_shade, zfrac_sun, &
1067  pfapar, pfapir, pfapar_bs, pfapir_bs )
1068  ENDIF
1069 !
1070 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1071 !
1072 !* 6.0 Fraction of leaves occupied by intercepted water
1073 ! ------------------------------------------------
1074 !
1075  CALL wet_leaves_frac(pwr, pveg, pwrmax_cf, pz0_with_snow, plai, zwrmax, zdelta)
1076 !
1077 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1078 !
1079 !* 7.0 Explicit snow scheme
1080 ! --------------------
1081 !
1082  CALL snow3l_isba(hisba, hsnow_isba, hsnowres, omeb, oglacier, himplicit_wind,&
1083  tptime, ptstep, pvegtype, &
1084  psnowswe, psnowheat, psnowrho, psnowalb, &
1085  psnowgran1, psnowgran2, psnowhist,psnowage, &
1086  ptg, pcg, pct, zsoilhcapz, zsoilcondz(:,1), &
1087  pps, pta, psw_rad, pqa, pvmod, plw_rad, prr, psr, &
1088  prhoa, puref, pexns, pexna, pdircoszw, plvtt, plstt, &
1089  pzref, pz0_with_snow, pz0eff, pz0h_with_snow, palb, pd_g, pdzg, &
1090  ppew_a_coef, ppew_b_coef, &
1091  ppet_a_coef, ppeq_a_coef, ppet_b_coef, ppeq_b_coef, &
1092  zsnow_thrufal_soil, zgrndflux, zflsn_cor, zgsfcsnow, zevapcor, &
1093  pswnet_n, pswnet_ns, plwnet_n, &
1094  prnsnow, phsnow, pgfluxsnow, phpsnow, zles3l, zlel3l, zevap3l, &
1095  psndrift, pustarsnow, ppsn, psrsfc, prrsfc, zsnowsfch, &
1096  zdelheatn, zdelheatn_sfc, &
1097  pemisnow, pcdsnow, pchsnow, psnowtemp, psnowliq, psnowdz, &
1098  psnowhmass, zri3l, pzenith, zdelheatg, zdelheatg_sfc, &
1099  plat, plon, zqs3l, &
1100  osnowdrift,osnowdrift_sublim,osnow_abs_zenith, &
1101  hsnowmetamo,hsnowrad )
1102 
1103 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1104 !
1105 !* 8.0 Plant stress, stomatal resistance and, possibly, CO2 assimilation
1106 ! --------------------------------------------------------------------
1107 !
1108  IF (hphoto=='NON') THEN
1109  CALL veg(psw_rad, pta, pqa, pps, prgl, plai, prsmin, pgamma, zf2, prs)
1110  ELSE IF (maxval(pgmes).NE.xundef .OR. minval(pgmes).NE.xundef) THEN
1111  zqsat(:)=qsat(ptg(:,1),pps(:))
1112  CALL cotwores(ptstep, hphoto, otr_ml, gshade, &
1113  pvegtype, ostressdef, pah, pbh, pf2i, pdmax, &
1114  ppoi, pcsp, ptg(:,1), zf2, psw_rad, presa, pqa, zqsat, ple, &
1115  ppsnv, zdelta, plai, prhoa, pzenith, pfzero, pepso, &
1116  pgamm, pqdgamm, pgmes, pgc, pqdgmes, pt1gmes, pt2gmes, &
1117  pamax, pqdamax, pt1amax, pt2amax, pffv, &
1118  ziacan_sunlit, ziacan_shade, zfrac_sun, piacan, &
1119  pabc, pan, panday, prs, panfm, pgpp, panf, presp_biomass_inst(:,1))
1120  ELSE
1121  presp_biomass_inst(:,1) = 0.0
1122  pgpp(:) = 0.0
1123  ENDIF
1124 !
1125 !
1126 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1127 !
1128 !* 9.0 ISBA Composit Energy Budget
1129 ! -----------------------------------------------
1130 !
1131  CALL isba_ceb(hisba, hsnow_isba, hcpsurf, oflood, otemp_arp, himplicit_wind, &
1132  ptstep, psodelx, ppew_a_coef, ppew_b_coef, ppet_a_coef, &
1133  ppeq_a_coef, ppet_b_coef, ppeq_b_coef, psnowalb, &
1134  psw_rad, plw_rad, pwg, pwgi, pexns, pexna, pta, pvmod, &
1135  pqa, prr, psr, pps, prs, pveg, pz0_with_snow, pz0eff, &
1136  pz0h_with_snow, pwfc, pwsat, ppsn, ppsng, ppsnv, pzref, &
1137  puref, pdircoszw, zf5, pffg, pffv, pff, pffg_nosnow, &
1138  pffv_nosnow, pwr, prhoa, pemis, palb, pct, zcs, pcg, &
1139  pd_g, pdzg, pdzdif, zsoilcondz, zsoilhcapz, zfrozen1, &
1140  ptdeep_a, ptdeep_b, pgammat, ppsnv_a, psnowfree_alb_veg, &
1141  psnowfree_alb_soil, zgrndflux, zflsn_cor, zsnow_thrufal_soil, &
1142  pffrozen, pfalb, pfemis, psnowswe(:,1), psrsfc, &
1143  ptg, presa, plvtt, plstt, pcps, zdelta, pch, pcd, pcdn, &
1144  pri, phug, zhugi, phv, phu, pqs, zalbt, zemist, pdeep_flux, &
1145  prn, ph, ple, pleg, plegi, plev, ples, pler, pletr, pevap, &
1146  pgflux, pmeltadv, pmelt, prestore, pustar, ple_flood, &
1147  plei_flood, psnowtemp(:,1), pac_agg, phu_agg )
1148 !
1149 ENDIF
1150 !
1151 !*******************************************************************************
1152 ! WARNING: at this stage, all fluxes have two different meanings according
1153 ! to the ISBA snow-scheme option:
1154 ! 'D95' : they represent aggregated (snow + flood + snow-flood-free) fluxes
1155 ! '3-L' : they represent flood + snow-flood-free fluxes
1156 !
1157 ! The variables concerned by this are: PRN, PH, PLE, PLEI, PLEG, PLEGI, PLEV, PLES,
1158 ! PLER, PLETR, PEVAP, PUSTAR, PGFLUX
1159 !*******************************************************************************
1160 !
1161 !* 12.0 Water transfers and phase change in the soil
1162 ! --------------------------------------------
1163 !
1164  CALL hydro(hisba, hsnow_isba, hrunoff, hsoilfrz, omeb, oglacier, &
1165  oflood, ptstep, pvegtype, &
1166  prrsfc, psrsfc, plev, pletr, pleg, ples, prunoffb, pwdrain, &
1167  pc1, pc2, pc3, pc4b, pc4ref, pwgeq, pcg, pct, zveg, plai, zwrmax, pmelt, &
1168  ptauice, plegi, prunoffd, psoilwght, klayer_hort, klayer_dun, &
1169  ppsnv, ppsng, zsnow_thrufal_soil, zevapcor, zsubvcor, pwr, zsoilhcapz, &
1170  psnowswe(:,1), psnowalb, psnowrho(:,1), pbcoef, pwsat, pcondsat, pmpotsat, &
1171  pwfc, pwwilt, zf2wght, zf2, pd_g, pdzg, pdzdif, pps, &
1172  pwg, pwgi, ptg, kwg_layer, pdrain, prunoff, ptopqs, &
1173  pirrig, pwatsup, pthreshold, lirriday, lirrigate, &
1174  hksat, hrain, hhort, pmuf, pfsat, pksat_ice, pd_ice, phort, pdrip, &
1175  pffg, pffv, pfflood, ppiflood, piflood, ppflood, prrveg, pirrig_flux, &
1176  pirrig_gr, pqsb, pfwtd, pwtd, &
1177  zdelheatg, zdelheatg_sfc, &
1178  zdelphaseg, zdelphaseg_sfc, plvtt, plstt )
1179 
1180 !-------------------------------------------------------------------------------
1181 !
1182 !* 13.0 Aggregated output fluxes and diagnostics
1183 ! -----------------------------------------
1184 !
1185 !* add snow component to output radiative parameters and fluxes in case
1186 ! of ES or CROCUS snow schemes
1187 !
1188  CALL isba_snow_agr( hsnow_isba, omeb, &
1189  pexns, pexna, pta, pqa, pzref, puref, pdircoszw, pvmod, &
1190  pz0eff, pz0_with_snow, pz0h_with_snow, prr, psr, &
1191  zemist, zalbt, ppsn, ppsng, ppsnv, &
1192  prn, ph, ple, plei, pleg, plegi, plev, ples, pler, &
1193  pletr, pevap, psubl, pgflux, plvtt, plstt, &
1194  pustar, &
1195  zles3l, zlel3l, zevap3l, &
1196  pswnet_v, pswnet_g, plwnet_v, plwnet_g, ph_v_c, ph_g_c, &
1197  plev_v_c, pletr_v_c, ples_v_c, &
1198  zqs3l, zalb3l, &
1199  prnsnow, phsnow, phpsnow, &
1200  pswnet_n, pswnet_ns, plwnet_n, &
1201  pgfluxsnow, zgsfcsnow, pustarsnow, &
1202  zgrndflux, zflsn_cor, pgrndflux, plesl, &
1203  pemisnow, &
1204  psnowtemp(:,1), pts_rad, pts, pri, pqs, phu, &
1205  pcd, pcdn, pch, psnowhmass, &
1206  prn_isba, ph_isba, pleg_isba, plegi_isba, plev_isba, &
1207  pletr_isba, pustar_isba, pler_isba, ple_isba, &
1208  plei_isba, pgflux_isba, pmeltadv, ptg(:,1), &
1209  pemist, palbt, ple_flood, plei_flood, &
1210  pffg, pffv, pff, ppalphan, ptc, omeb_litter, plelitter, &
1211  plelitteri)
1212 !
1213 !***************************************************************************
1214 ! All output fluxes and radiative variables have recovered the same physical
1215 ! meaning, that is they are aggregated quantities (snow + snow-free)
1216 !***************************************************************************
1217 !
1218 IF (lhook) CALL dr_hook('ISBA',1,zhook_handle)
1219 !
1220 !-------------------------------------------------------------------------------
1221 !
1222 END SUBROUTINE isba
subroutine soildif(HDIFSFCOND, OFLOOD, PVEG, PCV, PFFG, PFFV, PCG, PCT, PFROZEN1, PD_G, PDZG, PTG, PWG, PWGI, KWG_LAYER, PHCAPSOILZ, PCONDDRYZ, PCONDSLDZ, PBCOEF, PWSAT, PMPOTSAT, PSOILCONDZ, PSOILHCAPZ, PFWTD, PWTD, PWR)
Definition: soildif.F90:6
subroutine snow3l_isba(HISBA, HSNOW_ISBA, HSNOWRES, OMEB, OGLACIER, HIMPLICIT_WIND, TPTIME, PTSTEP, PVEGTYPE, PSNOWSWE, PSNOWHEAT, PSNOWRHO, PSNOWALB, PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, PSNOWAGE, PTG, PCG, PCT, PSOILHCAPZ, PSOILCONDZ, PPS, PTA, PSW_RAD, PQA, PVMOD, PLW_RAD, PRR, PSR, PRHOA, PUREF, PEXNS, PEXNA, PDIRCOSZW, PLVTT, PLSTT, PZREF, PZ0NAT, PZ0EFF, PZ0HNAT, PALB, PD_G, PDZG, PPEW_A_COEF, PPEW_B_COEF, PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, PPEQ_B_COEF, PTHRUFAL, PGRNDFLUX, PFLSN_COR, PGSFCSNOW, PEVAPCOR, PSWNETSNOW, PSWNETSNOWS, PLWNETSNOW, PRNSNOW, PHSNOW, PGFLUXSNOW, PHPSNOW, PLES3L, PLEL3L, PEVAP, PSNDRIFT, PUSTARSNOW, PPSN, PSRSFC, PRRSFC, PSNOWSFCH, PDELHEATN, PDELHEATN_SFC, PEMISNOW, PCDSNOW, PCHSNOW, PSNOWTEMP, PSNOWLIQ, PSNOWDZ, PSNOWHMASS, PRI, PZENITH, PDELHEATG, PDELHEATG_SFC, PLAT, PLON, PQS, OSNOWDRIFT, OSNOWDRIFT_SUBLIM, OSNOW_ABS_ZENITH, HSNOWMETAMO, HSNOWRAD)
Definition: snow3L_isba.F90:6
subroutine soil(HC1DRY, HSCOND, HSNOW_ISBA, OGLACIER, PSNOWRHOM, PVEG, PCGSAT, PCGMAX, PC1SAT, PC2REF, PACOEF, PPCOEF, PCV, PPSN, PPSNG, PPSNV, PFFG, PFFV, PFF, PCG, PC1, PC2, PWGEQ, PCT, PCS, PFROZEN1, PTG, PWG, PWGI, PHCAPSOILZ, PCONDDRYZ, PCONDSLDZ, PBCOEF, PWSAT, PWWILT, HKSAT, PCONDSAT, PFFG_NOSNOW, PFFV_NOSNOW)
Definition: soil.F90:6
subroutine isba_meb(TPTIME, OMEB, OMEB_LITTER, OMEB_GNDRES, PGNDLITTER, OFORC_MEASURE, OGLACIER, OTR_ML, OAGRI_TO_GRASS, OSHADE, OSTRESSDEF, OSNOWDRIFT, OSNOWDRIFT_SUBLIM, OSNOW_ABS_ZENITH, OIRRIGATE, OIRRIDAY, HSNOWMETAMO, HSNOWRAD, HPHOTO, HISBA, HCPSURF, HRAIN, HSNOW_ISBA, HSNOWRES, HIMPLICIT_WIND, KWG_LAYER, PTSTEP, PVEGTYPE, PLAT, PLON, PTHRESHOLD, PWATSUP, PIRRIG, PIRRIG_FLUX, PSOILHCAPZ, PSOILCONDZ, PFROZEN1, PPS, PZENITH, PSCA_SW, PSW_RAD, PVMOD, PRR, PSR, PRHOA, PTA, PQA, PH_VEG, PDIRCOSZW, PEXNS, PEXNA, PPET_A_COEF, PPET_B_COEF, PPEQ_A_COEF, PPEQ_B_COEF, PPEW_A_COEF, PPEW_B_COEF, PZREF, PUREF, PCH, PCD, PCDN, PRI, PRESA, PHUG, PHV, PHU, PQS, PZ0G_WITHOUT_SNOW, PZ0_MEBV, PZ0H_MEBV, PZ0EFF_MEBV, PZ0_MEBN, PZ0H_MEBN, PZ0EFF_MEBN, PZ0_WITH_SNOW, PZ0H_WITH_SNOW, PZ0EFF, PTV, PTL, PTG, PTC, PQC, PWR, PWRL, PWRLI, PWRVN, PWG, PWGI, PWRMAX_CF, PRGL, PRSMIN, PGAMMA, PRS, PALBNIR_TVEG, PALBVIS_TVEG, PALBNIR_TSOIL, PALBVIS_TSOIL, PFALB, PSNOWALB, PSNOWALBVIS, PSNOWALBNIR, PSNOWALBFIR, PABC, PFAPARC, PFAPIRC, PMUS, PLAI_EFFC, PIACAN, PFAPAR, PFAPIR, PFAPAR_BS, PFAPIR_BS, PAH, PBH, PF2I, PDMAX, PPOI, PCSP, PFZERO, PEPSO, PGAMM, PQDGAMM, PGMES, PGC, PQDGMES, PT1GMES, PT2GMES, PAMAX, PQDAMAX, PT1AMAX, PT2AMAX, PAN, PANDAY, PANFM, PGPP, PANF, PRESP_BIOMASS_INST, PFF, PPSN, PPALPHAN, PLAI, PF2, PWSAT, PWFC, PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, PSNOWAGE, PSNOWRHO, PSNOWSWE, PSNOWHEAT, PSNOWTEMP, PSNOWDZ, PSNOWLIQ, PFEMIS, PSWNET_N, PSWNET_V, PSWNET_G, PSWNET_NS, PALBT, PSWDOWN_GN, PLW_RAD, PLWNET_N, PLWNET_V, PLWNET_G, PLWDOWN_GN, PLEV_V_C, PLES_V_C, PH_V_C, PH_G_C, PLETR_V_C, PLER_V_C, PH_C_A, PH_N_C, PLE_V_C, PLE_G_C, PLE_C_A, PLE_N_C, PEVAP_N_C, PEVAP_G_C, PSR_GN, PMELTCV, PFRZCV, PMELTADV, PLE_FLOOD, PLEI_FLOOD, PLE, PH, PRN, PLEI, PLEGI, PLEG, PLELITTERI, PLELITTER, PDRIPLIT, PRRLIT, PLEV, PLER, PLETR, PEVAP, PLES, PLESL, PSUBL, PRESTORE, PGRNDFLUX, PFLSN_COR, PUSTAR, PHPSNOW, PSNOWHMASS, PRNSNOW, PHSNOW, PGFLUXSNOW, PUSTARSNOW, PSRSFC, PRRSFC, PEMISNOW, PCDSNOW, PCHSNOW, PEMIST, PTS_RAD, PHU_AGG, PAC_AGG, PDELHEATV_SFC, PDELHEATG_SFC, PDELHEATG, PDELHEATN, PDELHEATN_SFC, PRESTOREN, PD_G, PDZG, PCPS, PLVTT, PLSTT, PCT, PCV, PCG, PFFROZEN, PTDEEP_A, PTDEEP_B, PDEEP_FLUX, PMUF, PDRIP, PRRVEG, PRISNOW, PSNOW_THRUFAL, PSNOW_THRUFAL_SOIL, PEVAPCOR, PSUBVCOR, PLITCOR, PSNOWSFCH, PSNDRIFT, PQSNOW)
Definition: isba_meb.F90:6
subroutine soilstress(HISBA, PF2, PROOTFRAC, PWSAT, PWFC, PWWILT, PWG, PWGI, KWG_LAYER, PF2WGHT, PF5)
Definition: soilstress.F90:6
subroutine wet_leaves_frac(PWRM, PVEG, PWRMAX_CF, PZ0, PLAI, PWRMAX, PDELTA)
subroutine isba_ceb(HISBA, HSNOW_ISBA, HCPSURF, OFLOOD, OTEMP_ARP, HIMPLICIT_WIND, PTSTEP, PSODELX, PPEW_A_COEF, PPEW_B_COEF, PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, PPEQ_B_COEF, PSNOWALB, PSW_RAD, PLW_RAD, PWG, PWGI, PEXNS, PEXNA, PTA, PVMOD, PQA, PRR, PSR, PPS, PRS, PVEG, PZ0_WITH_SNOW, PZ0EFF, PZ0H_WITH_SNOW, PWFC, PWSAT, PPSN, PPSNG, PPSNV, PZREF, PUREF, PDIRCOSZW, PF5, PFFG, PFFV, PFF, PFFG_NOSNOW, PFFV_NOSNOW, PWR, PRHOA, PEMIS, PALB, PCT, PCS, PCG, PD_G, PDZG, PDZDIF, PSOILCONDZ, PSOILHCAPZ, PFROZEN1, PTDEEP_A, PTDEEP_B, PGAMMAT, PPSNV_A, PSNOWFREE_ALB_VEG, PSNOWFREE_ALB_SOIL, PGRNDFLUX, PFLSN_COR, PSNOW_THRUFAL, PFFROZEN, PFALB, PFEMIS, PSNOWSWE, PSRSFC, PTG, PRESA, PLVTT, PLSTT, PCPS, PDELTA, PCH, PCD, PCDN, PRI, PHUG, PHUGI, PHV, PHU, PQS, PALBT, PEMIST, PDEEP_FLUX, PRN, PH, PLE, PLEG, PLEGI, PLEV, PLES, PLER, PLETR, PEVAP, PGFLUX, PMELTADV, PMELT, PRESTORE, PUSTAR, PLE_FLOOD, PLEI_FLOOD, PSNOWTEMP, PAC_AGG, PHU_AGG)
Definition: isba_ceb.F90:6
subroutine isba_snow_agr(HSNOW_ISBA, OMEB, PEXNS, PEXNA, PTA, PQA, PZREF, PUREF, PDIRCOSZW, PVMOD, PZ0EFF, PZ0, PZ0H, PRR, PSR, PEMIS, PALB, PPSN, PPSNG, PPSNV, PRN, PH, PLE, PLEI, PLEG, PLEGI, PLEV, PLES, PLER, PLETR, PEVAP, PSUBL, PGFLUX, PLVTT, PLSTT, PUSTAR, PLES3L, PLEL3L, PEVAP3L, PSWNET_V, PSWNET_G, PLWNET_V, PLWNET_G, PH_V, PH_G, PLEV_V_C, PLETR_V_C, PLES_V_C, PQS3L, PALB3L, PRNSNOW, PHSNOW, PHPSNOW, PSWNETSNOW, PSWNETSNOWS, PLWNETSNOW, PGFLUXSNOW, PGSFCSNOW, PUSTARSNOW, PZGRNDFLUX, PFLSN_COR, PGRNDFLUX, PLESL, PEMISNOW, PSNOWTEMP, PTS_RAD, PTS, PRI, PQS, PHU, PCD, PCDN, PCH, PSNOWHMASS, PRN_ISBA, PH_ISBA, PLEG_ISBA, PLEGI_ISBA, PLEV_ISBA, PLETR_ISBA, PUSTAR_ISBA, PLER_ISBA, PLE_ISBA, PLEI_ISBA, PGFLUX_ISBA, PMELTADV, PTG, PEMIST, PALBT, PLE_FLOOD, PLEI_FLOOD, PFFG, PFFV, PFF, PPALPHAN, PTC, OMEB_LITTER, PLELITTER, PLELITTERI)
subroutine cotwores(PTSTEP, HPHOTO, OTR_ML, OSHADE, PVEGTYPE, OSTRESSDEF, PAH, PBH, PF2I, PDMAX, PPOI, PCSP, PTG, PF2, PSW_RAD, PRA, PQA, PQSAT, PLE, PPSNV, PDELTA, PLAI, PRHOA, PZENITH, PFZERO, PEPSO, PGAMM, PQDGAMM, PGMES, PGC, PQDGMES, PT1GMES, PT2GMES, PAMAX, PQDAMAX, PT1AMAX, PT2AMAX, PFFV, PIACAN_SUNLIT, PIACAN_SHADE, PFRAC_SUN, PIACAN, PABC, PAN, PANDAY, PRS, PANFM, PGPP, PANF, PRESP_LEAF)
Definition: cotwores.F90:6
subroutine veg(PSW_RAD, PTA, PQA, PPS, PRGL, PLAI, PRSMIN, PGAMMA, PF2, PRS)
Definition: veg.F90:6
subroutine isba(HISBA, HPHOTO, OTR_ML, HRUNOFF, HKSAT, HRAIN, HHORT, HC1DRY, HSCOND, HSNOW_ISBA, HSNOWRES, HCPSURF, HSOILFRZ, HDIFSFCOND, TPTIME, OFLOOD, OTEMP_ARP, OGLACIER, OMEB, OFORC_MEASURE, OMEB_LITTER, OMEB_GNDRES, PTSTEP, HIMPLICIT_WIND, OAGRI_TO_GRASS, OSNOWDRIFT, OSNOWDRIFT_SUBLIM, OSNOW_ABS_ZENITH, HSNOWMETAMO, HSNOWRAD, PCGMAX, PZREF, PUREF, PDIRCOSZW, PTA, PQA, PEXNA, PRHOA, PPS, PEXNS, PRR, PSR, PZENITH, PSCA_SW, PSW_RAD, PLW_RAD, PVMOD, PPEW_A_COEF, PPEW_B_COEF, PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, PPEQ_B_COEF, PRSMIN, PRGL, PGAMMA, PCV, PRUNOFFD, PSOILWGHT, KLAYER_HORT, KLAYER_DUN, PALBNIR_TVEG, PALBVIS_TVEG, PALBNIR_TSOIL, PALBVIS_TSOIL, PALB, PWRMAX_CF, PVEG, PLAI, PEMIS, PZ0_WITH_SNOW, PZ0H_WITH_SNOW, PVEGTYPE, PZ0EFF, PRGLCV, PGAMMACV, PRSMINCV, PROOTFRACCV, PWRMAX_CFCV, PLAIV, PBSLAI, PLAIMIN, PH_VEG, PPALPHAN, PZ0G_WITHOUT_SNOW, PZ0_MEBV, PZ0H_MEBV, PZ0EFF_MEBV, PZ0_MEBN, PZ0H_MEBN, PZ0EFF_MEBN, PGNDLITTER, PRUNOFFB, PCGSAT, PC1SAT, PC2REF, PC3, PC4B, PC4REF, PACOEF, PPCOEF, PTAUICE, PWDRAIN, PTDEEP_A, PTDEEP_B, PGAMMAT, PPSN, PPSNG, PPSNV, PPSNV_A, PSNOWFREE_ALB_VEG, PSNOWFREE_ALB_SOIL, PIRRIG, PWATSUP, PTHRESHOLD, LIRRIGATE, LIRRIDAY, OSTRESSDEF, PGC, PF2I, PDMAX, PAH, PBH, PCSP, PGMES, PPOI, PFZERO, PEPSO, PGAMM, PQDGAMM, PQDGMES, PT1GMES, PT2GMES, PAMAX, PQDAMAX, PT1AMAX, PT2AMAX, PABC, PD_G, PDZG, PDZDIF, KWG_LAYER, PROOTFRAC, PWFC, PWWILT, PWSAT, PBCOEF, PCONDSAT, PMPOTSAT, PHCAPSOIL, PCONDDRY, PCONDSLD, PD_ICE, PKSAT_ICE, PMUF, PFF, PFFG, PFFV, PFFG_NOSNOW, PFFV_NOSNOW, PFFROZEN, PFALB, PFEMIS, PFFLOOD, PPIFLOOD, PIFLOOD, PPFLOOD, PLE_FLOOD, PLEI_FLOOD, PSODELX, PLAT, PLON, PTG, PWG, PWGI, PCPS, PLVTT, PLSTT, PWR, PWRL, PWRLI, PWRVN, PTV, PTL, PRESA, PANFM, PFSAT, PSNOWALB, PSNOWALBVIS, PSNOWALBNIR, PSNOWALBFIR, PSNOWSWE, PSNOWHEAT, PSNOWRHO, PSNOWGRAN1, PSNOWGRAN2, PSNOWHIST, PSNOWAGE, PGRNDFLUX, PHPSNOW, PSNOWHMASS, PRNSNOW, PHSNOW, PGFLUXSNOW, PUSTARSNOW, PSRSFC, PRRSFC, PLESL, PEMISNOW, PCDSNOW, PCHSNOW, PTS_RAD, PTS, PHV, PQS, PSNOWTEMP, PSNOWLIQ, PSNOWDZ, PCG, PC1, PC2, PWGEQ, PCT, PCH, PCD, PCDN, PRI, PHU, PHUG, PEMIST, PALBT, PRS, PLE, PRN, PH, PLEI, PLEGI, PLEG, PLEV, PLES, PLER, PLETR, PEVAP, PGFLUX, PRESTORE, PUSTAR, PDRAIN, PRUNOFF, PMELT, PMELTADV, PTC, PQC, PRN_ISBA, PH_ISBA, PLEG_ISBA, PLEGI_ISBA, PLEV_ISBA, PLETR_ISBA, PUSTAR_ISBA, PLER_ISBA, PLE_ISBA, PLEI_ISBA, PGFLUX_ISBA, PHORT, PDRIP, PRRVEG, PAC_AGG, PHU_AGG, PFAPARC, PFAPIRC, PMUS, PLAI_EFFC, PAN, PANDAY, PRESP_BIOMASS_INST, PIACAN, PANF, PGPP, PFAPAR, PFAPIR, PFAPAR_BS, PFAPIR_BS, PIRRIG_FLUX, PDEEP_FLUX, PSWNET_V, PSWNET_G, PSWNET_N, PSWNET_NS, PLWNET_V, PLWNET_G, PLWNET_N, PLEV_V_C, PLES_V_C, PH_V_C, PH_G_C, PLETR_G_C, PLETR_V_C, PLER_G_C, PLELITTER, PLELITTERI, PDRIPLIT, PRRLIT, PLER_V_C, PH_C_A, PH_N_C, PLE_C_A, PLE_V_C, PLE_G_C, PLE_N_C, PEVAP_N_C, PEVAP_G_C, PSR_GN, PMELTCV, PFRZCV, PSWDOWN_GN, PLWDOWN_GN, PIRRIG_GR, PTOPQS, PQSB, PSUBL, PFWTD, PWTD, PSNDRIFT)
Definition: isba.F90:6
subroutine hydro(HISBA, HSNOW_ISBA, HRUNOFF, HSOILFRZ, OMEB, OGLACIER, OFLOOD, PTSTEP, PVEGTYPE, PRR, PSR, PLEV, PLETR, PLEG, PLES, PRUNOFFB, PWDRAIN, PC1, PC2, PC3, PC4B, PC4REF, PWGEQ, PCG, PCT, PVEG, PLAI, PWRMAX, PMELT, PTAUICE, PLEGI, PRUNOFFD, PSOILWGHT, KLAYER_HORT, KLAYER_DUN, PPSNV, PPSNG, PSNOW_THRUFAL, PEVAPCOR, PSUBVCOR, PWR, PSOILHCAPZ, PSNOWSWE, PSNOWALB, PSNOWRHO, PBCOEF, PWSAT, PCONDSAT, PMPOTSAT, PWFC, PWWILT, PF2WGHT, PF2, PD_G, PDZG, PDZDIF, PPS, PWG, PWGI, PTG, KWG_LAYER, PDRAIN, PRUNOFF, PTOPQS, PIRRIG, PWATSUP, PTHRESHOLD, LIRRIDAY, LIRRIGATE, HKSAT, HRAIN, HHORT, PMUF, PFSAT, PKSAT_ICE, PD_ICE, PHORTON, PDRIP, PFFG, PFFV, PFFLOOD, PPIFLOOD, PIFLOOD, PPFLOOD, PRRVEG, PIRRIG_FLUX, PIRRIG_GR, PQSB, PFWTD, PWTD, PDELHEATG, PDELHEATG_SFC, PDELPHASEG, PDELPHASEG_SFC, PLVTT, PLSTT)
Definition: hydro.F90:6
subroutine radiative_transfert(OAGRI_TO_GRASS, PVEGTYPE, PALBVIS_VEG, PALBVIS_SOIL, PALBNIR_VEG, PALBNIR_SOIL, PSW_RAD, PLAI, PZENITH, PABC, PFAPARC, PFAPIRC, PMUS, PLAI_EFFC, OSHADE, PIACAN, PIACAN_SUNLIT, PIACAN_SHADE, PFRAC_SUN, PFAPAR, PFAPIR, PFAPAR_BS, PFAPIR_BS)