SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_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 read_pgd_teb_n (DTCO, U, TM, &
7  hprogram)
8 ! #########################################
9 !
10 !!**** *READ_PGD_TEB_n* - reads TEB physiographic fields
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 01/2003
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
43 USE modd_surf_atm_n, ONLY : surf_atm_t
44 USE modd_teb_grid_n, ONLY : teb_grid_t
45 USE modd_surfex_n, ONLY : teb_model_t
46 !
48 !
49 USE modd_data_cover_par, ONLY : jpcover
50 !
51 !
53 !
55 USE modi_read_grid
56 USE modi_read_lcover
57 USE modi_read_pgd_teb_par_n
58 !
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 USE modi_get_type_dim_n
64 !
65 USE modi_read_lecoclimap
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 Declarations of arguments
70 ! -------------------------
71 !
72 !
73 TYPE(data_cover_t), INTENT(INOUT) :: dtco
74 TYPE(surf_atm_t), INTENT(INOUT) :: u
75 TYPE(teb_model_t), INTENT(INOUT) :: tm
76 !
77  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
78 !
79 !* 0.2 Declarations of local variables
80 ! -------------------------------
81 !
82 INTEGER :: iresp ! Error code after redding
83 !
84  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
85 INTEGER :: iversion
86 INTEGER :: ibugfix
87 !
88 REAL(KIND=JPRB) :: zhook_handle
89 !-------------------------------------------------------------------------------
90 !
91 !* 1D physical dimension
92 !
93 IF (lhook) CALL dr_hook('READ_PGD_TEB_N',0,zhook_handle)
94 yrecfm='SIZE_TOWN'
95  CALL get_type_dim_n(dtco, u, &
96  'TOWN ',tm%TG%NDIM)
97 !
98 !* 2. Other dimension initializations:
99 ! --------------------------------
100 !
101  CALL read_surf(&
102  hprogram,'VERSION',iversion,iresp)
103  CALL read_surf(&
104  hprogram,'BUG',ibugfix,iresp)
105 !
106 !* number of TEB patches
107 !
108 IF (iversion<7 .OR. iversion==7 .AND. ibugfix<=2) THEN
109  tm%TOP%NTEB_PATCH=1
110 ELSE
111  yrecfm='TEB_PATCH'
112  CALL read_surf(&
113  hprogram,yrecfm,tm%TOP%NTEB_PATCH,iresp)
114 END IF
115 !
116 !* number of road and roof layers
117 !
118 yrecfm='ROAD_LAYER'
119  CALL read_surf(&
120  hprogram,yrecfm,tm%TOP%NROAD_LAYER,iresp)
121 
122 yrecfm='ROOF_LAYER'
123  CALL read_surf(&
124  hprogram,yrecfm,tm%TOP%NROOF_LAYER,iresp)
125 
126 yrecfm='WALL_LAYER'
127  CALL read_surf(&
128  hprogram,yrecfm,tm%TOP%NWALL_LAYER,iresp)
129 !
130 !
131 !* type of averaging for Buildings (to allow ascendant compatibility)
132 !* type of Building Energy Model
133 !
134 IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=2)) THEN
135  tm%TOP%CBLD_ATYPE='ARI'
136  tm%TOP%CBEM = 'DEF'
137 ELSE
138  yrecfm='BLD_ATYPE'
139  CALL read_surf(&
140  hprogram,yrecfm,tm%TOP%CBLD_ATYPE,iresp)
141  yrecfm='BEM'
142  CALL read_surf(&
143  hprogram,yrecfm,tm%TOP%CBEM,iresp)
144 END IF
145 !
146 IF (tm%TOP%CBEM=="BEM") THEN
147  yrecfm='FLOOR_LAYER'
148  CALL read_surf(&
149  hprogram,yrecfm,tm%BOP%NFLOOR_LAYER,iresp)
150  yrecfm='COOL_COIL'
151  CALL read_surf(&
152  hprogram,yrecfm,tm%BOP%CCOOL_COIL,iresp)
153  yrecfm='HEAT_COIL'
154  CALL read_surf(&
155  hprogram,yrecfm,tm%BOP%CHEAT_COIL,iresp)
156  yrecfm='AUTOSIZE'
157  CALL read_surf(&
158  hprogram,yrecfm,tm%BOP%LAUTOSIZE,iresp)
159 ENDIF
160 !
161 !* Case of urban green roofs
162 !
163 IF (tm%TOP%LGARDEN) THEN
164  IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=2)) THEN
165  tm%TOP%LGREENROOF = .false.
166  ELSE
167  yrecfm='LGREENROOF'
168  CALL read_surf(&
169  hprogram,yrecfm,tm%TOP%LGREENROOF,iresp)
170  END IF
171 !
172 !* Case of urban hydrology
173 !
174  IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=3)) THEN
175  tm%TOP%LHYDRO = .false.
176  ELSE
177  yrecfm='LURBAN_HYDRO'
178  CALL read_surf(&
179  hprogram,yrecfm,tm%TOP%LHYDRO,iresp)
180  END IF
181 ENDIF
182 !
183 !* Solar panels
184 !
185 IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=3)) THEN
186  tm%TOP%LSOLAR_PANEL = .false.
187 ELSE
188  yrecfm='SOLAR_PANEL'
189  CALL read_surf(&
190  hprogram,yrecfm,tm%TOP%LSOLAR_PANEL,iresp)
191 END IF
192 !
193 !
194 !
195 !* 3. Physiographic data fields:
196 ! -------------------------
197 !
198 !* cover classes
199 !
200 ALLOCATE(tm%TOP%LCOVER(jpcover))
201  CALL read_lcover(&
202  hprogram,tm%TOP%LCOVER)
203 !
204 ALLOCATE(tm%TOP%XCOVER(tm%TG%NDIM,count(tm%TOP%LCOVER)))
205  CALL read_surf_cov(&
206  hprogram,'COVER',tm%TOP%XCOVER(:,:),tm%TOP%LCOVER,iresp)
207 !
208 !* orography
209 !
210 ALLOCATE(tm%TOP%XZS(tm%TG%NDIM))
211 yrecfm='ZS'
212  CALL read_surf(&
213  hprogram,yrecfm,tm%TOP%XZS(:),iresp)
214 !
215 !
216 !* latitude, longitude
217 !
218 ALLOCATE(tm%TG%XLAT (tm%TG%NDIM))
219 ALLOCATE(tm%TG%XLON (tm%TG%NDIM))
220 ALLOCATE(tm%TG%XMESH_SIZE(tm%TG%NDIM))
221  CALL read_grid(&
222  hprogram,tm%TG%CGRID,tm%TG%XGRID_PAR,&
223  tm%TG%XLAT,tm%TG%XLON,tm%TG%XMESH_SIZE,iresp)
224 !
225 !
226 !-------------------------------------------------------------------------------
227 !
228 !* 4. Physiographic data fields not to be computed by ecoclimap
229 ! ---------------------------------------------------------
230 !
231  CALL read_lecoclimap(&
232  hprogram,tm%TOP%LECOCLIMAP)
233 !
234  CALL read_pgd_teb_par_n(dtco, u, &
235  tm%BDD, tm%DTB, tm%DTT, tm%TG, tm%TOP, &
236  hprogram,tm%TG%NDIM,'-')
237 IF (lhook) CALL dr_hook('READ_PGD_TEB_N',1,zhook_handle)
238 !
239 !
240 !------------------------------------------------------------------------------
241 !
242 END SUBROUTINE read_pgd_teb_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine read_grid(HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON, PMESH_SIZE, KRESP, PDIR)
Definition: read_grid.F90:6
subroutine, public read_surf_cov(HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)
subroutine read_pgd_teb_n(DTCO, U, TM, HPROGRAM)
subroutine read_lcover(HPROGRAM, OCOVER)
Definition: read_lcover.F90:6
subroutine read_pgd_teb_par_n(DTCO, U, BDD, DTB, DTT, TG, TOP, HPROGRAM, KNI, HDIRIN)
subroutine read_lecoclimap(HPROGRAM, OECOCLIMAP)