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