SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
default_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 default_isba(PTSTEP, POUT_TSTEP, &
7  hrough, hrunoff, halbedo, hscond, &
8  hc1dry, hsoilfrz, hdifsfcond, hsnowres, &
9  hcpsurf, pcgmax, pcdrag, hksat, osoc, &
10  hrain, hhort, oglacier, ocanopy_drag, &
11  ovegupd, ospinupcarbs, ospinupcarbw, &
12  pspinmaxs, pspinmaxw, pco2_start, pco2_end,&
13  knbyearspins, knbyearspinw, &
14  onitro_dilu )
15 ! ########################################################################
16 !
17 !!**** *DEFAULT_ISBA* - routine to set default values for the configuration for ISBA
18 !!
19 !! PURPOSE
20 !! -------
21 !!
22 !!** METHOD
23 !! ------
24 !!
25 !! EXTERNAL
26 !! --------
27 !!
28 !!
29 !! IMPLICIT ARGUMENTS
30 !! ------------------
31 !!
32 !! REFERENCE
33 !! ---------
34 !!
35 !!
36 !! AUTHOR
37 !! ------
38 !! V. Masson *Meteo France*
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !! Original 01/2004
43 !! B.Decharme 04/2013 delete HTOPREG (never used)
44 !! water table / surface coupling
45 !-------------------------------------------------------------------------------
46 !
47 !* 0. DECLARATIONS
48 ! ------------
49 !
50 USE modd_surf_par, ONLY : xundef
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60 !
61 REAL, INTENT(OUT) :: ptstep ! time-step for run
62 REAL, INTENT(OUT) :: pout_tstep ! time-step for writing
63  CHARACTER(LEN=4), INTENT(OUT) :: hrough ! type of roughness length
64  CHARACTER(LEN=4), INTENT(OUT) :: halbedo ! albedo type
65 ! ! 'DRY '
66 ! ! 'EVOL'
67 ! ! 'WET '
68 ! ! 'USER'
69  CHARACTER(LEN=4), INTENT(OUT) :: hscond ! Thermal conductivity
70 ! ! 'DEF ' = DEFault: NP89 implicit method
71 ! ! 'PL98' = Peters-Lidard et al. 1998 used
72 ! ! for explicit computation of CG
73  CHARACTER(LEN=4), INTENT(OUT) :: hc1dry ! C1 formulation for dry soils
74 ! ! 'DEF ' = DEFault: Giard-Bazile formulation
75 ! ! 'GB93' = Giordani 1993, Braud 1993
76 ! !discontinuous at WILT
77  CHARACTER(LEN=3), INTENT(OUT) :: hsoilfrz ! soil freezing-physics option
78 ! ! 'DEF' = Default (Boone et al. 2000;
79 ! ! Giard and Bazile 2000)
80 ! ! 'LWT' = Phase changes as above,
81 ! ! but relation between unfrozen
82 ! ! water and temperature considered
83 ! NOTE that when using the YISBA='DIF' multi-layer soil option,
84 ! the 'LWT' method is used. It is only an option
85 ! when using the force-restore soil method ('2-L' or '3-L')
86 !
87  CHARACTER(LEN=4), INTENT(OUT) :: hdifsfcond ! Mulch effects
88 ! ! 'MLCH' = include the insulating effect of
89 ! ! leaf litter/mulch on the surf. thermal cond.
90 ! ! 'DEF ' = no mulch effect
91 ! NOTE: Only used when YISBA = DIF
92 !
93  CHARACTER(LEN=3), INTENT(OUT) :: hsnowres ! Turbulent exchanges over snow
94 ! ! 'DEF' = Default: Louis (ISBA)
95 ! ! 'RIL' = Maximum Richardson number limit
96 ! ! for stable conditions ISBA-SNOW3L
97 ! ! turbulent exchange option
98  CHARACTER(LEN=3), INTENT(OUT) :: hcpsurf ! SPECIFIC HEAT
99 ! ! 'DRY' = dry Cp
100 ! ! 'HUM' = Cp fct of qs
101 REAL, INTENT(OUT) :: pcgmax ! maximum soil heat capacity
102 !
103 REAL, INTENT(OUT) :: pcdrag ! drag coefficient in canopy
104 !
105  CHARACTER(LEN=4), INTENT(OUT) :: hrunoff ! surface runoff formulation
106 ! ! 'WSAT'
107 ! ! 'DT92'
108 ! ! 'SGH ' Topmodel
109 !
110  CHARACTER(LEN=3), INTENT(OUT) :: hksat ! SOIL HYDRAULIC CONDUCTIVITY PROFILE OPTION
111 ! ! 'DEF' = ISBA homogenous soil
112 ! ! 'SGH' = ksat exponential decay
113 !
114 LOGICAL, INTENT(OUT) :: osoc ! SOIL ORGANIC CARBON PROFILE OPTION
115 ! ! False = ISBA homogenous soil
116 ! ! True = SOC profile effect
117 !
118  CHARACTER(LEN=3), INTENT(OUT) :: hrain ! Rainfall spatial distribution
119  ! 'DEF' = No rainfall spatial distribution
120  ! 'SGH' = Rainfall exponential spatial distribution
121  !
122 !
123  CHARACTER(LEN=3), INTENT(OUT) :: hhort ! Horton runoff
124  ! 'DEF' = no Horton runoff
125  ! 'SGH' = Horton runoff
126 !
127 LOGICAL, INTENT(OUT) :: oglacier ! True = Over permanent snow and ice,
128 ! initialise WGI=WSAT,
129 ! Hsnow>=3.3m and allow 0.8<SNOALB<0.85
130  ! False = No specific treatment
131 LOGICAL, INTENT(OUT) :: ocanopy_drag ! T: drag activated in SBL scheme within the canopy
132 !
133 LOGICAL, INTENT(OUT) :: ovegupd ! T: update vegetation parameters
134  ! every decade
135  ! F: keep vegetation parameters
136  ! constant in time
137 !
138 LOGICAL, INTENT(OUT) :: ospinupcarbs ! T: carbon spinup soil
139 LOGICAL, INTENT(OUT) :: ospinupcarbw ! T: carbon spinup wood
140 REAL, INTENT(OUT) :: pspinmaxs ! max number of times CARBON_SOIL subroutine is called
141 REAL, INTENT(OUT) :: pspinmaxw ! max number of times the wood is accelerated
142 REAL, INTENT(OUT) :: pco2_start ! Pre-industrial CO2 concentration
143 REAL, INTENT(OUT) :: pco2_end ! Begin-transient CO2 concentration
144 INTEGER, INTENT(OUT) :: knbyearspins ! nbr years needed to reaches soil equilibrium
145 INTEGER, INTENT(OUT) :: knbyearspinw ! nbr years needed to reaches wood equilibrium
146 !
147 LOGICAL, INTENT(OUT) :: onitro_dilu ! nitrogen dilution fct of CO2 (Calvet et al. 2008)
148 !
149 !* 0.2 Declarations of local variables
150 ! -------------------------------
151 !
152 REAL(KIND=JPRB) :: zhook_handle
153 !
154 !-------------------------------------------------------------------------------
155 !
156 IF (lhook) CALL dr_hook('DEFAULT_ISBA',0,zhook_handle)
157 !
158 ptstep = xundef
159 pout_tstep = xundef
160 !!!!!do not phased!!!!!!!
161 !HROUGH = "NONE"
162 !!!!!do not phased!!!!!!!
163 hrough = "UNDE" ! undefined. Needs further information on canopy scheme use to set default
164 hscond = "PL98"
165 halbedo = "DRY "
166 !
167 hc1dry = 'DEF '
168 hsoilfrz = 'DEF'
169 hdifsfcond = 'DEF '
170 hsnowres = 'DEF'
171 hcpsurf = 'DRY'
172 !
173 hrunoff = "WSAT"
174 hksat = 'DEF'
175 osoc = .false.
176 hrain = 'DEF'
177 hhort = 'DEF'
178 !
179 pcgmax = 2.0e-5
180 !
181 pcdrag = 0.15
182 !
183 oglacier = .false.
184 !
185 ocanopy_drag = .false.
186 !
187 ovegupd = .true.
188 !
189 ospinupcarbs = .false.
190 ospinupcarbw = .false.
191 !
192 pspinmaxs = 0.
193 pspinmaxw = 0.
194 pco2_start= xundef
195 pco2_end = xundef
196 knbyearspins = 0
197 knbyearspinw = 0
198 !
199 onitro_dilu = .false.
200 !
201 IF (lhook) CALL dr_hook('DEFAULT_ISBA',1,zhook_handle)
202 !
203 !-------------------------------------------------------------------------------
204 !
205 END SUBROUTINE default_isba
subroutine default_isba(PTSTEP, POUT_TSTEP, HROUGH, HRUNOFF, HALBEDO, HSCOND, HC1DRY, HSOILFRZ, HDIFSFCOND, HSNOWRES, HCPSURF, PCGMAX, PCDRAG, HKSAT, OSOC, HRAIN, HHORT, OGLACIER, OCANOPY_DRAG, OVEGUPD, OSPINUPCARBS, OSPINUPCARBW, PSPINMAXS, PSPINMAXW, PCO2_START, PCO2_END, KNBYEARSPINS, KNBYEARSPINW, ONITRO_DILU)
Definition: default_isba.F90:6