SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_pgd_teb_greenroof_parn.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 ! #########
7  dtgr, tgro, tg, &
8  hprogram)
9 ! ################################################
10 !
11 !!**** *READ_PGD_TEB_GREENROOF_PAR_n* - reads ISBA physiographic fields
12 !!
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! V. Masson *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 01/2003
38 !! P. Le Moigne 12/2004 : add type of photosynthesis
39 !! C. de Munck 02/2012 : added parameterisation for sedum species under NVT_TROG
40 !-------------------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 !
46 !
47 !
48 !
51 USE modd_teb_grid_n, ONLY : teb_grid_t
52 !
53 USE modd_csts, ONLY : xday
54 USE modd_surf_par, ONLY : xundef
55 USE modd_data_cover_par, ONLY : nvegtype, nvt_gras, nvt_trog
56 !paramètres ci-dessus à initialiser pour les GR (sauf XPAR_OM_GR, XPAR_SAND_GR, XPAR_CLAY_GR qui sont lues)
57 USE modd_prep_teb_greenroof, ONLY : ngrid_level, xgrid_soil
58 !
65 !
66 !
67 USE yomhook ,ONLY : lhook, dr_hook
68 USE parkind1 ,ONLY : jprb
69 !
70 IMPLICIT NONE
71 !
72 !* 0.1 Declarations of arguments
73 ! -------------------------
74 !
75 !
76 !
77 !
78 TYPE(data_teb_greenroof_t), INTENT(INOUT) :: dtgr
79 TYPE(teb_greenroof_options_t), INTENT(INOUT) :: tgro
80 TYPE(teb_grid_t), INTENT(INOUT) :: tg
81 !
82  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
83 !
84 !* 0.2 Declarations of local variables
85 ! -------------------------------
86 !
87 INTEGER :: iresp ! IRESP : return-code if a problem appears
88  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
89  CHARACTER(LEN=100) :: ycomment ! Comment string
90 INTEGER :: ji ! loop index
91 INTEGER :: jtime ! loop index
92 INTEGER :: jlayer ! loop index
93 !
94 REAL, DIMENSION(TG%NDIM) :: zdata_wg1
95 REAL, DIMENSION(TG%NDIM) :: zdata_wgsat
96 !
97 LOGICAL :: gagri_to_grass
98 !
99 REAL(KIND=JPRB) :: zhook_handle
100 !
101 !-------------------------------------------------------------------------------
102 !
103 !* 1. Reading of PGD file
104 ! --------------------
105 !
106 IF (lhook) CALL dr_hook('READ_PGD_TEB_GREENROOF_PAR_N',0,zhook_handle)
107 !
108 gagri_to_grass=.false.
109 !
110 yrecfm='GR_NTIME'
111  CALL read_surf(&
112  hprogram,yrecfm,tgro%NTIME_GR,iresp)
113 !
114 yrecfm='GR_LAYER'
115  CALL read_surf(&
116  hprogram,yrecfm,tgro%NLAYER_GR,iresp)
117 !
118 ! Read type of green roof
119 yrecfm='D_TYPE_GR'
120  CALL read_surf(&
121  hprogram,yrecfm,tgro%CTYP_GR,iresp)
122 !
123 ! Read green roof OM fraction
124 ALLOCATE(dtgr%XPAR_OM_GR (tg%NDIM,tgro%NLAYER_GR))
125 DO jlayer=1,tgro%NLAYER_GR
126  !WRITE(YRECFM,FMT='(A8,I1.1)') 'D_OM_GR0',JLAYER
127  WRITE(yrecfm,fmt='(A7,I2.2)') 'D_OM_GR',jlayer
128  CALL read_surf(&
129  hprogram,yrecfm,dtgr%XPAR_OM_GR(:,jlayer),iresp,hcomment=ycomment)
130 END DO
131 !
132 ! Read green roof SAND fraction
133 ALLOCATE(dtgr%XPAR_SAND_GR (tg%NDIM,tgro%NLAYER_GR))
134 DO jlayer=1,tgro%NLAYER_GR
135  !WRITE(YRECFM,FMT='(A10,I1.1)') 'D_SAND_GR0',JLAYER
136  WRITE(yrecfm,fmt='(A9,I2.2)') 'D_SAND_GR',jlayer
137  CALL read_surf(&
138  hprogram,yrecfm,dtgr%XPAR_SAND_GR(:,jlayer),iresp,hcomment=ycomment)
139 END DO
140 !
141 ! Read green roof CLAY fraction
142 ALLOCATE(dtgr%XPAR_CLAY_GR (tg%NDIM,tgro%NLAYER_GR))
143 DO jlayer=1,tgro%NLAYER_GR
144  !WRITE(YRECFM,FMT='(A10,I1.1)') 'D_CLAY_GR0',JLAYER
145  WRITE(yrecfm,fmt='(A9,I2.2)') 'D_CLAY_GR',jlayer
146  CALL read_surf(&
147  hprogram,yrecfm,dtgr%XPAR_CLAY_GR(:,jlayer),iresp,hcomment=ycomment)
148 END DO
149 !
150 ! Read green roof LAI
151 ALLOCATE(dtgr%XPAR_LAI_GR (tg%NDIM,tgro%NTIME_GR))
152 DO jtime=1,tgro%NTIME_GR
153  WRITE(yrecfm,fmt='(A8,I2.2)') 'D_LAI_GR',jtime
154  CALL read_surf(&
155  hprogram,yrecfm,dtgr%XPAR_LAI_GR(:,jtime),iresp,hcomment=ycomment)
156 END DO
157 !
158 !
159 !-------------------------------------------------------------------------------
160 !
161 !* 2. Definition of ISBA parameters
162 ! -----------------------------
163 !
164 ALLOCATE(dtgr%XPAR_LAI (tg%NDIM,tgro%NTIME_GR))
165 ALLOCATE(dtgr%XPAR_VEG (tg%NDIM,tgro%NTIME_GR))
166 ALLOCATE(dtgr%XPAR_RSMIN (tg%NDIM))
167 ALLOCATE(dtgr%XPAR_GAMMA (tg%NDIM))
168 ALLOCATE(dtgr%XPAR_WRMAX_CF (tg%NDIM))
169 ALLOCATE(dtgr%XPAR_RGL (tg%NDIM))
170 ALLOCATE(dtgr%XPAR_CV (tg%NDIM))
171 ALLOCATE(dtgr%XPAR_DG (tg%NDIM,tgro%NLAYER_GR))
172 ALLOCATE(dtgr%XPAR_ROOTFRAC (tg%NDIM,tgro%NLAYER_GR))
173 ALLOCATE(dtgr%XPAR_DICE (tg%NDIM))
174 ALLOCATE(dtgr%XPAR_Z0 (tg%NDIM,tgro%NTIME_GR))
175 ALLOCATE(dtgr%XPAR_Z0_O_Z0H (tg%NDIM))
176 ALLOCATE(dtgr%XPAR_ALBNIR_VEG (tg%NDIM))
177 ALLOCATE(dtgr%XPAR_ALBVIS_VEG (tg%NDIM))
178 ALLOCATE(dtgr%XPAR_ALBUV_VEG (tg%NDIM))
179 ALLOCATE(dtgr%XPAR_ALBNIR_SOIL(tg%NDIM))
180 ALLOCATE(dtgr%XPAR_ALBVIS_SOIL(tg%NDIM))
181 ALLOCATE(dtgr%XPAR_ALBUV_SOIL (tg%NDIM))
182 ALLOCATE(dtgr%XPAR_ALBNIR_DRY (tg%NDIM))
183 ALLOCATE(dtgr%XPAR_ALBVIS_DRY (tg%NDIM))
184 ALLOCATE(dtgr%XPAR_ALBUV_DRY (tg%NDIM))
185 ALLOCATE(dtgr%XPAR_ALBNIR_WET (tg%NDIM))
186 ALLOCATE(dtgr%XPAR_ALBVIS_WET (tg%NDIM))
187 ALLOCATE(dtgr%XPAR_ALBUV_WET (tg%NDIM))
188 ALLOCATE(dtgr%XPAR_EMIS (tg%NDIM,tgro%NTIME_GR))
189 ALLOCATE(dtgr%XPAR_VEGTYPE (tg%NDIM,nvegtype))
190 ALLOCATE(dtgr%XPAR_GMES (tg%NDIM))
191 ALLOCATE(dtgr%XPAR_RE25 (tg%NDIM))
192 ALLOCATE(dtgr%XPAR_BSLAI (tg%NDIM))
193 ALLOCATE(dtgr%XPAR_LAIMIN (tg%NDIM))
194 ALLOCATE(dtgr%XPAR_SEFOLD (tg%NDIM))
195 ALLOCATE(dtgr%XPAR_GC (tg%NDIM))
196 ALLOCATE(dtgr%XPAR_DMAX (tg%NDIM))
197 ALLOCATE(dtgr%XPAR_F2I (tg%NDIM))
198 ALLOCATE(dtgr%LDATA_STRESS (tg%NDIM))
199 ALLOCATE(dtgr%XPAR_H_TREE (tg%NDIM))
200 ALLOCATE(dtgr%XPAR_CE_NITRO (tg%NDIM))
201 ALLOCATE(dtgr%XPAR_CF_NITRO (tg%NDIM))
202 ALLOCATE(dtgr%XPAR_CNA_NITRO (tg%NDIM))
203 !
204 dtgr%XPAR_LAI (:,:) = xundef
205 dtgr%XPAR_VEG (:,:) = xundef
206 dtgr%XPAR_RSMIN (:) = xundef
207 dtgr%XPAR_GAMMA (:) = xundef
208 dtgr%XPAR_WRMAX_CF (:) = xundef
209 dtgr%XPAR_RGL (:) = xundef
210 dtgr%XPAR_CV (:) = xundef
211 dtgr%XPAR_DG (:,:) = xundef
212 dtgr%XPAR_DICE (:) = xundef
213 dtgr%XPAR_ROOTFRAC (:,:) = xundef
214 dtgr%XPAR_Z0 (:,:) = xundef
215 dtgr%XPAR_Z0_O_Z0H (:) = xundef
216 dtgr%XPAR_ALBNIR_VEG (:) = xundef
217 dtgr%XPAR_ALBVIS_VEG (:) = xundef
218 dtgr%XPAR_ALBUV_VEG (:) = xundef
219 dtgr%XPAR_ALBNIR_SOIL (:) = xundef
220 dtgr%XPAR_ALBVIS_SOIL (:) = xundef
221 dtgr%XPAR_ALBUV_SOIL (:) = xundef
222 dtgr%XPAR_ALBNIR_DRY (:) = xundef
223 dtgr%XPAR_ALBVIS_DRY (:) = xundef
224 dtgr%XPAR_ALBUV_DRY (:) = xundef
225 dtgr%XPAR_ALBNIR_WET (:) = xundef
226 dtgr%XPAR_ALBVIS_WET (:) = xundef
227 dtgr%XPAR_ALBUV_WET (:) = xundef
228 dtgr%XPAR_EMIS (:,:) = xundef
229 dtgr%XPAR_VEGTYPE (:,:) = xundef
230 dtgr%XPAR_GMES (:) = xundef
231 dtgr%XPAR_RE25 (:) = xundef
232 dtgr%XPAR_BSLAI (:) = xundef
233 dtgr%XPAR_LAIMIN (:) = xundef
234 dtgr%XPAR_SEFOLD (:) = xundef
235 dtgr%XPAR_GC (:) = xundef
236 dtgr%XPAR_DMAX (:) = xundef
237 dtgr%XPAR_F2I (:) = xundef
238 dtgr%LDATA_STRESS (:) = .false.
239 dtgr%XPAR_H_TREE (:) = xundef
240 dtgr%XPAR_CE_NITRO (:) = xundef
241 dtgr%XPAR_CF_NITRO (:) = xundef
242 dtgr%XPAR_CNA_NITRO (:) = xundef
243 !
244 !---------------------------------------------------------------------------
245 ! Vegtypes adapted to greenroofs:
246 !--------------------------------
247 ! NPATCH = 1
248 ! 2D cases : all greenroofs have same vegetation (defined by CTYP_GR)
249 ! (CTYP_GR == 'GRASS') <=> NVT_GRAS (10)
250 ! ** OR **
251 ! (CTYP_GR == 'SEDUM') <=> NVT_TROG (11)
252 ! NB1: => no aggregation of vegetype parameters needed
253 ! NB2: Functions existing for gardens are used for initial greenroofs
254 ! This will need to be refined specifically for greenroofs
255 !
256 dtgr%XPAR_VEGTYPE(:,:) = 0.
257 IF (tgro%CTYP_GR == 'GRASS') dtgr%XPAR_VEGTYPE(:, nvt_gras) = 1.
258 IF (tgro%CTYP_GR == 'SEDUM') dtgr%XPAR_VEGTYPE(:, nvt_trog) = 1.
259 !--------------------------------------------------------------------------
260 !
261 ! Dry/Wet soil albedos: (* Will need to account for XOM_GR eventually *)
262 !CALL DRY_WET_SOIL_ALBEDOS_1D(XSAND_GR(:,1),XCLAY_GR(:,1), &
263  CALL dry_wet_soil_albedos_1d(dtgr%XPAR_SAND_GR(:,1),dtgr%XPAR_CLAY_GR(:,1), &
264  dtgr%XPAR_VEGTYPE, &
265  dtgr%XPAR_ALBNIR_DRY,dtgr%XPAR_ALBVIS_DRY,dtgr%XPAR_ALBUV_DRY, &
266  dtgr%XPAR_ALBNIR_WET,dtgr%XPAR_ALBVIS_WET,dtgr%XPAR_ALBUV_WET )
267 !
268 ! Critical normilized soil water content for stress parameterisation
269 dtgr%XPAR_F2I(:) = 0.3
270 !
271 ! Ratio between roughness length for momentum and heat
272 dtgr%XPAR_Z0_O_Z0H(:) = 10.
273 !
274 ! Defensive/offensive strategy (1/0)
275 dtgr%LDATA_STRESS(:) = .false.
276 !
277 DO ji=1,tg%NDIM
278 !
279 ! Vegetation albedo: near-IR, visible, and UV albedo
280 ! * Will need to be adapted to greenroof GRASS and SEDUM species *
281 ! * vérifier si/où l'abedo ds l'UV est utilisé *
282  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_ALBNIR_VEG(ji)= 0.3
283  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_ALBNIR_VEG(ji)= 0.154 ! mesures ONERA/Doya (2011)
284 
285  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_ALBVIS_VEG(ji)= 0.10
286  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_ALBVIS_VEG(ji)= 0.154 ! mesures ONERA/Doya (2011)
287 
288  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_ALBUV_VEG(ji) = 0.0800
289  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_ALBUV_VEG(ji) = 0.1250
290 !
291 ! Soil albedo (* Will need to be refined for greenroofs - cf OM fraction *)
292  zdata_wgsat(:) = 0.
293  zdata_wg1(:) = 0.
294  CALL soil_albedo('DRY', &
295  zdata_wgsat, zdata_wg1, &
296  dtgr%XPAR_ALBVIS_DRY, dtgr%XPAR_ALBNIR_DRY, dtgr%XPAR_ALBUV_DRY, &
297  dtgr%XPAR_ALBVIS_WET, dtgr%XPAR_ALBNIR_WET, dtgr%XPAR_ALBUV_WET, &
298  dtgr%XPAR_ALBVIS_SOIL,dtgr%XPAR_ALBNIR_SOIL,dtgr%XPAR_ALBUV_SOIL )
299 !
300 ! Min stomatal resistance
301  !IF(XPAR_VEGTYPE(JI,NVT_GRAS)>0. ) XPAR_RSMIN(JI)= 40 (dans isba & garden)
302  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_RSMIN(ji)= 120 ! for GRASS
303  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_RSMIN(ji)= 150. ! for SEDUM
304  !IF(XPAR_VEGTYPE(JI,NVT_TROG)>0. ) XPAR_RSMIN(JI)= 120.
305 !
306 ! Gamma parameter
307 ! (* Check if values needs to be refined for GRASS and SEDUM *)
308  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_GAMMA(ji)= 0.
309  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_GAMMA(ji)= 0.
310 !
311 ! Wrmax_cf
312 ! (* Check if needs to be refined for GRASS and SEDUM greenroofs *)
313  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_WRMAX_CF(ji)= 0.2
314  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_WRMAX_CF(ji)= 0.2
315 !
316 ! Rgl
317 ! (* Check if needs to be refined for GRASS and SEDUM greenroofs *)
318  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_RGL(ji)= 100.
319  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_RGL(ji)= 100.
320 !
321 ! Cv
322 ! (* Check if needs to be refined for GRASS and SEDUM greenroofs *)
323  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_CV(ji)= 2.e-5
324  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_CV(ji)= 2.e-5
325 !
326 !! Mesophyll conductance (m s-1)
327 ! (* Check if needs to be refined for GRASS and SEDUM greenroofs *)
328  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_GMES(ji)= 0.020
329  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_GMES(ji)= 0.020
330  !IF(XPAR_VEGTYPE(JI,NVT_TROG)>0. ) XPAR_GMES(JI)= 0.003
331 !
332 ! Ecosystem Respiration (kg/kg.m.s-1)
333 ! (* Check if needs to be refined for GRASS and SEDUM greenroofs *)
334  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_RE25(ji)= 3.0e-7
335  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog )>0.) dtgr%XPAR_RE25(ji)= 3.0e-7
336 !
337 ! Cuticular conductance (m s-1)
338  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_GC(ji)= 0.00025
339  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_GC(ji)= 0.00025
340 !
341 ! Ratio d(biomass)/d(lai) (kg/m2)
342  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_BSLAI(ji)= 0.36
343  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_BSLAI(ji)= 0.06
344 !
345 ! Maximum air saturation deficit tolerate by vegetation (kg/kg)
346  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_DMAX(ji)= 0.1
347  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_DMAX(ji)= 0.1
348 !
349 ! e-folding time for senescence (days)
350  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_SEFOLD(ji)= 90.* xday
351  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_SEFOLD(ji)= 60.* xday
352 !
353 ! Minimum LAI (m2/m2)
354  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_LAIMIN (ji) = 0.3
355  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_LAIMIN (ji) = 0.3
356 !
357 ! Leaf aera ratio sensitivity to nitrogen concentration
358  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_CE_NITRO(ji)= 5.56
359  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_CE_NITRO(ji)= 3.79
360 !
361 ! Lethal minimum value of leaf area ratio
362  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_CF_NITRO(ji)= 6.73
363  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_CF_NITRO(ji)= 9.84
364 !
365 ! Nitrogen concentration of active biomass
366  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_CNA_NITRO(ji)= 1.9
367  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog )>0.) dtgr%XPAR_CNA_NITRO(ji)= 1.3
368 !
369 ! Depth of greenroof ground layers
370  dtgr%XPAR_DG(ji, 1) = xgrid_soil(ngrid_level - 5)
371  dtgr%XPAR_DG(ji, 2) = xgrid_soil(ngrid_level - 4)
372  dtgr%XPAR_DG(ji, 3) = xgrid_soil(ngrid_level - 3)
373  dtgr%XPAR_DG(ji, 4) = xgrid_soil(ngrid_level - 2)
374  dtgr%XPAR_DG(ji, 5) = xgrid_soil(ngrid_level - 1)
375  dtgr%XPAR_DG(ji, 6) = xgrid_soil(ngrid_level - 0)
376 !
377 ! Root fractions
378  dtgr%XPAR_ROOTFRAC(ji, 1) = 0.04
379  dtgr%XPAR_ROOTFRAC(ji, 2) = 0.36
380  dtgr%XPAR_ROOTFRAC(ji, 3) = 0.68
381  dtgr%XPAR_ROOTFRAC(ji, 4) = 1.
382  dtgr%XPAR_ROOTFRAC(ji, 5) = 1.
383  dtgr%XPAR_ROOTFRAC(ji, 6) = 1.
384 !
385 ! Depth of the soil column for the calculation of the frozen soil fraction (m)
386  dtgr%XPAR_DICE(ji) = dtgr%XPAR_DG(ji,1)
387 !
388 DO jtime=1,tgro%NTIME_GR
389 ! Leaf Area Index
390  dtgr%XPAR_LAI(ji,jtime) = dtgr%XPAR_LAI_GR(ji,jtime)
391 
392 ! Fraction of vegetation on greenroof
393 !* Will need to be refined for greenroofs *)
394  !XPAR_VEG (JI,1,JTIME) = VEG_FROM_LAI (XPAR_LAI_GR(JI,JTIME), &
395  ! XPAR_VEGTYPE(JI,:),GAGRI_TO_GRASS)
396  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_VEG (ji,jtime) = 0.9
397  !IF(XPAR_VEGTYPE(JI,NVT_TROG)>0. ) XPAR_VEG (JI,JTIME) = 1.0
398  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_VEG (ji,jtime) = 0.95
399 
400 ! Roughness length for momentum
401 !* Will need to be refined for greenroofs *)
402  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_Z0 (ji,jtime) = 0.01
403  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_Z0 (ji,jtime) = 0.01
404  !
405 ! Emissivity
406 !* Will need to be refined for greenroofs *)
407  !XPAR_EMIS (JI,1,JTIME) = EMIS_FROM_VEG (XPAR_VEG (JI,1,JTIME),&
408  ! XPAR_VEGTYPE(JI,:))
409  IF(dtgr%XPAR_VEGTYPE(ji,nvt_gras)>0. ) dtgr%XPAR_EMIS (ji,jtime) = 0.95
410  IF(dtgr%XPAR_VEGTYPE(ji,nvt_trog)>0. ) dtgr%XPAR_EMIS (ji,jtime) = 0.83 ! Feng. et al. (2010)
411 
412 END DO
413 !
414 ENDDO
415 !
416 IF (lhook) CALL dr_hook('READ_PGD_TEB_GREENROOF_PAR_N',1,zhook_handle)
417 !
418 !-------------------------------------------------------------------------------
419 !
420 END SUBROUTINE read_pgd_teb_greenroof_par_n
subroutine read_pgd_teb_greenroof_par_n(DTGR, TGRO, TG, HPROGRAM)
subroutine dry_wet_soil_albedos_1d(PSAND, PCLAY, PVEGTYPE, PALBNIR_DRY, PALBVIS_DRY, PALBUV_DRY, PALBNIR_WET, PALBVIS_WET, PALBUV_WET)