SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_teb_greenroof_extern.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 prep_teb_greenroof_extern (DTCO, I, U, &
7  hprogram,hsurf,hfile,hfiletype,hfilepgd,hfilepgdtype,kluout,kpatch,pfield)
8 ! #################################################################################
9 !
10 !!**** *PREP_TEB_GREENROOF_EXTERN* - initializes ISBA fields from operational GRIB
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !! Based on "prep_teb_garden_extern"
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! A. Lemonsu & C. de Munck
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 07/2011
30 !!------------------------------------------------------------------
31 !
32 !
34 USE modd_isba_n, ONLY : isba_t
35 USE modd_surf_atm_n, ONLY : surf_atm_t
36 !
38 !
40 !
41 USE modi_prep_grid_extern
44 USE modi_open_aux_io_surf
45 USE modi_close_aux_io_surf
46 USE modi_read_teb_patch
47 USE modi_town_presence
48 !
49 USE modd_prep, ONLY : cingrid_type, cinterp_type
50 USE modd_prep_teb_greenroof, ONLY : xgrid_soil, xwr_def
51 USE modd_data_cover_par, ONLY : nvegtype
52 USE modd_surf_par, ONLY : xundef
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 USE modi_put_on_all_vegtypes
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 TYPE(data_cover_t), INTENT(INOUT) :: dtco
65 TYPE(isba_t), INTENT(INOUT) :: i
66 TYPE(surf_atm_t), INTENT(INOUT) :: u
67 !
68  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
69  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
70  CHARACTER(LEN=28), INTENT(IN) :: hfile ! name of file
71  CHARACTER(LEN=6), INTENT(IN) :: hfiletype ! type of input file
72  CHARACTER(LEN=28), INTENT(IN) :: hfilepgd ! name of file
73  CHARACTER(LEN=6), INTENT(IN) :: hfilepgdtype ! type of input file
74 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
75 INTEGER, INTENT(IN) :: kpatch
76 REAL,DIMENSION(:,:,:), POINTER :: pfield ! field to interpolate horizontally (on final soil grid)
77 !
78 !* 0.2 declarations of local variables
79 !
80  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
81 INTEGER :: iresp ! reading return code
82 INTEGER :: ini ! total 1D dimension
83 INTEGER :: ipatch ! number of patch
84 !
85 REAL, DIMENSION(:,:,:), POINTER :: zfield ! field read on initial MNH vertical soil grid, all patches
86 REAL, DIMENSION(:,:), POINTER :: zfield1 ! field read on initial MNH vertical soil grid, one patch
87 REAL, DIMENSION(:,:,:), POINTER :: zd ! depth of field in the soil
88 REAL, DIMENSION(:,:), POINTER :: zd1 ! depth of field in the soil, one patch
89 REAL, DIMENSION(:,:), ALLOCATABLE :: zout !
90 LOGICAL :: gteb ! flag if TEB fields are present
91 INTEGER :: jpatch ! loop counter for patch
92  CHARACTER(LEN=12) :: ysurf ! type of field
93 INTEGER :: iteb_patch ! number of TEB patches in file
94 INTEGER :: iversion ! SURFEX version
95 INTEGER :: ibugfix ! SURFEX bug version
96 LOGICAL :: gold_name ! old name flag for temperatures
97  CHARACTER(LEN=3) :: ypatch ! indentificator for TEB patch
98 LOGICAL :: ggreenroof ! T if gardens are present in the file
99 !
100 REAL(KIND=JPRB) :: zhook_handle
101 !
102 !------------------------------------------------------------------------------
103 !
104 !* 1. Preparation of IO for reading in the file
105 ! -----------------------------------------
106 !
107 !* Note that all points are read, even those without physical meaning.
108 ! These points will not be used during the horizontal interpolation step.
109 ! Their value must be defined as XUNDEF.
110 !
111 IF (lhook) CALL dr_hook('PREP_TEB_GREENROOF_EXTERN',0,zhook_handle)
112 !
113  CALL open_aux_io_surf(&
114  hfilepgd,hfilepgdtype,'FULL ')
115 !
116 !* reading of version of the file being read
117  CALL read_surf(&
118  hfilepgdtype,'VERSION',iversion,iresp)
119  CALL read_surf(&
120  hfilepgdtype,'BUG',ibugfix,iresp)
121 gold_name=(iversion<7 .OR. (iversion==7 .AND. ibugfix<3))
122 !
123 !------------------------------------------------------------------------------
124 !
125 !* 2. Reading of grid
126 ! ---------------
127 !
128  CALL prep_grid_extern(&
129  hfilepgdtype,kluout,cingrid_type,cinterp_type,ini)
130 !
131 !* reads if TEB fields exist in the input file
132  CALL town_presence(&
133  hfilepgdtype,gteb)
134 !
135 IF (gteb) THEN
136  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
137  CALL read_teb_patch(&
138  hfilepgd,hfilepgdtype,iteb_patch)
139  CALL open_aux_io_surf(&
140  hfilepgd,hfilepgdtype,'FULL ')
141  ypatch=' '
142  IF (iteb_patch>1) THEN
143  WRITE(ypatch,fmt='(A,I1,A)') 'T',min(kpatch,iteb_patch),'_'
144  END IF
145 END IF
146 !
147 ! A FAIRE : VERIFIER QUE LES MODIFS DES PATCH/GTEB/GGREENROOF SONT CORRECTES
148 !---------------------------------------------------------------------------------------
149 !
150 !* 3. Transformation into physical quantity to be interpolated
151 ! --------------------------------------------------------
152 !
153 SELECT CASE(hsurf)
154 !
155 !* 3. Orography
156 ! ---------
157 !
158  CASE('ZS ')
159  ALLOCATE(pfield(ini,1,1))
160  yrecfm='ZS'
161  CALL read_surf(&
162  hfilepgdtype,yrecfm,pfield(:,1,1),iresp,hdir='A')
163  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
164 !
165 !--------------------------------------------------------------------------
166 !
167 !
168 !* 3.1 Profile of temperature, water or ice in the soil
169 !
170  CASE('TG ','WG ','WGI ')
171 !* choice if one reads garden fields (if present) or ISBA fields
172  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
173  CALL open_aux_io_surf(&
174  hfilepgd,hfilepgdtype,'TOWN ')
175  ggreenroof = .false.
176  IF (gteb) CALL read_surf(&
177  hfilepgdtype,'LGREENROOF',ggreenroof,iresp)
178  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
179  IF (ggreenroof) THEN
180  ysurf = 'GR_'//hsurf(1:3)
181  ysurf=ypatch//ysurf
182  ELSE
183  ysurf = hsurf
184  END IF
185  ysurf=adjustl(ysurf)
186 !* reading of the profile and its depth definition
187  CALL read_extern_isba(u, &
188  dtco, i, &
189  hfile,hfiletype,hfilepgd,hfilepgdtype,kluout,ini,&
190  hsurf,ysurf,zfield,zd)
191 !
192  ALLOCATE(zfield1(SIZE(zfield,1),SIZE(zfield,2)))
193  ALLOCATE(zd1(SIZE(zfield,1),SIZE(zfield,2)))
194  ALLOCATE(zout(SIZE(zfield,1),SIZE(xgrid_soil)))
195  ALLOCATE(pfield(SIZE(zfield,1),SIZE(xgrid_soil),SIZE(zfield,3)))
196 !
197  DO jpatch=1,SIZE(zfield,3)
198  zfield1(:,:)=zfield(:,:,jpatch)
199  zd1(:,:)=zd(:,:,jpatch)
200  CALL interp_grid_nat(zd1,zfield1,xgrid_soil,zout)
201  pfield(:,:,jpatch)=zout(:,:)
202  END DO
203 !
204  DEALLOCATE(zfield)
205  DEALLOCATE(zout)
206  DEALLOCATE(zfield1)
207  DEALLOCATE(zd)
208 !
209 !--------------------------------------------------------------------------
210 !
211 !* 3.4 Water content intercepted on leaves, LAI
212 !
213  CASE('WR ')
214  ALLOCATE(pfield(ini,1,nvegtype))
215  !* choice if one reads garden fields (if present) or ISBA fields
216  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
217  CALL open_aux_io_surf(&
218  hfilepgd,hfilepgdtype,'TOWN ')
219  ggreenroof = .false.
220  IF (gteb) CALL read_surf(&
221  hfilepgdtype,'LGREENROOF',ggreenroof,iresp)
222  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
223  IF (ggreenroof) THEN
224  ipatch = 1
225  yrecfm = 'GD_WR'
226  yrecfm=ypatch//yrecfm
227  CALL open_aux_io_surf(&
228  hfile,hfiletype,'TOWN ')
229  ELSE
230  yrecfm = 'PATCH_NUMBER'
231  CALL open_aux_io_surf(&
232  hfilepgd,hfilepgdtype,'NATURE')
233  CALL read_surf(&
234  hfilepgdtype,yrecfm,ipatch,iresp)
235  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
236  CALL open_aux_io_surf(&
237  hfile,hfiletype,'NATURE')
238  yrecfm = 'WR'
239  END IF
240  yrecfm=adjustl(yrecfm)
241  ALLOCATE(zfield(ini,1,ipatch))
242  CALL read_surf(&
243  hfiletype,yrecfm,zfield(:,1,:),iresp,hdir='A')
244  CALL close_aux_io_surf(hfile,hfiletype)
245  CALL put_on_all_vegtypes(ini,1,1,nvegtype,zfield,pfield)
246  DEALLOCATE(zfield)
247 !
248  CASE('LAI ')
249  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
250  ALLOCATE(pfield(ini,1,nvegtype))
251  pfield(:,:,:) = xundef
252 !
253 END SELECT
254 !
255 !
256 !---------------------------------------------------------------------------
257 !
258 !* 6. End of IO
259 ! ---------
260 !
261 IF (lhook) CALL dr_hook('PREP_TEB_GREENROOF_EXTERN',1,zhook_handle)
262 !
263 !---------------------------------------------------------------------------
264 !---------------------------------------------------------------------------
265 END SUBROUTINE prep_teb_greenroof_extern
subroutine close_aux_io_surf(HFILE, HFILETYPE)
subroutine open_aux_io_surf(HFILE, HFILETYPE, HMASK)
subroutine read_extern_isba(U, DTCO, I, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, KNI, HFIELD, HNAME, PFIELD, PDEPTH, OKEY)
subroutine read_teb_patch(HFILEPGD, HFILEPGDTYPE, KTEB_PATCH)
subroutine put_on_all_vegtypes(KNI, KLAYER, KPATCH, KVEGTYPE, PFIELD_PATCH, PFIELD_VEGTYPE)
subroutine town_presence(HFILETYPE, OTEB)
subroutine prep_grid_extern(HFILETYPE, KLUOUT, HGRIDTYPE, HINTERP_TYPE, KNI)
subroutine prep_teb_greenroof_extern(DTCO, I, U, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, KPATCH, PFIELD)