SURFEX v8.1
General documentation of Surfex
prep_isba_buffer.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_isba_buffer (G, U, HPROGRAM,HSURF,KLUOUT,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_ISBA_BUFFER* - initializes ISBA fields from operational BUFFER
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! S. Malardel
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 03/2005
28 !!------------------------------------------------------------------
29 !
30 
31 !
32 !
33 USE modd_sfx_grid_n, ONLY : grid_t
34 USE modd_surf_atm_n, ONLY : surf_atm_t
35 !
37 !
39 !
40 USE modi_prep_buffer_grid
42 !
43 USE modd_prep, ONLY : cinterp_type
44 USE modd_prep_isba, ONLY : xgrid_soil, xwr_def
45 USE modd_surf_par, ONLY : xundef
46 USE modd_grid_buffer, ONLY : nni
47 USE modn_prep_isba, ONLY : lextrap_tg,lextrap_wg,lextrap_wgi
48 #ifdef SFX_ARO
49 USE modi_oi_hor_extrapol_surf
50 #endif
53 USE modi_abor1_sfx
54 !
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 TYPE(grid_t), INTENT(INOUT) :: G
65 TYPE(surf_atm_t), INTENT(INOUT) :: U
66 !
67  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
68  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
69 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
70 REAL,DIMENSION(:,:,:), POINTER :: PFIELD ! field to interpolate horizontally
71 !
72 !* 0.2 declarations of local variables
73 !
74 type(date_time) :: tztime_buf ! current date and time
75  CHARACTER(LEN=6) :: YINMODEL ! model from which buffer originates
76 REAL, DIMENSION(:,:), POINTER :: ZFIELD ! field read
77 REAL, DIMENSION(:), POINTER :: ZFIELD1D ! field read
78 REAL, DIMENSION(:,:), POINTER :: ZD ! depth of field in the soil
79 REAL,DIMENSION(:),POINTER :: ZLSM
80 REAL,DIMENSION(:),POINTER :: ZALT
81 REAL,ALLOCATABLE,DIMENSION(:) :: ZFIELD_EP
82 REAL,ALLOCATABLE,DIMENSION(:) :: ZFIELD_EP_IN
83 REAL,ALLOCATABLE,DIMENSION(:) :: ZLSM_NATURE
84 REAL,ALLOCATABLE,DIMENSION(:) :: ZALT_NATURE
85 LOGICAL,ALLOCATABLE,DIMENSION(:) :: OINTERP
86 INTEGER :: ILAYER,II
87 REAL(KIND=JPRB) :: ZHOOK_HANDLE
88 !
89 !-------------------------------------------------------------------------------------
90 !
91 !* 1. Reading of grid
92 ! ---------------
93 !
94 IF (lhook) CALL dr_hook('PREP_ISBA_BUFFER',0,zhook_handle)
95  CALL prep_buffer_grid(kluout,yinmodel,tztime_buf)
96 
97 !
98 !* 2. Reading of field
99 ! ----------------
100 !
101 !* 3. Transformation into physical quantity to be interpolated
102 ! --------------------------------------------------------
103 !
104 SELECT CASE(hsurf)
105 !
106 !* 3.1 Profile of temperature in the soil
107 !
108  CASE('TG ')
109  !* reading of the profile and its depth definition
110  SELECT CASE(yinmodel)
111  CASE('ALADIN')
112  CALL read_buffer_tg(kluout,yinmodel,zfield,zd)
113  IF ( lextrap_tg ) THEN
114  IF ( SIZE(u%NR_NATURE) /= u%NSIZE_NATURE ) THEN
115  CALL abor1_sfx('ABORT: PREP_ISBA_BUFFER - DIFFERENT SIZES')
116  ELSE
117  ! Allocate working arrays
118  ALLOCATE(zfield_ep(u%NSIZE_NATURE))
119  ALLOCATE(zfield_ep_in(u%NSIZE_NATURE))
120  ALLOCATE(ointerp(u%NSIZE_NATURE))
121  ALLOCATE(zlsm_nature(u%NSIZE_NATURE))
122  ALLOCATE(zalt_nature(u%NSIZE_NATURE))
123 
124  ! Read LSM and ZS
125  CALL read_buffer_land_mask(kluout,yinmodel,zlsm)
126  CALL read_buffer_zs(kluout,yinmodel,zalt)
127 
128  ! Pack nature points to reduce dimension to nsize_nature
129  CALL pack_same_rank(u%NR_NATURE,zlsm,zlsm_nature)
130  CALL pack_same_rank(u%NR_NATURE,zalt,zalt_nature)
131 
132  ! Do extrapolations in all layers
133  DO ilayer=1,SIZE(zfield,2)
134  WRITE(kluout,*) 'Extrapolating TG from nearest land point in points where LSM < 0.5. LAYER:',ilayer
135 
136  ! Pack nature points to reduce dimension
137  CALL pack_same_rank(u%NR_NATURE,zfield(:,ilayer),zfield_ep(:))
138  ! Set values to be extrapolated
139  ointerp=.false.
140  DO ii=1,u%NSIZE_NATURE
141  IF ( zlsm_nature(ii) < 0.5 ) THEN
142  ointerp(ii) = .true.
143  zfield_ep(ii) = xundef
144  ENDIF
145  ENDDO
146 
147  zfield_ep_in(:) = zfield_ep(:)
148 #ifdef SFX_ARO
149  CALL oi_hor_extrapol_surf(u%NSIZE_NATURE,g%XLAT,g%XLON,zfield_ep_in(:), &
150  g%XLAT,g%XLON,zfield_ep(:),ointerp,pzs=zalt,ndim2=10)
151 #endif
152 
153  ! Unpack to full rank
154  CALL unpack_same_rank(u%NR_NATURE,zfield_ep(:),zfield(:,ilayer))
155  ENDDO
156  DEALLOCATE(zfield_ep)
157  DEALLOCATE(zfield_ep_in)
158  DEALLOCATE(zlsm_nature)
159  DEALLOCATE(zalt_nature)
160  DEALLOCATE(ointerp)
161  ENDIF
162  ENDIF
163  END SELECT
164 
166 
167  CASE('WG ')
168  !* reading of the profile and its depth definition
169  SELECT CASE(yinmodel)
170  CASE('ARPEGE','ALADIN','MOCAGE')
171  CALL read_buffer_wg(kluout,yinmodel,zfield,zd)
172  IF ( lextrap_wg ) THEN
173  IF ( SIZE(u%NR_NATURE) /= u%NSIZE_NATURE ) THEN
174  CALL abor1_sfx('ABORT: PREP_ISBA_BUFFER - DIFFERENT SIZES')
175  ELSE
176  ! Allocate working arrays
177  ALLOCATE(zfield_ep(u%NSIZE_NATURE))
178  ALLOCATE(zfield_ep_in(u%NSIZE_NATURE))
179  ALLOCATE(ointerp(u%NSIZE_NATURE))
180  ALLOCATE(zlsm_nature(u%NSIZE_NATURE))
181 
182  ! Read LSM
183  CALL read_buffer_land_mask(kluout,yinmodel,zlsm)
184 
185  ! Pack nature points to reduce dimension to nsize_nature
186  CALL pack_same_rank(u%NR_NATURE,zlsm,zlsm_nature)
187 
188  ! Do extrapolations in all layers
189  DO ilayer=1,SIZE(zfield,2)
190  WRITE(kluout,*) 'Extrapolating WG from nearest land point in points where LSM < 0.5. LAYER:',ilayer
191 
192  ! Pack nature points to reduce dimension
193  CALL pack_same_rank(u%NR_NATURE,zfield(:,ilayer),zfield_ep(:))
194  ! Set values to be extrapolated
195  ointerp=.false.
196 
197  DO ii=1,u%NSIZE_NATURE
198  IF ( zlsm_nature(ii) < 0.5 ) THEN
199  ointerp(ii) = .true.
200  zfield_ep(ii) = xundef
201  ENDIF
202  ENDDO
203 
204  zfield_ep_in(:) = zfield_ep
205 #ifdef SFX_ARO
206  CALL oi_hor_extrapol_surf(u%NSIZE_NATURE,g%XLAT,g%XLON,zfield_ep_in(:), &
207  g%XLAT,g%XLON,zfield_ep(:),ointerp,ndim2=10)
208 #endif
209 
210  ! Unpack to full rank
211  CALL unpack_same_rank(u%NR_NATURE,zfield_ep(:),zfield(:,ilayer))
212  ENDDO
213  DEALLOCATE(zfield_ep)
214  DEALLOCATE(zfield_ep_in)
215  DEALLOCATE(zlsm_nature)
216  DEALLOCATE(ointerp)
217  ENDIF
218  ENDIF
219 
220  END SELECT
222 
223 
224 !* 3.3 Profile of soil ice content
225 
226  CASE('WGI ')
227  !* reading of the profile and its depth definition
228  SELECT CASE(yinmodel)
229  CASE('ALADIN')
230  CALL read_buffer_wgi(kluout,yinmodel,zfield,zd)
231  IF ( lextrap_wgi ) THEN
232 
233  IF ( SIZE(u%NR_NATURE) /= u%NSIZE_NATURE ) THEN
234  CALL abor1_sfx('ABORT: PREP_ISBA_BUFFER - DIFFERENT SIZES')
235  ELSE
236 
237  ! Allocate working arrays
238  ALLOCATE(zfield_ep(u%NSIZE_NATURE))
239  ALLOCATE(zfield_ep_in(u%NSIZE_NATURE))
240  ALLOCATE(ointerp(u%NSIZE_NATURE))
241  ALLOCATE(zlsm_nature(u%NSIZE_NATURE))
242 
243  ! Read LSM
244  CALL read_buffer_land_mask(kluout,yinmodel,zlsm)
245 
246  ! Pack nature points to reduce dimension to nsize_nature
247  CALL pack_same_rank(u%NR_NATURE,zlsm,zlsm_nature)
248 
249  ! Do extrapolations in all layers
250  DO ilayer=1,SIZE(zfield,2)
251  WRITE(kluout,*) 'Extrapolating WGI from nearest land point in points where LSM < 0.5. LAYER:',ilayer
252 
253  ! Pack nature points to reduce dimension
254  CALL pack_same_rank(u%NR_NATURE,zfield(:,ilayer),zfield_ep(:))
255  ! Set values to be extrapolated
256  ointerp=.false.
257  DO ii=1,u%NSIZE_NATURE
258  IF ( zlsm_nature(ii) < 0.5 ) THEN
259  ointerp(ii) = .true.
260  zfield_ep(ii) = xundef
261  ENDIF
262  ENDDO
263 
264  zfield_ep_in(:) = zfield_ep
265 #ifdef SFX_ARO
266  CALL oi_hor_extrapol_surf(u%NSIZE_NATURE,g%XLAT,g%XLON,zfield_ep_in(:), &
267  g%XLAT,g%XLON,zfield_ep(:),ointerp,ndim2=10)
268 #endif
269 
270  ! Unpack to full rank
271  CALL unpack_same_rank(u%NR_NATURE,zfield_ep(:),zfield(:,ilayer))
272  ENDDO
273  DEALLOCATE(zfield_ep)
274  DEALLOCATE(zfield_ep_in)
275  DEALLOCATE(zlsm_nature)
276  DEALLOCATE(ointerp)
277  ENDIF
278  ENDIF
279 
280  END SELECT
282 !
283 !* 3.4 Water content intercepted on leaves, LAI
284 !
285  CASE('WR ')
286  ALLOCATE(pfield(nni,1,1))
287  pfield(:,:,:) = xwr_def
288 !
289  CASE('LAI ')
290  ALLOCATE(pfield(nni,1,1))
291  pfield(:,:,:) = xundef
292 !
293 !
294 !* 3.5 Other fields
295 !
296  CASE('ZS ')
297  CALL read_buffer_zs(kluout,yinmodel,zfield1d)
298  ALLOCATE(pfield(SIZE(zfield1d,1),1,1))
299  pfield(:,1,1)=zfield1d(:)
300  DEALLOCATE(zfield1d)
301 !
302  CASE('ICE_STO')
303  ALLOCATE(pfield(nni,1,1))
304  pfield(:,:,:) = 0.0
305 !
306  CASE DEFAULT
307  CALL abor1_sfx('PREP_ISBA_BUFFER: '//trim(hsurf)//" initialization not implemented !")
308 !
309 END SELECT
310 !
311 !* 4. Interpolation method
312 ! --------------------
313 !
314 cinterp_type='BUFFER'
315 !
316 !
317 !-------------------------------------------------------------------------------------
318 !-------------------------------------------------------------------------------------
319 !
320 IF (lhook) CALL dr_hook('PREP_ISBA_BUFFER',1,zhook_handle)
321 CONTAINS
322 !
323 !-------------------------------------------------------------------------------------
324 !-------------------------------------------------------------------------------------
325 SUBROUTINE soil_profile_buffer
326 !-------------------------------------------------------------------------------------
327 !
328 REAL, DIMENSION(:,:), ALLOCATABLE :: ZOUT ! work array
329 REAL(KIND=JPRB) :: ZHOOK_HANDLE
330 !
331 !-------------------------------------------------------------------------------------
332 !
333  !
334  !* interpolation on fine vertical grid
335  IF (lhook) CALL dr_hook('SOIL_PROFILE_BUFFER',0,zhook_handle)
336  ALLOCATE(zout(SIZE(zfield,1),SIZE(xgrid_soil)))
337  CALL interp_grid_nat(zd,zfield,xgrid_soil,zout)
338  !
339  !* extends definition to all vegtypes.
340  ALLOCATE(pfield(SIZE(zfield,1),SIZE(xgrid_soil),1))
341  pfield(:,:,1)=zout(:,:)
342  !* end
343  DEALLOCATE(zout)
344  DEALLOCATE(zfield)
345  DEALLOCATE(zd)
346 IF (lhook) CALL dr_hook('SOIL_PROFILE_BUFFER',1,zhook_handle)
347 
348 END SUBROUTINE soil_profile_buffer
349 !
350 !-------------------------------------------------------------------------------------
351 END SUBROUTINE prep_isba_buffer
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
subroutine read_buffer_tg(KLUOUT, HINMODEL, PFIELD, PD)
subroutine prep_isba_buffer(G, U, HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine read_buffer_land_mask(KLUOUT, HINMODEL, PMASK)
subroutine read_buffer_wgi(KLUOUT, HINMODEL, PFIELD, PD)
subroutine prep_buffer_grid(KLUOUT, HINMODEL, TPTIME_BUF)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine read_buffer_zs(KLUOUT, HINMODEL, PFIELD)
logical lhook
Definition: yomhook.F90:15
subroutine read_buffer_wg(KLUOUT, HINMODEL, PFIELD, PD)
subroutine soil_profile_buffer