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