SURFEX v8.1
General documentation of Surfex
prep_snow_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_snow_buffer (G, U, HPROGRAM,HSURF,KLUOUT,KLAYER,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_SNOW_BUFFER* - prepares snow field 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 USE modd_sfx_grid_n, ONLY : grid_t
32 USE modd_surf_atm_n, ONLY : surf_atm_t
33 !
34 USE mode_snow3l
35 !
37 !
39 !
40 USE modi_prep_buffer_grid
41 #ifdef SFX_ARO
42 USE modi_oi_hor_extrapol_surf
43 #endif
46 USE modi_abor1_sfx
47 !
48 USE modd_prep, ONLY : cinterp_type
49 USE modd_prep_isba, ONLY : lextrap_sn
50 USE modd_prep_snow, ONLY : xgrid_snow
51 USE modd_surf_par, ONLY : xundef
52 USE modd_grid_buffer, ONLY : nni
53 USE modd_snow_par, ONLY : xansmin, xansmax, xrhosmax
54 USE modd_csts, ONLY : xtt
55 !
56 !
57 USE yomhook ,ONLY : lhook, dr_hook
58 USE parkind1 ,ONLY : jprb
59 !
60 IMPLICIT NONE
61 !
62 !* 0.1 declarations of arguments
63 !
64 !
65 TYPE(grid_t), INTENT(INOUT) :: G
66 TYPE(surf_atm_t), INTENT(INOUT) :: U
67 !
68  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
69  CHARACTER(LEN=10), INTENT(IN) :: HSURF ! type of field
70 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
71 INTEGER, INTENT(IN) :: KLAYER ! Number of layer of output snow scheme
72 REAL,DIMENSION(:,:,:), POINTER :: PFIELD ! field to interpolate horizontally
73 !
74 !* 0.2 declarations of local variables
75 !
76 type(date_time) :: tztime_buffer ! current date and time
77  CHARACTER(LEN=6) :: YINMODEL ! model from which GRIB file originates
78 REAL, DIMENSION(:), POINTER :: ZFIELD1D ! field read
79 REAL, DIMENSION(:), POINTER :: ZHEAT ! heat in snow
80 REAL, DIMENSION(:), POINTER :: ZRHO ! density of snow
81 REAL,DIMENSION(:),POINTER :: ZLSM ! Land/sea mask
82 INTEGER :: JVEGTYPE ! loop counter on vegtypes
83 INTEGER :: JLAYER ! loop on snow fine grid
84 REAL,ALLOCATABLE,DIMENSION(:) :: ZFIELD_EP
85 REAL,ALLOCATABLE,DIMENSION(:) :: ZFIELD_EP_IN
86 REAL,ALLOCATABLE,DIMENSION(:) :: ZLSM_NATURE
87 LOGICAL,ALLOCATABLE,DIMENSION(:) :: OINTERP
88 INTEGER :: II
89 INTEGER,PARAMETER :: IDIM2=10
90 REAL(KIND=JPRB) :: ZHOOK_HANDLE
91 !
92 !-------------------------------------------------------------------------------------
93 !
94 !* 1. Reading of grid
95 ! ---------------
96 !
97 IF (lhook) CALL dr_hook('PREP_SNOW_BUFFER',0,zhook_handle)
98  CALL prep_buffer_grid(kluout,yinmodel,tztime_buffer)
99 !
100 !-------------------------------------------------------------------------------------
101 !
102 !* 2. Reading of the physical field for urban areas
103 ! ---------------------------------------------
104 !
105 IF (hsurf(7:8)=='RO') THEN
106  !
107  SELECT CASE(hsurf(1:3))
108  CASE('DEP')
109  ALLOCATE(pfield(nni,klayer,1))
110  CASE('ALB','WWW')
111  ALLOCATE(pfield(nni,1,1))
112  CASE('HEA','RHO')
113  ALLOCATE(pfield(nni,SIZE(xgrid_snow),1))
114  END SELECT
115  !
116  pfield(:,:,:) = 0.
117 !
118 !-------------------------------------------------------------------------------------
119 !
120 !* 3. Reading of the physical field for vegetated areas
121 ! -------------------------------------------------
122 !
123 ELSE
124 !
125  SELECT CASE(hsurf(1:3))
126 !
127 !* 3.1 Total snow content (kg/m2)
128 !
129  CASE('WWW')
130  CALL read_buffer_snow_veg(kluout,yinmodel,zfield1d)
131  IF ( lextrap_sn ) THEN
132  IF ( SIZE(u%NR_NATURE) /= u%NSIZE_NATURE ) THEN
133  CALL abor1_sfx('ABORT: PREP_ISBA_BUFFER - DIFFERENT SIZES')
134  ELSE
135  ! Allocate working arrays
136  ALLOCATE(zfield_ep(u%NSIZE_NATURE))
137  ALLOCATE(zfield_ep_in(u%NSIZE_NATURE))
138  ALLOCATE(ointerp(u%NSIZE_NATURE))
139  ALLOCATE(zlsm_nature(u%NSIZE_NATURE))
140 
141  ! Read LSM
142  CALL read_buffer_land_mask(kluout,yinmodel,zlsm)
143 
144  ! Pack nature points to reduce dimension to nsize_nature
145  CALL pack_same_rank(u%NR_NATURE,zlsm,zlsm_nature)
146 
147  ! Do extrapolation
148  WRITE(kluout,*) 'Extrapolating WWW from nearest land point in points where LSM < 0.5.'
149 
150  ! Pack nature points to reduce dimension
151  CALL pack_same_rank(u%NR_NATURE,zfield1d(:),zfield_ep(:))
152 
153  ! Set values to be extrapolated
154  ointerp=.false.
155  DO ii=1,u%NSIZE_NATURE
156  IF ( zlsm_nature(ii) < 0.5 ) THEN
157  ointerp(ii) = .true.
158  zfield_ep(ii) = xundef
159  ENDIF
160  ENDDO
161 
162  zfield_ep_in(:) = zfield_ep
163 #ifdef SFX_ARO
164  CALL oi_hor_extrapol_surf(u%NSIZE_NATURE,g%XLAT,g%XLON,zfield_ep_in(:),g%XLAT,g%XLON,zfield_ep(:),ointerp,ndim2=idim2)
165 #endif
166 
167  ! Unpack to full rank
168  CALL unpack_same_rank(u%NR_NATURE,zfield_ep(:),zfield1d(:))
169  DEALLOCATE(zfield_ep)
170  DEALLOCATE(zfield_ep_in)
171  DEALLOCATE(zlsm_nature)
172  DEALLOCATE(ointerp)
173  ENDIF
174  ENDIF
175  !
176  ALLOCATE(pfield(nni,1,1))
177  pfield(:,1,1)=zfield1d(:)
178  DEALLOCATE(zfield1d)
179 !
180 !
181 !* 3.2 Total snow depth (m) to snow layers ticknesses (m)
182 !
183  CASE('DEP')
184  CALL read_buffer_snow_veg_depth(kluout,yinmodel,zfield1d)
185  IF ( lextrap_sn ) THEN
186  IF ( SIZE(u%NR_NATURE) /= u%NSIZE_NATURE ) THEN
187  CALL abor1_sfx('ABORT: PREP_ISBA_BUFFER - DIFFERENT SIZES')
188  ELSE
189  ! Allocate working arrays
190  ALLOCATE(zfield_ep(u%NSIZE_NATURE))
191  ALLOCATE(zfield_ep_in(u%NSIZE_NATURE))
192  ALLOCATE(ointerp(u%NSIZE_NATURE))
193  ALLOCATE(zlsm_nature(u%NSIZE_NATURE))
194 
195  ! Read LSM
196  CALL read_buffer_land_mask(kluout,yinmodel,zlsm)
197 
198  ! Pack nature points to reduce dimension to nsize_nature
199  CALL pack_same_rank(u%NR_NATURE,zlsm,zlsm_nature)
200 
201  ! Do extrapolation
202  WRITE(kluout,*) 'Extrapolating DEP from nearest land point in points where LSM < 0.5.'
203 
204  ! Pack nature points to reduce dimension
205  CALL pack_same_rank(u%NR_NATURE,zfield1d(:),zfield_ep(:))
206  ! Set values to be extrapolated
207  ointerp=.false.
208  DO ii=1,u%NSIZE_NATURE
209  IF ( zlsm_nature(ii) < 0.5 ) THEN
210  ointerp(ii) = .true.
211  zfield_ep(ii) = xundef
212  ENDIF
213  ENDDO
214 
215  zfield_ep_in(:) = zfield_ep
216 #ifdef SFX_ARO
217  CALL oi_hor_extrapol_surf(u%NSIZE_NATURE,g%XLAT,g%XLON,zfield_ep_in(:),g%XLAT,g%XLON,zfield_ep(:),ointerp,ndim2=idim2)
218 #endif
219 
220  ! Unpack to full rank
221  CALL unpack_same_rank(u%NR_NATURE,zfield_ep(:),zfield1d(:))
222  DEALLOCATE(zfield_ep)
223  DEALLOCATE(zfield_ep_in)
224  DEALLOCATE(zlsm_nature)
225  DEALLOCATE(ointerp)
226  ENDIF
227  ENDIF
228 
229  !
230  ALLOCATE(pfield(nni,1,1))
231  pfield(:,1,1) = zfield1d(:)
232  DEALLOCATE(zfield1d)
233 !
234 !
235 !* 3.3 Profile of heat in the snow
236 !
237  CASE('HEA')
238  !* read temperature
239  CALL read_buffer_ts(kluout,yinmodel,zfield1d)
240  WHERE (zfield1d/=xundef) zfield1d(:) = min(zfield1d,xtt)
241  !
242  ALLOCATE(pfield(nni,1,1))
243  pfield(:,1,1)=zfield1d(:)
244  DEALLOCATE(zfield1d)
245 !
246 !* 3.4 Albedo
247 !
248  CASE('ALB')
249  ALLOCATE(pfield(nni,1,1))
250  pfield = 0.5 * ( xansmin + xansmax )
251 !
252 !* 3.5 Density
253 !
254  CASE('RHO')
255  ALLOCATE(pfield(nni,1,1))
256  pfield = xrhosmax
257 
258  END SELECT
259  !
260 END IF
261 !
262 !-------------------------------------------------------------------------------------
263 !
264 !* 4. Interpolation method
265 ! --------------------
266 !
267 cinterp_type='BUFFER'
268 IF (lhook) CALL dr_hook('PREP_SNOW_BUFFER',1,zhook_handle)
269 !
270 !-------------------------------------------------------------------------------------
271 END SUBROUTINE prep_snow_buffer
subroutine read_buffer_land_mask(KLUOUT, HINMODEL, PMASK)
subroutine prep_buffer_grid(KLUOUT, HINMODEL, TPTIME_BUF)
subroutine read_buffer_snow_veg_depth(KLUOUT, HINMODEL, PFIELD)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
subroutine prep_snow_buffer(G, U, HPROGRAM, HSURF, KLUOUT, KLAYER, PFIELD)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine read_buffer_ts(KLUOUT, HINMODEL, PFIELD)
logical lhook
Definition: yomhook.F90:15
real, save xtt
Definition: modd_csts.F90:66
subroutine read_buffer_snow_veg(KLUOUT, HINMODEL, PFIELD)
real, dimension(ngrid_level) xgrid_snow