SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pgd_teb.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 pgd_teb (DTCO, DGU, UG, U, USS, DTI, TM, GDM, GRM, &
7  hprogram,oecoclimap,ogarden)
8 ! ##############################################################
9 !
10 !!**** *PGD_TEB* monitor for averaging and interpolations of TEB physiographic fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! V. Masson Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 10/12/97
37 !! A. Lemonsu 05/2009 Key for garden option
38 !! G. Pigeon /09/12: WALL, ROOF, FLOOR, MASS LAYER default to 5
39 !!
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 !
49 USE modd_surf_atm_n, ONLY : surf_atm_t
51 USE modd_data_isba_n, ONLY : data_isba_t
52 !
53 USE modd_surfex_n, ONLY : teb_model_t
56 !
57 USE modd_data_cover_par, ONLY : jpcover
58 !
59 USE modi_get_surf_size_n
60 USE modi_pack_pgd
61 USE modi_pgd_teb_par
62 USE modi_pgd_teb_veg
63 USE modi_get_luout
64 USE modi_read_nam_pgd_teb
66 USE modi_pgd_bem_par
67 USE modi_abor1_sfx
68 !
69 !
70 USE yomhook ,ONLY : lhook, dr_hook
71 USE parkind1 ,ONLY : jprb
72 !
73 USE modi_write_cover_tex_teb
74 !
75 IMPLICIT NONE
76 !
77 !* 0.1 Declaration of arguments
78 ! ------------------------
79 !
80 !
81 TYPE(data_cover_t), INTENT(INOUT) :: dtco
82 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
83 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
84 TYPE(surf_atm_t), INTENT(INOUT) :: u
85 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
86 TYPE(data_isba_t), INTENT(INOUT) :: dti
87 TYPE(teb_model_t), INTENT(INOUT) :: tm
88 TYPE(teb_garden_model_t), INTENT(INOUT) :: gdm
89 TYPE(teb_greenroof_model_t), INTENT(INOUT) :: grm
90 !
91  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
92 LOGICAL, INTENT(IN) :: oecoclimap ! T if parameters are computed with ecoclimap
93 ! ! F if all parameters must be specified
94 LOGICAL, INTENT(IN) :: ogarden ! T if urban green areas
95 !
96 !
97 !* 0.2 Declaration of local variables
98 ! ------------------------------
99 !
100 INTEGER :: iluout ! output listing logical unit
101 REAL(KIND=JPRB) :: zhook_handle
102 !
103 !-------------------------------------------------------------------------------
104 !
105 !* 1. Initializations of defaults
106 ! ---------------------------
107 !
108 IF (lhook) CALL dr_hook('PGD_TEB',0,zhook_handle)
109  CALL get_luout(hprogram,iluout)
110 
111 tm%TOP%NROOF_LAYER = 5
112 tm%TOP%NROAD_LAYER = 5
113 tm%TOP%NWALL_LAYER = 5
114 tm%BOP%NFLOOR_LAYER = 5
115 !
116 !-------------------------------------------------------------------------------
117 !
118 !* 2. Reading of namelist
119 ! -------------------
120 !
121  CALL read_nam_pgd_teb(hprogram,tm%TOP%NTEB_PATCH,tm%TOP%CBEM,tm%BOP%CCOOL_COIL,&
122  tm%BOP%CHEAT_COIL,tm%BOP%LAUTOSIZE,tm%TOP%NROAD_LAYER,&
123  tm%TOP%NROOF_LAYER,tm%TOP%NWALL_LAYER,tm%BOP%NFLOOR_LAYER, &
124  tm%TOP%LGREENROOF,tm%TOP%LHYDRO,tm%TOP%LSOLAR_PANEL )
125 !
126 !-------------------------------------------------------------------------------
127 !
128 !* 3. Coherence of options
129 ! --------------------
130 !
131  CALL test_nam_var_surf(iluout,'CBLD',tm%TOP%CBEM,'DEF','BEM ')
132  CALL test_nam_var_surf(iluout,'CCOOL_COIL',tm%BOP%CCOOL_COIL,'IDEAL ','DXCOIL')
133  CALL test_nam_var_surf(iluout,'CHEAT_COIL',tm%BOP%CHEAT_COIL,'IDEAL ','FINCAP')
134 !
135 IF (.NOT. ogarden) THEN
136  IF (tm%TOP%LGREENROOF) CALL abor1_sfx('ERROR: You cannot activate LGREENROOF if LGARDEN is FALSE')
137  IF (tm%TOP%LHYDRO ) CALL abor1_sfx('ERROR: You cannot activate LHYDRO if LGARDEN is FALSE')
138 ENDIF
139 !
140 !-------------------------------------------------------------------------------
141 !
142 !* 4. Number of points and packing
143 ! ----------------------------
144 !
145  CALL get_surf_size_n(dtco, u, &
146  'TOWN ',tm%TG%NDIM)
147 !
148 ALLOCATE(tm%TOP%LCOVER (jpcover))
149 ALLOCATE(tm%TOP%XCOVER (tm%TG%NDIM,jpcover))
150 ALLOCATE(tm%TOP%XZS (tm%TG%NDIM))
151 ALLOCATE(tm%TG%XLAT (tm%TG%NDIM))
152 ALLOCATE(tm%TG%XLON (tm%TG%NDIM))
153 ALLOCATE(tm%TG%XMESH_SIZE (tm%TG%NDIM))
154 !
155  CALL pack_pgd(dtco, u, &
156  hprogram, 'TOWN ', &
157  tm%TG%CGRID, tm%TG%XGRID_PAR, &
158  tm%TOP%LCOVER, tm%TOP%XCOVER, tm%TOP%XZS, &
159  tm%TG%XLAT, tm%TG%XLON, tm%TG%XMESH_SIZE )
160 !
161 !-------------------------------------------------------------------------------
162 !
163 !* 5. TEB specific fields
164 ! -------------------
165 !
166 tm%TOP%LECOCLIMAP = oecoclimap
167  CALL pgd_teb_par(dtco, dgu, ug, u, uss, tm%BDD, tm%DTT, dti, tm%TG, &
168  hprogram,ogarden,tm%TOP%LGREENROOF,tm%TOP%CBLD_ATYPE)
169 !
170 !-------------------------------------------------------------------------------
171 !
172 !* 6. Prints of cover parameters in a tex file
173 ! ----------------------------------------
174 !
175 IF (oecoclimap) CALL write_cover_tex_teb
176 !
177 !
178 !-------------------------------------------------------------------------------
179 !
180 !* 7. Case of urban green areas (and hydrology)
181 ! -----------------------------------------
182 !
183 tm%TOP%LGARDEN = ogarden
184 !
185 IF (tm%TOP%LGARDEN) CALL pgd_teb_veg(dtco, ug, u, uss, gdm, grm, tm%TOP, tm%TG, &
186  hprogram)
187 !
188 !-------------------------------------------------------------------------------
189 !
190 !* 8. Case of Building Energy Model
191 ! -----------------------------
192 !
193 IF (tm%TOP%CBEM .EQ. 'BEM') CALL pgd_bem_par(dtco, dgu, ug, u, uss, tm%DTB, dti, tm%TG, &
194  hprogram,tm%BOP%LAUTOSIZE)
195 !
196 IF (lhook) CALL dr_hook('PGD_TEB',1,zhook_handle)
197 !
198 !-------------------------------------------------------------------------------
199 !
200 END SUBROUTINE pgd_teb
subroutine read_nam_pgd_teb(HPROGRAM, KTEB_PATCH, HBEM, HCOOL_COIL, HHEAT_COIL, OAUTOSIZE, KROAD_LAYER, KROOF_LAYER, KWALL_LAYER, KFLOOR_LAYER, OGREENROOF, OHYDRO, OSOLAR_PANEL)
subroutine get_surf_size_n(DTCO, U, HTYPE, KL)
subroutine pack_pgd(DTCO, U, HPROGRAM, HSURF, HGRID, PGRID_PAR, OCOVER, PCOVER, PZS, PLAT, PLON, PMESH_SIZE, PDIR)
Definition: pack_pgd.F90:6
subroutine write_cover_tex_teb
subroutine pgd_teb_par(DTCO, DGU, UG, U, USS, BDD, DTT, DTI, TG, HPROGRAM, OGARDEN, OGREENROOF, HBLD_ATYPE)
Definition: pgd_teb_par.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine pgd_bem_par(DTCO, DGU, UG, U, USS, DTB, DTI, TG, HPROGRAM, OAUTOSIZE)
Definition: pgd_bem_par.F90:6
subroutine pgd_teb_veg(DTCO, UG, U, USS, GDM, GRM, TOP, TG, HPROGRAM)
Definition: pgd_teb_veg.F90:6
subroutine pgd_teb(DTCO, DGU, UG, U, USS, DTI, TM, GDM, GRM, HPROGRAM, OECOCLIMAP, OGARDEN)
Definition: pgd_teb.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6