SURFEX v8.1
General documentation of Surfex
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, IO, U, GCP, &
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 USE modd_surfex_mpi, ONLY : nrank, npio
32 !
35 USE modd_surf_atm_n, ONLY : surf_atm_t
37 !
39 !
41 !
42 USE modi_prep_grid_extern
45 USE modi_open_aux_io_surf
46 USE modi_close_aux_io_surf
47 USE modi_read_teb_patch
48 USE modi_town_presence
49 USE modi_make_choice_array
50 !
52 USE modd_prep_teb_garden,ONLY : xgrid_soil, xwr_def
53 USE modd_data_cover_par, ONLY : nvegtype
54 USE modd_surf_par, ONLY : xundef
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 USE modi_put_on_all_vegtypes
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 declarations of arguments
64 !
65 !
66 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
67 TYPE(isba_options_t), INTENT(INOUT) :: IO
68 TYPE(surf_atm_t), INTENT(INOUT) :: U
69 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
72  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
73  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! name of file
74  CHARACTER(LEN=6), INTENT(IN) :: HFILETYPE ! type of input file
75  CHARACTER(LEN=28), INTENT(IN) :: HFILEPGD ! name of file
76  CHARACTER(LEN=6), INTENT(IN) :: HFILEPGDTYPE ! type of input file
77 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
78 INTEGER, INTENT(IN) :: KPATCH
79 REAL,DIMENSION(:,:,:), POINTER :: PFIELD ! field to interpolate horizontally (on final soil grid)
80 !
81 !* 0.2 declarations of local variables
82 !
83  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
84 INTEGER :: IRESP ! reading return code
85 INTEGER :: INI ! total 1D dimension
86 INTEGER :: IPATCH ! number of patch
87 !
88 REAL, DIMENSION(:,:,:), POINTER :: ZFIELD ! field read on initial MNH vertical soil grid, all patches
89 REAL, DIMENSION(:,:), POINTER :: ZFIELD1 ! field read on initial MNH vertical soil grid, one patch
90 REAL, DIMENSION(:,:,:), POINTER :: ZD ! depth of field in the soil
91 REAL, DIMENSION(:,:), POINTER :: ZD1 ! depth of field in the soil, one patch
92 REAL, DIMENSION(:,:), ALLOCATABLE :: ZOUT !
93  CHARACTER(LEN=12) :: YSURF ! type of field
94  CHARACTER(LEN=3) :: YPATCH ! indentificator for TEB patch
95 INTEGER :: JPATCH ! loop counter for patch
96 INTEGER :: ITEB_PATCH ! number of TEB patches in file
97 INTEGER :: IVERSION ! SURFEX version
98 INTEGER :: IBUGFIX ! SURFEX bug version
99 LOGICAL :: GTEB ! flag if TEB fields are present
100 LOGICAL :: GOLD_NAME ! old name flag for temperatures
101 LOGICAL :: GGARDEN ! T if gardens are present in the file
102 LOGICAL :: GDIM
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(hfilepgd,hfilepgdtype,'FULL ')
122 !
123 !* reading of version of the file being read
124  CALL read_surf(hfilepgdtype,'VERSION',iversion,iresp)
125  CALL read_surf(hfilepgdtype,'BUG',ibugfix,iresp)
126 gold_name = (iversion<7 .OR. (iversion==7 .AND. ibugfix<3))
127 !
128  CALL prep_grid_extern(gcp,hfilepgdtype,kluout,cingrid_type,cinterp_type,ini)
129 !
130 IF (nrank/=npio) ini = 0
131 !
132 !* reads if TEB fields exist in the input file
133  CALL town_presence(hfilepgdtype,gteb,hdir='-')
134 !
135 IF (gteb) THEN
136  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
137  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'TOWN ')
138  CALL read_teb_patch(hfilepgd,hfilepgdtype,iversion,ibugfix,iteb_patch,hdir='-')
139  ypatch=' '
140  IF (iteb_patch>1) THEN
141  WRITE(ypatch,fmt='(A,I1,A)') 'T',min(kpatch,iteb_patch),'_'
142  END IF
143 END IF
144 !
145  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
146 !
147 !---------------------------------------------------------------------------------------
148 !
149 !* 3. Transformation into physical quantity to be interpolated
150 ! --------------------------------------------------------
151 !
152 SELECT CASE(hsurf)
153 !
154 !* 3. Orography
155 ! ---------
156 !
157  CASE('ZS ')
158  ALLOCATE(pfield(ini,1,1))
159  yrecfm='ZS'
160  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'FULL ')
161  CALL read_surf(hfilepgdtype,yrecfm,pfield(:,1,1),iresp,hdir='A')
162  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
163 !
164 !--------------------------------------------------------------------------
165 !
166 !
167 !* 3.1 Profile of temperature, water or ice in the soil
168 !
169  CASE('TG ','WG ','WGI ')
170 !* choice if one reads garden fields (if present) or ISBA fields
171  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'TOWN ')
172  ggarden = .false.
173  IF (gteb) CALL read_surf(hfilepgdtype,'GARDEN',ggarden,iresp,hdir='-')
174  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
175  IF (ggarden) THEN
176  ysurf = 'GD_'//hsurf(1:3)
177  IF (gold_name) ysurf = 'TWN_'//hsurf(1:3)
178  ysurf = ypatch//ysurf
179  ELSE
180  ysurf = hsurf
181  END IF
182  ysurf=adjustl(ysurf)
183 !* reading of the profile and its depth definition
184  CALL read_extern_isba(u, dtco, gcp, io, hfile,hfiletype,hfilepgd,hfilepgdtype,kluout,ini,&
185  hsurf,ysurf,zfield,zd)
186 !
187  IF (nrank==npio) THEN
188 
189  ALLOCATE(zout(SIZE(zfield,1),SIZE(xgrid_soil)))
190  ALLOCATE(pfield(SIZE(zfield,1),SIZE(xgrid_soil),SIZE(zfield,3)))
191  ALLOCATE(zfield1(SIZE(zfield,1),SIZE(zfield,2)))
192  ALLOCATE(zd1(SIZE(zfield,1),SIZE(zfield,2)))
193  DO jpatch=1,SIZE(zfield,3)
194  zfield1(:,:)=zfield(:,:,jpatch)
195  zd1(:,:)=zd(:,:,jpatch)
196  CALL interp_grid_nat(zd1,zfield1,xgrid_soil,zout)
197  pfield(:,:,jpatch)=zout(:,:)
198  END DO
199  DEALLOCATE(zfield)
200  DEALLOCATE(zout)
201  DEALLOCATE(zfield1)
202  DEALLOCATE(zd)
203 
204  ENDIF
205 !
206 !--------------------------------------------------------------------------
207 !
208 !* 3.4 Water content intercepted on leaves, LAI
209 !
210  CASE('WR ')
211  !* choice if one reads garden fields (if present) or ISBA fields
212  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'TOWN ')
213  ggarden = .false.
214  IF (gteb) CALL read_surf(hfilepgdtype,'GARDEN',ggarden,iresp,hdir='-')
215  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
216  IF (ggarden) THEN
217  ipatch = 1
218  yrecfm = 'GD_WR'
219  IF (gold_name) yrecfm = 'TWN_WR'
220  yrecfm = ypatch//yrecfm
221  CALL open_aux_io_surf(hfile,hfiletype,'TOWN ')
222  ELSE
223  ipatch = 0
224  yrecfm = 'PATCH_NUMBER'
225  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'NATURE')
226  CALL read_surf(hfilepgdtype,yrecfm,ipatch,iresp,hdir='-')
227  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
228  CALL open_aux_io_surf(hfile,hfiletype,'NATURE')
229  yrecfm = 'WR'
230  END IF
231 
232  CALL read_surf(hfiletype,'VERSION',iversion,iresp)
233  CALL read_surf(hfiletype,'BUG',ibugfix,iresp)
234  gdim = (iversion>8 .OR. iversion==8 .AND. ibugfix>0)
235  IF (gdim) CALL read_surf(hfiletype,'SPLIT_PATCH',gdim,iresp)
236  yrecfm=adjustl(yrecfm)
237  ALLOCATE(zfield(ini,1,ipatch))
238  IF (ggarden) THEN
239  CALL read_surf(hfiletype,yrecfm,zfield(:,1,1),iresp,hdir='E')
240  ELSE
241  CALL make_choice_array(hfiletype, ipatch, gdim, yrecfm, zfield(:,1,:),hdir='E')
242  ENDIF
243  CALL close_aux_io_surf(hfile,hfiletype)
244  IF (ipatch/=1) THEN
245  ALLOCATE(pfield(ini,1,nvegtype))
246  CALL put_on_all_vegtypes(ini,1,ipatch,nvegtype,zfield,pfield)
247  ELSE
248  ALLOCATE(pfield(ini,1,1))
249  pfield(:,:,:) = zfield(:,:,:)
250  ENDIF
251  DEALLOCATE(zfield)
252 !
253  CASE('LAI ')
254  ALLOCATE(pfield(ini,1,1))
255  pfield(:,:,:) = xundef
256 !
257 END SELECT
258 !
259 !
260 !---------------------------------------------------------------------------
261 !
262 !* 6. End of IO
263 ! ---------
264 !
265 IF (lhook) CALL dr_hook('PREP_TEB_GARDEN_EXTERN',1,zhook_handle)
266 !
267 !---------------------------------------------------------------------------
268 !---------------------------------------------------------------------------
269 END SUBROUTINE prep_teb_garden_extern
character(len=10) cingrid_type
Definition: modd_prep.F90:39
subroutine make_choice_array(HPROGRAM, KNPATCH, ODIM, HRECFM, PWORK, HDIR, KPATCH)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine close_aux_io_surf(HFILE, HFILETYPE)
subroutine town_presence(HFILETYPE, OTEB, HDIR)
subroutine prep_grid_extern(GCP, HFILETYPE, KLUOUT, HGRIDTYPE, HINTER
subroutine put_on_all_vegtypes(KNI, KLAYER, KPATCH, KVEGTYPE, PFIELD_P
real, parameter xundef
subroutine prep_teb_garden_extern(DTCO, IO, U, GCP, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, KPATCH, PFIELD)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine read_extern_isba(U, DTCO, GCP, IO, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, KNI, HFIELD, HNAME, PFIELD, PDEPTH, OKEY)
logical lhook
Definition: yomhook.F90:15
subroutine read_teb_patch(HFILEPGD, HFILEPGDTYPE, KVERSION, KBUGFIX,
subroutine open_aux_io_surf(HFILE, HFILETYPE, HMASK, HDIR)