SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_tebn.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 writesurf_pgd_teb_n (DGU, U, TM, GDM, GRM, &
7  hprogram)
8 ! ###############################################
9 !
10 !!**** *WRITE_PGD_TEB_n* - writes TEB fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2003
36 !! B. Decharme 07/2011 : delete argument HWRITE
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 !
45 USE modd_surf_atm_n, ONLY : surf_atm_t
46 USE modd_surfex_n, ONLY : teb_model_t
49 !
50 USE modd_data_cover_par, ONLY : jpcover
51 !
53 !
55 USE modi_write_grid
56 !
57 !
58 USE yomhook ,ONLY : lhook, dr_hook
59 USE parkind1 ,ONLY : jprb
60 !
61 USE modi_writesurf_pgd_teb_par_n
62 USE modi_writesurf_pgd_teb_veg_n
63 USE modi_writesurf_pgd_teb_greenroof_n
64 !
65 IMPLICIT NONE
66 !
67 !* 0.1 Declarations of arguments
68 ! -------------------------
69 !
70 !
71 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
72 TYPE(surf_atm_t), INTENT(INOUT) :: u
73 TYPE(teb_model_t), INTENT(INOUT) :: tm
74 TYPE(teb_garden_model_t), INTENT(INOUT) :: gdm
75 TYPE(teb_greenroof_model_t), INTENT(INOUT) :: grm
76 !
77  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
78 !
79 !* 0.2 Declarations of local variables
80 ! -------------------------------
81 !
82 INTEGER :: iresp ! IRESP : return-code if a problem appears
83  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
84  CHARACTER(LEN=100):: ycomment ! Comment string
85 !
86 REAL(KIND=JPRB) :: zhook_handle
87 !
88 !-------------------------------------------------------------------------------
89 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_N',0,zhook_handle)
90 !
91 !* 1. Dimension initializations:
92 ! -------------------------
93 !
94 !
95 !* number of TEB patches
96 !
97 yrecfm='TEB_PATCH'
98 ycomment=yrecfm
99  CALL write_surf(dgu, u, &
100  hprogram,yrecfm,tm%TOP%NTEB_PATCH,iresp,hcomment=ycomment)
101 !
102 !
103 !* number of roof layers
104 !
105 yrecfm='ROOF_LAYER'
106 ycomment=yrecfm
107  CALL write_surf(dgu, u, &
108  hprogram,yrecfm,tm%TOP%NROOF_LAYER,iresp,hcomment=ycomment)
109 !
110 !* number of road layers
111 !
112 yrecfm='ROAD_LAYER'
113 ycomment=yrecfm
114  CALL write_surf(dgu, u, &
115  hprogram,yrecfm,tm%TOP%NROAD_LAYER,iresp,hcomment=ycomment)
116 !
117 !* number of wall layers
118 !
119 yrecfm='WALL_LAYER'
120 ycomment=yrecfm
121  CALL write_surf(dgu, u, &
122  hprogram,yrecfm,tm%TOP%NWALL_LAYER,iresp,hcomment=ycomment)
123 !
124 !* flag indicating if fields are computed from ecoclimap or not
125 !
126 yrecfm='ECOCLIMAP'
127 ycomment=yrecfm
128  CALL write_surf(dgu, u, &
129  hprogram,yrecfm,tm%TOP%LECOCLIMAP,iresp,hcomment=ycomment)
130 !
131 !
132 !* Type of Building Energy Model
133 !
134 yrecfm='BEM'
135 ycomment=yrecfm
136  CALL write_surf(dgu, u, &
137  hprogram,yrecfm,tm%TOP%CBEM,iresp,hcomment=ycomment)
138 !
139 IF (tm%TOP%CBEM=='BEM') THEN
140  yrecfm='COOL_COIL'
141  ycomment=yrecfm
142  CALL write_surf(dgu, u, &
143  hprogram,yrecfm,tm%BOP%CCOOL_COIL,iresp,hcomment=ycomment)
144  !
145  yrecfm='HEAT_COIL'
146  ycomment=yrecfm
147  CALL write_surf(dgu, u, &
148  hprogram,yrecfm,tm%BOP%CHEAT_COIL,iresp,hcomment=ycomment)
149  !
150  yrecfm='AUTOSIZE'
151  ycomment=yrecfm
152  CALL write_surf(dgu, u, &
153  hprogram,yrecfm,tm%BOP%LAUTOSIZE,iresp,hcomment=ycomment)
154 END IF
155 !
156 !* Type of averaging of buildings characteristics
157 !
158 yrecfm='BLD_ATYPE'
159 ycomment=yrecfm
160  CALL write_surf(dgu, u, &
161  hprogram,yrecfm,tm%TOP%CBLD_ATYPE,iresp,hcomment=ycomment)
162 !
163 !
164 !
165 !* number of floor layers
166 !
167 IF (tm%TOP%CBEM=="BEM") THEN
168  yrecfm='FLOOR_LAYER'
169  ycomment=yrecfm
170  CALL write_surf(dgu, u, &
171  hprogram,yrecfm,tm%BOP%NFLOOR_LAYER,iresp,hcomment=ycomment)
172 ENDIF
173 !
174 !
175 !* Use of solar panels
176 !
177 yrecfm='SOLAR_PANEL'
178 ycomment=yrecfm
179  CALL write_surf(dgu, u, &
180  hprogram,yrecfm,tm%TOP%LSOLAR_PANEL,iresp,hcomment=ycomment)
181 !
182 !------------------------------------------------------------------------------
183 !
184 ! * ISBA fields for urban green areas
185 !
186 IF (tm%TOP%LGARDEN) THEN
187 !
188 ! * Greenroofs and hydrology (only activated if LGARDEN)
189 !
190 yrecfm='LGREENROOF'
191 ycomment=yrecfm
192  CALL write_surf(dgu, u, &
193  hprogram,yrecfm,tm%TOP%LGREENROOF,iresp,hcomment=ycomment)
194 !
195 yrecfm='LURBAN_HYDRO'
196 ycomment=yrecfm
197  CALL write_surf(dgu, u, &
198  hprogram,yrecfm,tm%TOP%LHYDRO,iresp,hcomment=ycomment)
199 !
200 ! * General ISBA options for urban vegetation
201 !
202 ! * Pedo-transfert function
203 !
204 yrecfm='GD_PEDOTF'
205 ycomment=yrecfm
206  CALL write_surf(dgu, u, &
207  hprogram,yrecfm,gdm%TVG%CPEDOTF,iresp,hcomment=ycomment)
208 !
209 ! * type of photosynthesis
210 !
211 yrecfm='GD_PHOTO'
212 ycomment=yrecfm
213  CALL write_surf(dgu, u, &
214  hprogram,yrecfm,gdm%TVG%CPHOTO,iresp,hcomment=ycomment)
215 !
216 !* new radiative transfert
217 !
218 yrecfm='GD_TR_ML'
219 ycomment=yrecfm
220  CALL write_surf(dgu, u, &
221  hprogram,yrecfm,gdm%TVG%LTR_ML,iresp,hcomment=ycomment)
222 !
223 ! * ISBA fields specific to urban gardens
224 !
225  CALL writesurf_pgd_teb_veg_n(dgu, u, &
226  gdm%DTGD, gdm%TGDO, gdm%TGDP, gdm%TVG, &
227  hprogram)
228 !
229 ! * ISBA fields specific to urban greenroofs
230 !
231 IF (tm%TOP%LGREENROOF) CALL writesurf_pgd_teb_greenroof_n(dgu, u, &
232  grm%TGRO, grm%TGRP, &
233  hprogram)
234 !
235 ENDIF
236 !
237 !------------------------------------------------------------------------------
238 !
239 !* 2. Physiographic data fields:
240 ! -------------------------
241 !
242 !* cover classes
243 !
244 yrecfm='COVER_LIST'
245 ycomment='(LOGICAL LIST)'
246  CALL write_surf(dgu, u, &
247  hprogram,yrecfm,tm%TOP%LCOVER(:),iresp,hcomment=ycomment,hdir='-')
248 !
249 ycomment='COVER FIELDS'
250  CALL write_surf_cov(dgu, u, &
251  hprogram,'COVER',tm%TOP%XCOVER(:,:),tm%TOP%LCOVER,iresp,hcomment=ycomment)
252 !
253 !* orography
254 !
255 yrecfm='ZS'
256 ycomment='ZS'
257  CALL write_surf(dgu, u, &
258  hprogram,yrecfm,tm%TOP%XZS(:),iresp,hcomment=ycomment)
259 !
260 !* latitude, longitude
261 !
262  CALL write_grid(dgu, u, &
263  hprogram,tm%TG%CGRID,tm%TG%XGRID_PAR,tm%TG%XLAT,tm%TG%XLON,tm%TG%XMESH_SIZE,iresp)
264 !
265 !-------------------------------------------------------------------------------
266  CALL writesurf_pgd_teb_par_n(tm%BDD, tm%DTB, gdm%DTGD, grm%DTGR, tm%DTT, dgu, u, gdm%TGDO, &
267  gdm%TGDP, grm%TGRO, gdm%TIR, tm%TOP, &
268  hprogram)
269 !
270 IF (lhook) CALL dr_hook('WRITESURF_PGD_TEB_N',1,zhook_handle)
271 !-------------------------------------------------------------------------------
272 !
273 END SUBROUTINE writesurf_pgd_teb_n
subroutine writesurf_pgd_teb_veg_n(DGU, U, DTGD, TGDO, TGDP, TVG, HPROGRAM)
subroutine write_grid(DGU, U, HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON, PMESH_SIZE, KRESP, PDIR, HDIR)
Definition: write_grid.F90:6
subroutine writesurf_pgd_teb_n(DGU, U, TM, GDM, GRM, HPROGRAM)
subroutine writesurf_pgd_teb_par_n(BDD, DTB, DTGD, DTGR, DTT, DGU, U, TGDO, TGDP, TGRO, TIR, TOP, HPROGRAM)
subroutine writesurf_pgd_teb_greenroof_n(DGU, U, TGRO, TGRP, HPROGRAM)
subroutine, public write_surf_cov(DGU, U, HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)