SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_pgd_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 read_nam_pgd_isba(HPROGRAM, KPATCH, KGROUND_LAYER, &
7  hisba, hpedotf, hphoto, otr_ml, prm_patch, &
8  hclay, hclayfiletype, punif_clay, oimp_clay, &
9  hsand, hsandfiletype, punif_sand, oimp_sand, &
10  hsoc_top, hsoc_sub, hsocfiletype, punif_soc_top, &
11  punif_soc_sub, oimp_soc, hcti, hctifiletype, oimp_cti, &
12  hperm, hpermfiletype, punif_perm, oimp_perm, omeb, &
13  hgw, hgwfiletype, punif_gw, oimp_gw, &
14  hrunoffb, hrunoffbfiletype, punif_runoffb, &
15  hwdrain, hwdrainfiletype , punif_wdrain, psoilgrid, &
16  hph, hphfiletype, punif_ph, hfert, hfertfiletype, &
17  punif_fert )
18 ! ##############################################################
19 !
20 !!**** *READ_NAM_PGD_ISBA* reads namelist for ISBA
21 !!
22 !! PURPOSE
23 !! -------
24 !!
25 !! METHOD
26 !! ------
27 !!
28 !
29 !! EXTERNAL
30 !! --------
31 !OTR_ML, !
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !! AUTHOR
39 !! ------
40 !!
41 !! V. Masson Meteo-France
42 !!
43 !! MODIFICATION
44 !! ------------
45 !!
46 !! Original 01/2005
47 !! 2008 B. Decharme : uniform value of subgrid drainage coefficient
48 !! 12/2008 E. Martin : files of data for subgrid drainage
49 !! and subgridrunoff
50 !! 06/2009 B. Decharme : files of data for topographic index
51 !! 07/2012 B. Decharme : files of data for permafrost area and for SOC top and sub soil
52 !! 10/2014 P. Samuelsson: MEB
53 !----------------------------------------------------------------------------
54 !
55 !* 0. DECLARATION
56 ! -----------
57 !
58 USE modd_surf_par, ONLY : xundef, nundef
59 !
60 USE modi_get_luout
61 USE modi_open_namelist
62 USE modi_close_namelist
63 !
64 USE mode_pos_surf
65 !
66 !
67 USE yomhook ,ONLY : lhook, dr_hook
68 USE parkind1 ,ONLY : jprb
69 !
70 IMPLICIT NONE
71 !
72 !* 0.1 Declaration of arguments
73 ! ------------------------
74 !
75  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
76 INTEGER, INTENT(OUT) :: kpatch ! number of patches
77 INTEGER, INTENT(OUT) :: kground_layer ! number of soil layers
78  CHARACTER(LEN=3), INTENT(OUT) :: hisba ! ISBA option
79  CHARACTER(LEN=4), INTENT(OUT) :: hpedotf ! Pedo-transfert function for DIF
80  CHARACTER(LEN=3), INTENT(OUT) :: hphoto ! photosynthesis option
81 LOGICAL, INTENT(OUT) :: otr_ml ! new radiative transfert
82 REAL, INTENT(OUT) :: prm_patch ! threshold to remove little fractions of patches
83  CHARACTER(LEN=28), INTENT(OUT) :: hsand ! file name for sand fraction
84  CHARACTER(LEN=28), INTENT(OUT) :: hclay ! file name for clay fraction
85  CHARACTER(LEN=28), INTENT(OUT) :: hcti ! file name for topographic index
86  CHARACTER(LEN=28), INTENT(OUT) :: hperm ! file name for permafrost distribution
87  CHARACTER(LEN=28), INTENT(OUT) :: hgw ! file name for groundwater distribution
88  CHARACTER(LEN=28), INTENT(OUT) :: hrunoffb ! file name for runoffb parameter
89  CHARACTER(LEN=28), INTENT(OUT) :: hwdrain ! file name for wdrain parameter
90  CHARACTER(LEN=6), INTENT(OUT) :: hsandfiletype ! sand data file type
91  CHARACTER(LEN=6), INTENT(OUT) :: hclayfiletype ! clay data file type
92  CHARACTER(LEN=6), INTENT(OUT) :: hctifiletype ! topographic index data file type
93  CHARACTER(LEN=6), INTENT(OUT) :: hpermfiletype ! permafrost distribution data file type
94  CHARACTER(LEN=6), INTENT(OUT) :: hgwfiletype ! groundwater distribution data file type
95  CHARACTER(LEN=6), INTENT(OUT) :: hrunoffbfiletype ! subgrid runoff data file type
96  CHARACTER(LEN=6), INTENT(OUT) :: hwdrainfiletype ! subgrid drainage data file type
97 REAL, INTENT(OUT) :: punif_sand ! uniform value of sand fraction
98 REAL, INTENT(OUT) :: punif_clay ! uniform value of clay fraction
99 REAL, INTENT(OUT) :: punif_runoffb ! uniform value of subgrid runoff coefficient
100 REAL, INTENT(OUT) :: punif_wdrain ! uniform value of subgrid drainage coefficient
101 REAL, INTENT(OUT) :: punif_perm ! uniform value of permafrost distribution
102 REAL, INTENT(OUT) :: punif_gw ! uniform value of groundwater distribution
103 LOGICAL, INTENT(OUT) :: oimp_sand ! Imposed values for Sand
104 LOGICAL, INTENT(OUT) :: oimp_clay ! Imposed values for Clay
105 LOGICAL, INTENT(OUT) :: oimp_cti ! Imposed values for topographic index statistics
106 LOGICAL, INTENT(OUT) :: omeb ! MEB
107 LOGICAL, INTENT(OUT) :: oimp_perm ! Imposed maps of permafrost distribution
108 LOGICAL, INTENT(OUT) :: oimp_gw ! Imposed maps of permafrost distribution
109  CHARACTER(LEN=28), INTENT(OUT) :: hsoc_top ! file name for organic carbon
110  CHARACTER(LEN=28), INTENT(OUT) :: hsoc_sub ! file name for organic carbon
111  CHARACTER(LEN=6), INTENT(OUT) :: hsocfiletype ! organic carbon data file type
112 REAL, INTENT(OUT) :: punif_soc_top ! uniform value of organic carbon top soil (kg/m2)
113 REAL, INTENT(OUT) :: punif_soc_sub ! uniform value of organic carbon sub soil (kg/m2)
114 LOGICAL, INTENT(OUT) :: oimp_soc ! Imposed maps of organic carbon
115 REAL, DIMENSION(:), INTENT(OUT) :: psoilgrid ! Soil layer thickness for DIF
116  CHARACTER(LEN=28), INTENT(OUT) :: hph ! file name for pH
117  CHARACTER(LEN=28), INTENT(OUT) :: hfert ! file name for fertilisation rate
118  CHARACTER(LEN=6), INTENT(OUT) :: hphfiletype ! pH data file type
119  CHARACTER(LEN=6), INTENT(OUT) :: hfertfiletype ! fertilisation data file type
120 REAL, INTENT(OUT) :: punif_ph ! uniform value of pH
121 REAL, INTENT(OUT) :: punif_fert ! uniform value of fertilisation rate
122 !
123 !
124 !* 0.2 Declaration of local variables
125 ! ------------------------------
126 !
127 INTEGER :: iluout ! output listing logical unit
128 INTEGER :: ilunam ! namelist file logical unit
129 LOGICAL :: gfound ! flag when namelist is present
130 !
131 !* 0.3 Declaration of namelists
132 ! ------------------------
133 !
134 INTEGER :: npatch ! number of patches
135 INTEGER :: nground_layer ! number of soil layers
136  CHARACTER(LEN=3) :: cisba ! ISBA option
137  CHARACTER(LEN=4) :: cpedo_function ! Pedo-transfert function for DIF
138  CHARACTER(LEN=3) :: cphoto ! photosynthesis option
139 LOGICAL :: ltr_ml ! new radiative transfert
140 REAL :: xrm_patch ! threshold to remove little fractions of patches
141  CHARACTER(LEN=28) :: ysand ! file name for sand fraction
142  CHARACTER(LEN=28) :: yclay ! file name for clay fraction
143  CHARACTER(LEN=28) :: ycti ! file name for topographic index
144  CHARACTER(LEN=28) :: yperm ! file name for permafrost distribution
145  CHARACTER(LEN=28) :: ygw ! file name for groundwater map
146  CHARACTER(LEN=28) :: yrunoffb ! file name for runoffb parameter
147  CHARACTER(LEN=28) :: ywdrain ! file name for wdrain parameter
148  CHARACTER(LEN=28) :: yph ! file name for pH
149  CHARACTER(LEN=28) :: yfert ! file name for fertilisation rate
150  CHARACTER(LEN=6) :: ysandfiletype ! sand data file type
151  CHARACTER(LEN=6) :: yclayfiletype ! clay data file type
152  CHARACTER(LEN=6) :: yctifiletype ! topographic index data file type
153  CHARACTER(LEN=6) :: ypermfiletype ! permafrost distribution data file type
154  CHARACTER(LEN=6) :: ygwfiletype ! groundwater distribution data file type
155  CHARACTER(LEN=6) :: yrunoffbfiletype ! subgrid runoff data file type
156  CHARACTER(LEN=6) :: ywdrainfiletype ! subgrid drainage data file type
157  CHARACTER(LEN=6) :: yphfiletype ! pH data file type
158  CHARACTER(LEN=6) :: yfertfiletype ! fertilisation data file type
159 LOGICAL :: limp_sand ! Imposed maps of Sand from another PGD file
160 LOGICAL :: limp_clay ! Imposed maps of Clay from another PGD file
161 LOGICAL :: limp_cti ! Imposed values for topographic index statistics from another PGD file
162 LOGICAL :: lmeb ! MEB
163 LOGICAL :: limp_perm ! Imposed maps of permafrost distribution
164 LOGICAL :: limp_gw ! Imposed maps of groundwater distribution
165 REAL :: xunif_sand ! uniform value of sand fraction
166 REAL :: xunif_clay ! uniform value of clay fraction
167 REAL :: xunif_runoffb ! uniform value of subgrid runoff coefficient
168 REAL :: xunif_wdrain ! uniform value of subgrid drainage coefficient
169 REAL :: xunif_perm ! uniform value of permafrost distribution
170 REAL :: xunif_gw ! uniform groundwater distribution
171 REAL :: xunif_ph ! uniform value of pH
172 REAL :: xunif_fert ! uniform value of fertilisation rate
173 !
174 REAL, DIMENSION(150) :: xsoilgrid ! Soil layer thickness for DIF
175 !
176  CHARACTER(LEN=28) :: ysoc_top ! file name for organic carbon expressed in kg/m2
177  CHARACTER(LEN=28) :: ysoc_sub ! file name for organic carbon expressed in kg/m2
178  CHARACTER(LEN=6) :: ysocfiletype ! organic carbon data file type
179 REAL :: xunif_soc_top ! uniform value of organic carbon (kg/m2)
180 REAL :: xunif_soc_sub ! uniform value of organic carbon (kg/m2)
181 LOGICAL :: limp_soc ! Imposed maps of organic carbon
182 !
183 REAL(KIND=JPRB) :: zhook_handle
184 !
185 namelist/nam_isba/ npatch, nground_layer, cisba, cpedo_function, cphoto, &
186  ltr_ml, xrm_patch, yclay, yclayfiletype, xunif_clay, &
187  limp_clay, ysand, ysandfiletype, xunif_sand, limp_sand, &
188  ysoc_top, ysoc_sub, ysocfiletype, xunif_soc_top, &
189  xunif_soc_sub, limp_soc, ycti, yctifiletype, limp_cti, &
190  yperm, ypermfiletype, xunif_perm, limp_perm, lmeb, &
191  ygw, ygwfiletype, xunif_gw, limp_gw, &
192  yrunoffb, yrunoffbfiletype, xunif_runoffb, &
193  ywdrain, ywdrainfiletype, xunif_wdrain, xsoilgrid, &
194  yph, yphfiletype, xunif_ph, yfert, yfertfiletype, &
195  xunif_fert
196 !
197 !-------------------------------------------------------------------------------
198 !
199 !* 1. Initializations of defaults
200 ! ---------------------------
201 !
202 !#####################
203 IF (lhook) CALL dr_hook('READ_NAM_PGD_ISBA',0,zhook_handle)
204 npatch = 1
205 nground_layer = nundef
206  cisba = '3-L'
207  cpedo_function = 'CH78'
208  cphoto = 'NON'
209 ltr_ml = .false.
210 xsoilgrid(:) = xundef
211 xrm_patch = 0.0
212 !#####################
213 !
214 xunif_clay = 0.33
215 xunif_sand = 0.33
216 xunif_soc_top = xundef
217 xunif_soc_sub = xundef
218 xunif_runoffb = 0.5
219 xunif_wdrain = 0.
220 xunif_perm = xundef
221 xunif_gw = xundef
222 xunif_ph = xundef
223 xunif_fert = xundef
224 !
225 yclay = ' '
226 ysand = ' '
227 ysoc_top = ' '
228 ysoc_sub = ' '
229 ycti = ' '
230 yperm = ' '
231 ygw = ' '
232 yrunoffb = ' '
233 ywdrain = ' '
234 yph = ' '
235 yfert = ' '
236 !
237 yclayfiletype = ' '
238 ysandfiletype = ' '
239 ysocfiletype = ' '
240 yctifiletype = ' '
241 ypermfiletype = ' '
242 ygwfiletype = ' '
243 yrunoffbfiletype = ' '
244 ywdrainfiletype = ' '
245 yphfiletype = ' '
246 yphfiletype = ' '
247 !
248 limp_clay = .false.
249 limp_sand = .false.
250 limp_soc = .false.
251 limp_cti = .false.
252 lmeb = .false.
253 limp_perm = .false.
254 limp_gw = .false.
255 !
256  CALL get_luout(hprogram,iluout)
257 !
258 !-------------------------------------------------------------------------------
259 !
260 !* 2. Reading of namelist
261 ! -------------------
262 !
263  CALL open_namelist(hprogram,ilunam)
264 !
265  CALL posnam(ilunam,'NAM_ISBA',gfound,iluout)
266 IF (gfound) READ(unit=ilunam,nml=nam_isba)
267 !
268  CALL close_namelist(hprogram,ilunam)
269 !
270 !-------------------------------------------------------------------------------
271 !
272 kpatch = npatch ! number of patches
273 kground_layer = nground_layer ! number of soil layers
274 psoilgrid = xsoilgrid ! soil layer tickness for DIF
275 hisba = cisba ! ISBA option
276 hpedotf = cpedo_function ! Pedo-transfert function for DIF
277 hphoto = cphoto ! photosynthesis option
278 otr_ml = ltr_ml ! new radiative transfert
279 prm_patch = xrm_patch ! threshol to remove little fractions of patches
280 hsand = ysand ! file name for sand fraction
281 hclay = yclay ! file name for clay fraction
282 hsoc_top = ysoc_top ! file name for organic carbon
283 hsoc_sub = ysoc_sub ! file name for organic carbon
284 hcti = ycti ! file name for topographic index
285 hperm = yperm ! file name for permafrost distribution
286 hgw = ygw ! file name for groundwater distribution
287 hrunoffb = yrunoffb ! file name for subgrid runoff
288 hwdrain = ywdrain ! file name for subgrid drainage
289 hsandfiletype = ysandfiletype ! sand data file type
290 hclayfiletype = yclayfiletype ! clay data file type
291 hsocfiletype = ysocfiletype ! organic carbon data file type
292 hctifiletype = yctifiletype ! topographic index data file type
293 hpermfiletype = ypermfiletype ! permafrost distribution data file type
294 hgwfiletype = ygwfiletype ! groundwater distribution data file type
295 hrunoffbfiletype = yrunoffbfiletype ! subgrid runoff data file type
296 hwdrainfiletype = ywdrainfiletype ! subgrid drainage data file type
297 punif_sand = xunif_sand ! uniform value of sand fraction
298 punif_clay = xunif_clay ! uniform value of clay fraction
299 punif_soc_top = xunif_soc_top ! uniform value of organic carbon top soil
300 punif_soc_sub = xunif_soc_sub ! uniform value of organic carbon sub soil
301 punif_runoffb = xunif_runoffb ! uniform value of subgrid runoff coefficient
302 punif_wdrain = xunif_wdrain ! uniform value of subgrid drainage coefficient
303 punif_perm = xunif_perm ! uniform value of permafrost distribution
304 punif_gw = xunif_gw ! uniform value of groundwater distribution
305 oimp_sand = limp_sand ! Imposed values for SAND
306 oimp_clay = limp_clay ! Imposed values for CLAY
307 oimp_soc = limp_soc ! Imposed values for organic carbon
308 oimp_cti = limp_cti ! Imposed values for topographic index statistics
309 oimp_perm = limp_perm ! Imposed values for permafrost distribution
310 omeb = lmeb ! MEB
311 oimp_gw = limp_gw ! Imposed values for groundwater distribution
312 !
313 hph = yph ! file name for pH value
314 hfert = yfert ! file name for fertilisation data
315 hphfiletype = yphfiletype ! pH data file type
316 hfertfiletype = yfertfiletype ! Fertilisation data file type
317 punif_ph = xunif_ph ! uniform value of pH
318 punif_fert = xunif_fert ! uniform value of fertilisation rate
319 !
320 IF (lhook) CALL dr_hook('READ_NAM_PGD_ISBA',1,zhook_handle)
321 !
322 !-------------------------------------------------------------------------------
323 !
324 END SUBROUTINE read_nam_pgd_isba
subroutine read_nam_pgd_isba(HPROGRAM, KPATCH, KGROUND_LAYER, HISBA, HPEDOTF, HPHOTO, OTR_ML, PRM_PATCH, HCLAY, HCLAYFILETYPE, PUNIF_CLAY, OIMP_CLAY, HSAND, HSANDFILETYPE, PUNIF_SAND, OIMP_SAND, HSOC_TOP, HSOC_SUB, HSOCFILETYPE, PUNIF_SOC_TOP, PUNIF_SOC_SUB, OIMP_SOC, HCTI, HCTIFILETYPE, OIMP_CTI, HPERM, HPERMFILETYPE, PUNIF_PERM, OIMP_PERM, OMEB, HGW, HGWFILETYPE, PUNIF_GW, OIMP_GW, HRUNOFFB, HRUNOFFBFILETYPE, PUNIF_RUNOFFB, HWDRAIN, HWDRAINFILETYPE, PUNIF_WDRAIN, PSOILGRID, HPH, HPHFILETYPE, PUNIF_PH, HFERT, HFERTFILETYPE, PUNIF_FERT)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)