SURFEX v8.1
General documentation of Surfex
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, UG, GCP, TOP, TG, &
7  BOP, BDD, DTB, DTT, 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
46 !
48 USE modd_sfx_grid_n, ONLY : grid_t
51 USE modd_data_bem_n, ONLY : data_bem_t
52 USE modd_data_teb_n, ONLY : data_teb_t
53 !
55 !
56 USE modd_data_cover_par, ONLY : jpcover
57 !
58 !
60 !
62 USE modi_pack_init
63 USE modi_read_pgd_teb_par_n
64 !
65 !
66 USE yomhook ,ONLY : lhook, dr_hook
67 USE parkind1 ,ONLY : jprb
68 !
69 USE modi_get_type_dim_n
70 !
71 USE modi_read_lecoclimap
72 !
73 IMPLICIT NONE
74 !
75 !* 0.1 Declarations of arguments
76 ! -------------------------
77 !
78 !
79 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
80 TYPE(surf_atm_t), INTENT(INOUT) :: U
81 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
82 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
83 !
84 TYPE(teb_options_t), INTENT(INOUT) :: TOP
85 TYPE(grid_t), INTENT(INOUT) :: TG
86 TYPE(bem_options_t), INTENT(INOUT) :: BOP
87 TYPE(bld_desc_t), INTENT(INOUT) :: BDD
88 TYPE(data_bem_t), INTENT(INOUT) :: DTB
89 TYPE(data_teb_t), INTENT(INOUT) :: DTT
90 !
91  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
92 !
93 !* 0.2 Declarations of local variables
94 ! -------------------------------
95 !
96  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
97 INTEGER :: IVERSION
98 INTEGER :: IBUGFIX
99 INTEGER :: IRESP ! Error code after redding
100 !
101 LOGICAL :: GECOSG
102 !
103 REAL(KIND=JPRB) :: ZHOOK_HANDLE
104 !-------------------------------------------------------------------------------
105 !
106 !* 1D physical dimension
107 !
108 IF (lhook) CALL dr_hook('READ_PGD_TEB_N',0,zhook_handle)
109 yrecfm='SIZE_TOWN'
110  CALL get_type_dim_n(dtco, u, 'TOWN ',tg%NDIM)
111 !
112 !* 2. Other dimension initializations:
113 ! --------------------------------
114 !
115  CALL read_surf(hprogram,'VERSION',iversion,iresp)
116  CALL read_surf(hprogram,'BUG',ibugfix,iresp)
117 !
118 !* number of TEB patches
119 !
120 IF (iversion<7 .OR. iversion==7 .AND. ibugfix<=2) THEN
121  top%NTEB_PATCH=1
122 ELSE
123  yrecfm='TEB_PATCH'
124  CALL read_surf(hprogram,yrecfm,top%NTEB_PATCH,iresp)
125 END IF
126 !
127 !* number of road and roof layers
128 !
129 yrecfm='ROAD_LAYER'
130  CALL read_surf( hprogram,yrecfm,top%NROAD_LAYER,iresp)
131 
132 yrecfm='ROOF_LAYER'
133  CALL read_surf(hprogram,yrecfm,top%NROOF_LAYER,iresp)
134 
135 yrecfm='WALL_LAYER'
136  CALL read_surf(hprogram,yrecfm,top%NWALL_LAYER,iresp)
137 !
138 !
139 !* type of averaging for Buildings (to allow ascendant compatibility)
140 !* type of Building Energy Model
141 !
142 IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=2)) THEN
143  top%CBLD_ATYPE='ARI'
144  top%CBEM = 'DEF'
145 ELSE
146  yrecfm='BLD_ATYPE'
147  CALL read_surf(hprogram,yrecfm,top%CBLD_ATYPE,iresp)
148  yrecfm='BEM'
149  CALL read_surf(hprogram,yrecfm,top%CBEM,iresp)
150 END IF
151 !
152 IF (top%CBEM=="BEM") THEN
153  yrecfm='FLOOR_LAYER'
154  CALL read_surf(hprogram,yrecfm,bop%NFLOOR_LAYER,iresp)
155  yrecfm='COOL_COIL'
156  CALL read_surf(hprogram,yrecfm,bop%CCOOL_COIL,iresp)
157  yrecfm='HEAT_COIL'
158  CALL read_surf(hprogram,yrecfm,bop%CHEAT_COIL,iresp)
159  yrecfm='AUTOSIZE'
160  CALL read_surf(hprogram,yrecfm,bop%LAUTOSIZE,iresp)
161 ENDIF
162 !
163 !* Case of urban green roofs
164 !
165 IF (top%LGARDEN) THEN
166  IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=2)) THEN
167  top%LGREENROOF = .false.
168  ELSE
169  yrecfm='LGREENROOF'
170  CALL read_surf(hprogram,yrecfm,top%LGREENROOF,iresp)
171  END IF
172 !
173 !* Case of urban hydrology
174 !
175  IF (iversion<7 .OR.( iversion==7 .AND. ibugfix<=3)) THEN
176  top%LHYDRO = .false.
177  ELSE
178  yrecfm='LURBAN_HYDRO'
179  CALL read_surf(hprogram,yrecfm,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  top%LSOLAR_PANEL = .false.
187 ELSE
188  yrecfm='SOLAR_PANEL'
189  CALL read_surf(hprogram,yrecfm,top%LSOLAR_PANEL,iresp)
190 END IF
191 !
192 !
193 !
194 !* 3. Physiographic data fields:
195 ! -------------------------
196 !
197 !* cover classes
198 !
199 ALLOCATE(top%LCOVER(jpcover))
200 ALLOCATE(top%XZS(tg%NDIM))
201 ALLOCATE(tg%XLAT (tg%NDIM))
202 ALLOCATE(tg%XLON (tg%NDIM))
203 ALLOCATE(tg%XMESH_SIZE (tg%NDIM))
204  CALL pack_init(dtco,u,ug,hprogram,'TOWN ',tg, top%LCOVER,top%XCOVER,top%XZS )
205 !
206 !-------------------------------------------------------------------------------
207 !
208 !* 4. Physiographic data fields not to be computed by ecoclimap
209 ! ---------------------------------------------------------
210 !
211  CALL read_lecoclimap(hprogram,top%LECOCLIMAP,gecosg)
212 !
213  CALL read_pgd_teb_par_n(dtco, u, gcp, bdd, dtb, dtt, tg%NDIM, top, &
214  hprogram,tg%NDIM,'-')
215 !
216 IF (lhook) CALL dr_hook('READ_PGD_TEB_N',1,zhook_handle)
217 !
218 !------------------------------------------------------------------------------
219 !
220 END SUBROUTINE read_pgd_teb_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine pack_init(DTCO, U, UG, HPROGRAM, HSURF, G, OCOVER, PCOV
Definition: pack_init.F90:7
subroutine read_surf_cov(HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)
subroutine read_lecoclimap(HPROGRAM, OECOCLIMAP, OECOSG, HDIR)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine read_pgd_teb_n(DTCO, U, UG, GCP, TOP, TG, BOP, BDD, DTB, DTT, HPROGRAM)
subroutine read_pgd_teb_par_n(DTCO, U, GCP, BDD, DTB, DTT, KDIM,