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