SURFEX v8.1
General documentation of Surfex
prep_hor_teb_greenroof_field.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 prep_hor_teb_greenroof_field (DTCO, UG, U, USS, GCP, IO, S, K, P, PEK, TG, TOP, &
7  HPROGRAM,HSURF,HATMFILE,HATMFILETYPE,HPGDFILE,HPGDFILETYPE,KPATCH,YDCTL)
8 ! #################################################################################################
9 !
10 !!**** *PREP_HOR_TEB_GREENROOF_FIELD* - reads, interpolates and prepares an ISBA field for green roofs
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! Based on "prep_hor_teb_garden_field"
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !!
24 !! AUTHOR
25 !! ------
26 !! V. Masson, A. Lemonsu & C. de Munck
27 !!
28 !! MODIFICATIONS
29 !! -------------
30 !! Original 07/2011
31 !! P. Marguinaud 10/2014, Support for a 2-part PREP
32 !!------------------------------------------------------------------
33 !
34 !
37 USE modd_surf_atm_n, ONLY : surf_atm_t
38 USE modd_sso_n, ONLY : sso_t
40 !
43 !
44 USE modd_sfx_grid_n, ONLY : grid_t
46 !
49 USE modd_grid_grib, ONLY : cinmodel
50 USE modd_surfex_mpi, ONLY : nrank, npio, ncomm, nproc
52 USE modd_prep_teb_greenroof, ONLY : xgrid_soil, ngrid_level, &
53  xwsnow_gr, xrsnow_gr, xtsnow_gr,xlwcsnow_gr, &
54  xagesnow_gr, xasnow_gr, lsnow_ideal_gr
55 USE modd_isba_par, ONLY : xwgmin
56 USE modd_data_cover_par, ONLY : nvegtype
57 USE modd_surf_par, ONLY : xundef
58 !
60 !
61 USE modi_prep_grib_grid
62 USE modi_read_prep_teb_greenroof_conf
63 USE modi_read_prep_greenroof_snow
64 USE modi_prep_teb_greenroof_ascllv
65 USE modi_prep_teb_greenroof_grib
66 USE modi_prep_teb_greenroof_unif
67 USE modi_prep_teb_greenroof_buffer
68 USE modi_hor_interpol
69 USE modi_vegtype_grid_to_patch_grid
70 USE modi_prep_hor_snow_fields
71 USE modi_get_luout
72 USE modi_prep_teb_greenroof_extern
73 USE modi_put_on_all_vegtypes
74 USE modi_allocate_gr_snow
75 !
76 USE modi_abor1_sfx
77 !
78 USE yomhook ,ONLY : lhook, dr_hook
79 USE parkind1 ,ONLY : jprb
80 !
81 IMPLICIT NONE
82 !
83 #ifdef SFX_MPI
84 include "mpif.h"
85 #endif
86 !
87 !* 0.1 declarations of arguments
88 !
89 !
90 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
91 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
92 TYPE(surf_atm_t), INTENT(INOUT) :: U
93 TYPE(sso_t), INTENT(INOUT) :: USS
94 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
95 !
96 TYPE(isba_options_t), INTENT(INOUT) :: IO
97 TYPE(isba_s_t), INTENT(INOUT) :: S
98 TYPE(isba_k_t), INTENT(INOUT) :: K
99 TYPE(isba_p_t), INTENT(INOUT) :: P
100 TYPE(isba_pe_t), INTENT(INOUT) :: PEK
101 !
102 TYPE(grid_t), INTENT(INOUT) :: TG
103 TYPE(teb_options_t), INTENT(INOUT) :: TOP
104 type(prep_ctl), INTENT(INOUT) :: ydctl
105 !
106  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
107  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
108  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! name of the Atmospheric file
109  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! type of the Atmospheric file
110  CHARACTER(LEN=28), INTENT(IN) :: HPGDFILE ! name of the Atmospheric file
111  CHARACTER(LEN=6), INTENT(IN) :: HPGDFILETYPE! type of the Atmospheric file
112 !
113 INTEGER, INTENT(IN) :: KPATCH
114 !
115 !* 0.2 declarations of local variables
116 !
117  CHARACTER(LEN=6) :: YFILETYPE ! type of input file
118  CHARACTER(LEN=28) :: YFILE ! name of file
119  CHARACTER(LEN=6) :: YFILEPGDTYPE ! type of input file
120  CHARACTER(LEN=28) :: YFILEPGD ! name of file
121  CHARACTER(LEN=6) :: YFILETYPE_SNOW ! type of input file
122  CHARACTER(LEN=28) :: YFILE_SNOW ! name of file
123  CHARACTER(LEN=6) :: YFILEPGDTYPE_SNOW ! type of input file
124  CHARACTER(LEN=28) :: YFILEPGD_SNOW ! name of file
125 REAL, POINTER, DIMENSION(:,:,:) :: ZFIELDIN=>null() ! field to interpolate horizontally
126 !
127 TYPE(nsurf_snow) :: TNPSNOW
128 !
129 REAL, ALLOCATABLE, DIMENSION(:,:,:) :: ZFIELDOUTP ! field interpolated horizontally
130 REAL, ALLOCATABLE, DIMENSION(:,:,:) :: ZFIELDOUTV !
131 REAL, ALLOCATABLE, DIMENSION(:,:,:) :: ZVEGTYPE_PATCH ! vegtype for each patch
132 REAL, ALLOCATABLE, DIMENSION(:,:) :: ZW ! work array (x, fine soil grid, npatch)
133 REAL, ALLOCATABLE, DIMENSION(:,:) :: ZF ! work array (x, output soil grid, npatch)
134 REAL, ALLOCATABLE, DIMENSION(:,:) :: ZDG ! out T grid (x, output soil grid, npatch)
135 REAL, ALLOCATABLE, DIMENSION(:,:) :: ZPATCH ! work array for patches
136 REAL, ALLOCATABLE, DIMENSION(:) :: ZSG1SNOW, ZSG2SNOW, ZHISTSNOW
137 INTEGER :: ILUOUT ! output listing logical unit
138 !
139 type(date_time) :: tztime_grib ! current date and time
140 LOGICAL :: GUNIF ! flag for prescribed uniform field
141 LOGICAL :: GUNIF_SNOW ! flag for prescribed uniform field
142 INTEGER :: JVEGTYPE, JPATCH ! loop on vegtypes
143 INTEGER :: JLAYER ! loop on layers
144 INTEGER :: INI, INL, INP
145 INTEGER :: IWORK ! Work integer
146 INTEGER :: INFOMPI
147 REAL(KIND=JPRB) :: ZHOOK_HANDLE
148 !-------------------------------------------------------------------------------------
149 !
150 !
151 !* 1. Reading of input file name and type
152 !
153 IF (lhook) CALL dr_hook('PREP_HOR_TEB_GREENROOF_FIELD',0,zhook_handle)
154 !
155 IF (.NOT. prep_ctl_can(ydctl)) THEN
156  CALL abor1_sfx('PREP_HOR_TEB_GREENROOF_FIELD: TWO STEP PREP NOT IMPLEMENTED')
157 ENDIF
158 !
159  CALL get_luout(hprogram,iluout)
160 !
161  CALL read_prep_teb_greenroof_conf(hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,&
162  hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,iluout,gunif)
163 !
164 cmask = 'TOWN '
165 !
166 ini=SIZE(tg%XLAT)
167 !
168 !-------------------------------------------------------------------------------------
169 !* 2. Snow variables case
170 !
171 IF (hsurf=='SN_VEG ') THEN
172  CALL read_prep_greenroof_snow(hprogram,pek%TSNOW%SCHEME,pek%TSNOW%NLAYER,yfile_snow,&
173  yfiletype_snow,yfilepgd_snow,yfilepgdtype_snow,gunif_snow)
174  !
175  IF(.NOT.gunif_snow.AND.len_trim(yfile_snow)==0.AND.len_trim(yfiletype_snow)==0)THEN
176  !IF(LEN_TRIM(YFILE)/=0.AND.LEN_TRIM(YFILETYPE)/=0)THEN
177  IF (yfiletype=='GRIB') THEN
178  yfile_snow = yfile
179  yfiletype_snow = yfiletype
180  yfilepgd_snow = yfilepgd
181  yfilepgdtype_snow = yfilepgdtype
182  ELSE
183  gunif_snow=.true.
184  IF(all(xwsnow_gr==xundef))xwsnow_gr=0.0
185  ENDIF
186  ENDIF
187  !
188  ALLOCATE(zsg1snow(SIZE(xwsnow_gr)))
189  ALLOCATE(zsg2snow(SIZE(xwsnow_gr)))
190  ALLOCATE(zhistsnow(SIZE(xwsnow_gr)))
191  !
192  ALLOCATE(tnpsnow%AL(1))
193  tnpsnow%AL(1)%SCHEME = pek%TSNOW%SCHEME
194  tnpsnow%AL(1)%NLAYER = pek%TSNOW%NLAYER
195  !
196  CALL prep_hor_snow_fields(dtco, tg, u, gcp, hprogram,hsurf, &
197  yfile,yfiletype, &
198  yfilepgd, yfilepgdtype, &
199  iluout,gunif_snow, 1, kpatch, &
200  ini, tnpsnow, top%TTIME, &
201  xwsnow_gr, xrsnow_gr, xtsnow_gr,&
202  xlwcsnow_gr, xasnow_gr, &
203  lsnow_ideal_gr, zsg1snow, &
204  zsg2snow, zhistsnow, xagesnow_gr, ydctl, &
205  pvegtype_patch=s%XVEGTYPE_PATCH, ppatch=s%XPATCH )
206  !
207  CALL allocate_gr_snow(pek%TSNOW,ini)
208  pek%TSNOW%WSNOW = tnpsnow%AL(1)%WSNOW
209  pek%TSNOW%RHO = tnpsnow%AL(1)%RHO
210  pek%TSNOW%ALB = tnpsnow%AL(1)%ALB
211  IF (pek%TSNOW%SCHEME/='D95') pek%TSNOW%HEAT = tnpsnow%AL(1)%HEAT
212  IF (pek%TSNOW%SCHEME=='CRO'.OR.pek%TSNOW%SCHEME=='3-L') &
213  pek%TSNOW%AGE = tnpsnow%AL(1)%AGE
214  IF (pek%TSNOW%SCHEME=='CRO') THEN
215  pek%TSNOW%GRAN1 = tnpsnow%AL(1)%GRAN1
216  pek%TSNOW%GRAN2 = tnpsnow%AL(1)%GRAN2
217  pek%TSNOW%HIST = tnpsnow%AL(1)%HIST
218  ENDIF
219  !
220  DEALLOCATE(zsg1snow)
221  DEALLOCATE(zsg2snow)
222  DEALLOCATE(zhistsnow)
223  IF (lhook) CALL dr_hook('PREP_HOR_TEB_GREENROOF_FIELD',1,zhook_handle)
224  RETURN
225 END IF
226 !
227 !-------------------------------------------------------------------------------------
228 !
229 !* 3. Reading of input configuration (Grid and interpolation type)
230 !
231 IF (gunif) THEN
232  CALL prep_teb_greenroof_unif(iluout,hsurf,zfieldin)
233 ELSE IF (yfiletype=='ASCLLV') THEN
234  CALL prep_teb_greenroof_ascllv(dtco, ug, u, uss, hprogram,hsurf,iluout,zfieldin)
235 ELSE IF (yfiletype=='GRIB ') THEN
236  CALL prep_grib_grid(yfile,iluout,cinmodel,cingrid_type,cinterp_type,tztime_grib)
237  IF (nrank==npio) CALL prep_teb_greenroof_grib(hprogram,hsurf,yfile,iluout,zfieldin)
238 ELSE IF (yfiletype=='MESONH' .OR. yfiletype=='ASCII ' .OR. yfiletype=='LFI '&
239  .OR. yfiletype=='FA '.OR. yfiletype=='AROME '.OR.yfiletype=='NC ') THEN
240  CALL prep_teb_greenroof_extern(dtco, io, u, gcp, &
241  hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,iluout,kpatch,zfieldin)
242 ELSE IF (yfiletype=='BUFFER') THEN
243  CALL prep_teb_greenroof_buffer(hprogram,hsurf,iluout,zfieldin)
244 ELSE
245  CALL abor1_sfx('PREP_HOR_TEB_GREENROOF_FIELD: data file type not supported : '//yfiletype)
246 END IF
247 !
248 !-------------------------------------------------------------------------------------
249 !
250 !* 5. Horizontal interpolation for vegtype grid
251 !
252 IF (nrank==npio) THEN
253  inl = SIZE(zfieldin,2)
254  inp = SIZE(zfieldin,3)
255 ELSE
256  IF (.NOT.ASSOCIATED(zfieldin)) ALLOCATE(zfieldin(0,0,0))
257 ENDIF
258 !
259 IF (nproc>1) THEN
260 #ifdef SFX_MPI
261  CALL mpi_bcast(inl,kind(inl)/4,mpi_integer,npio,ncomm,infompi)
262  CALL mpi_bcast(inp,kind(inp)/4,mpi_integer,npio,ncomm,infompi)
263 #endif
264 ENDIF
265 !
266 ALLOCATE(zfieldoutp(ini,inl,inp))
267 !
268 DO jpatch = 1, inp
269  IF (inp==nvegtype) linterp = (s%XVEGTYPE(:,jpatch) > 0.)
270  CALL hor_interpol(dtco, u, gcp, iluout,zfieldin(:,:,jpatch),zfieldoutp(:,:,jpatch))
271  linterp = .true.
272 END DO
273 !
274 DEALLOCATE(zfieldin )
275 !
276 ALLOCATE(zw(ini,inl))
277 zw = 0.
278 !
279 IF (1/=inp) THEN
280  !
281  ALLOCATE(zfieldoutv(ini,inl,nvegtype))
282  CALL put_on_all_vegtypes(ini,inl,inp,nvegtype,zfieldoutp,zfieldoutv)
283  !
284  DO jvegtype=1,nvegtype
285  DO jlayer=1,SIZE(zw,2)
286  zw(:,jlayer) = zw(:,jlayer) + s%XVEGTYPE(:,jvegtype) * zfieldoutv(:,jlayer,jvegtype)
287  END DO
288  END DO
289  DEALLOCATE(zfieldoutv)
290  !
291 ELSE
292  !
293  zw(:,:) = zfieldoutp(:,:,1)
294  !
295 ENDIF
296 !
297 DEALLOCATE(zfieldoutp)
298 !
299 !-------------------------------------------------------------------------------------
300 !
301 !* 6. Transformation from vegtype grid to patch grid
302 !
303 !
304 !* 8. Deallocations
305 !
306 !-------------------------------------------------------------------------------------
307 !
308 !* 7. Return to historical variable
309 !
310 !
311 SELECT CASE (hsurf)
312  !
313  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
314  !
315  CASE('WG ')
316  ALLOCATE(zf(ini,io%NGROUND_LAYER))
317  !
318  !* interpolates on output levels
319  CALL init_from_ref_grid(xgrid_soil,zw,p%XDG(:,:),zf)
320 
321  !
322  !* retrieves soil water content from soil relative humidity
323  ALLOCATE(pek%XWG(ini,io%NGROUND_LAYER))
324  pek%XWG(:,:) = k%XWWILT + zf(:,:) * (k%XWFC-k%XWWILT)
325  pek%XWG(:,:) = max(min(pek%XWG(:,:),k%XWSAT),xwgmin)
326  !
327  WHERE(zf(:,:)==xundef)pek%XWG(:,:)=xundef
328  !
329  DEALLOCATE(zf)
330  !
331  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
332  !
333  CASE('WGI ')
334  ALLOCATE(zf(ini,io%NGROUND_LAYER))
335  !
336  !* interpolates on output levels
337  CALL init_from_ref_grid(xgrid_soil,zw,p%XDG(:,:),zf)
338  !
339  !* retrieves soil ice content from soil relative humidity
340  ALLOCATE(pek%XWGI(ini,io%NGROUND_LAYER))
341  pek%XWGI(:,:) = zf(:,:) * k%XWSAT
342  pek%XWGI(:,:) = max(min(pek%XWGI(:,:),k%XWSAT),0.)
343  !
344  WHERE(zf(:,:)==xundef)pek%XWGI(:,:)=xundef
345  !
346  DEALLOCATE(zf)
347  !
348  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
349  !
350  CASE('TG ')
351  iwork=io%NGROUND_LAYER
352  ALLOCATE(pek%XTG(ini,iwork))
353  ALLOCATE(zdg(SIZE(p%XDG,1),iwork))
354  !* diffusion method, the soil grid is the same as for humidity
355  zdg(:,:) = p%XDG(:,:)
356  CALL init_from_ref_grid(xgrid_soil,zw,zdg,pek%XTG(:,:))
357  DEALLOCATE(zdg)
358  !
359 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
360  !
361  CASE('WR ')
362  ALLOCATE(pek%XWR(ini))
363  pek%XWR(:) = zw(:,1)
364  !
365  !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
366  !
367  CASE('LAI ')
368  !* LAI is updated only if present and pertinent (evolutive LAI) in input file
369  WHERE (zw(:,1)/=xundef) pek%XLAI(:) = zw(:,1)
370  !
371 END SELECT
372 !
373 DEALLOCATE(zw)
374 !-------------------------------------------------------------------------------------
375 !
376 IF (lhook) CALL dr_hook('PREP_HOR_TEB_GREENROOF_FIELD',1,zhook_handle)
377 !
378 !-------------------------------------------------------------------------------------
379 !-------------------------------------------------------------------------------------
380 !
381 CONTAINS
382 !
383 !-------------------------------------------------------------------------------------
384 !-------------------------------------------------------------------------------------
385 !
386 SUBROUTINE init_from_ref_grid(PGRID1,PT1,PD2,PT2)
387 !
389 !
390 REAL, DIMENSION(:,:), INTENT(IN) :: PT1 ! variable profile
391 REAL, DIMENSION(:), INTENT(IN) :: PGRID1 ! normalized grid
392 REAL, DIMENSION(:,:), INTENT(IN) :: PD2 ! output layer thickness
393 REAL, DIMENSION(:,:), INTENT(OUT) :: PT2 ! variable profile
394 !
395 INTEGER :: JI, JL ! loop counter
396 REAL, DIMENSION(SIZE(PT1,1),SIZE(PT1,2)) :: ZD1 ! input grid
397 !
398 INTEGER :: ILAYER1, ILAYER2
399 REAL(KIND=JPRB) :: ZHOOK_HANDLE
400 !
401 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
402 !
403 IF (lhook) CALL dr_hook('INIT_FROM_REF_GRID',0,zhook_handle)
404 !
405 IF (SIZE(pt1,2)==3) THEN
406 !
407 !* 1. case with only 3 input levels (typically coming from 'UNIF')
408 ! -----------------------------
409 !
410  !surface layer (generally 0.01m imposed)
411  pt2(:,1) = pt1(:,1)
412  !deep layers
413  DO jl=2,io%NGROUND_LAYER
414  pt2(:,jl) = pt1(:,3)
415  END DO
416  !if root layers
417  DO ji=1,SIZE(pt1,1)
418  DO jl=2,io%NGROUND_LAYER
419  IF(p%XROOTFRAC(ji,jl)<=1.0)THEN
420  pt2(ji,jl) = pt1(ji,2)
421  EXIT
422  ENDIF
423  END DO
424  END DO
425 !
426 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
427 ELSE
428 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
429 !
430 !* 2. case with fine grid as input (general case)
431 ! ----------------------------
432 !
433  DO jl=1,SIZE(pt1,2)
434  zd1(:,jl) = pgrid1(jl)
435  END DO
436 !
437  CALL interp_grid_nat(zd1,pt1(:,:),pd2,pt2(:,:))
438 !
439 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
440 END IF
441 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
442 !
443 IF (lhook) CALL dr_hook('INIT_FROM_REF_GRID',1,zhook_handle)
444 !
445 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
446 END SUBROUTINE init_from_ref_grid
447 !-------------------------------------------------------------------------------------
448 !
449 END SUBROUTINE prep_hor_teb_greenroof_field
subroutine prep_teb_greenroof_buffer(HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine prep_grib_grid(HGRIB, KLUOUT, HINMODEL, HGRIDTYPE, HINTERP_
character(len=10) cingrid_type
Definition: modd_prep.F90:39
subroutine read_prep_teb_greenroof_conf(HPROGRAM, HVAR, HFILE, HFILET
subroutine prep_hor_snow_fields(DTCO, G, U, GCP, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, OUNIF, KPATCH, KTEB_PATCH, KL, TNPSNOW, TPTIME, PUNIF_WSNOW, PUNIF_RSNOW, PUNIF_TSNOW, PUNIF_LWCSNOW, PUNIF_ASNOW, OSNOW_IDEAL, PUNIF_SG1SNOW, PUNIF_SG2SNOW, PUNIF_HISTSNOW, PUNIF_AGESNOW, YDCTL, PVEGTYPE_PATCH, KSIZE_P, KR_P, PPATCH, OKEY)
subroutine init_from_ref_grid(PGRID1, PT1, PD2, PT2)
real, dimension(:), allocatable xzs_ls
Definition: modd_prep.F90:45
character(len=6) cmask
Definition: modd_prep.F90:41
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine prep_teb_greenroof_ascllv(DTCO, UG, U, USS, HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine put_on_all_vegtypes(KNI, KLAYER, KPATCH, KVEGTYPE, PFIELD_P
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
character(len=6) cinmodel
logical, dimension(:), allocatable linterp
Definition: modd_prep.F90:43
subroutine hor_interpol(DTCO, U, GCP, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:7
subroutine prep_teb_greenroof_unif(KLUOUT, HSURF, PFIELD)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine prep_teb_greenroof_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)
subroutine prep_hor_teb_greenroof_field(DTCO, UG, U, USS, GCP, IO, S, K, P, PEK, TG, TOP, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, KPATCH, YDCTL)
logical function prep_ctl_can(YDCTL)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
subroutine allocate_gr_snow(TPSNOW, KLU)
logical lhook
Definition: yomhook.F90:15
subroutine read_prep_greenroof_snow(HPROGRAM, HSNOW, KSNOW_LAYER, HFI
subroutine prep_teb_greenroof_extern(DTCO, IO, U, GCP, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, KPATCH, PFIELD)