SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_snow_grib.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_grib(HPROGRAM,HSURF,HFILE,KLUOUT,KLAYER,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_SNOW_GRIB* - prepares snow field from operational GRIB
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! C. Ardilouze 06/2013 read snow albedo and density (for Erai-land)
29 !!------------------------------------------------------------------
30 !
31 !
33 USE mode_snow3l
34 !
36 !
37 USE modi_prep_grib_grid
39 !
40 USE modd_prep, ONLY : cingrid_type, cinterp_type
41 USE modd_prep_snow, ONLY : ngrid_level, xgrid_snow
42 USE modd_data_cover_par, ONLY : nvegtype
43 USE modd_surf_par, ONLY : xundef
44 USE modd_grid_grib, ONLY : cgrib_file, nni
45 USE modd_snow_par, ONLY : xansmin, xansmax, xrhosmax
46 USE modd_csts, ONLY : xtt
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 declarations of arguments
55 !
56  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
57  CHARACTER(LEN=10), INTENT(IN) :: hsurf ! type of field
58  CHARACTER(LEN=28), INTENT(IN) :: hfile ! name of file
59 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
60 INTEGER, INTENT(IN) :: klayer ! Number of layer of output snow scheme
61 REAL,DIMENSION(:,:,:), POINTER :: pfield ! field to interpolate horizontally
62 !
63 !* 0.2 declarations of local variables
64 !
65 TYPE (date_time) :: tztime_grib ! current date and time
66  CHARACTER(LEN=6) :: yinmodel ! model from which GRIB file originates
67 REAL, DIMENSION(:) , POINTER :: zmask => null() ! Land mask
68 REAL, DIMENSION(:), POINTER :: zfield1d => null() ! field read
69 REAL, DIMENSION(:), POINTER :: zheat => null() ! heat in snow
70 REAL, DIMENSION(:), POINTER :: zrho => null() ! density of snow
71 INTEGER :: jvegtype ! loop counter on vegtypes
72 INTEGER :: jlayer ! loop on snow fine grid
73 REAL(KIND=JPRB) :: zhook_handle
74 !
75 !-------------------------------------------------------------------------------------
76 !
77 !* 1. Reading of grid
78 ! ---------------
79 !
80 IF (lhook) CALL dr_hook('PREP_SNOW_GRIB',0,zhook_handle)
81 !
82 IF (trim(hfile).NE.cgrib_file) cgrib_file=""
83 !
84  CALL prep_grib_grid(hfile,kluout,yinmodel,cingrid_type,tztime_grib)
85 !
86  CALL read_grib_land_mask(hfile,kluout,yinmodel,zmask)
87 !
88 !-------------------------------------------------------------------------------------
89 !
90 !* 2. Reading of the physical field for urban areas
91 ! ---------------------------------------------
92 !
93 IF (hsurf(7:8)=='RO') THEN
94  !
95  SELECT CASE(hsurf(1:3))
96  CASE('DEP')
97  ALLOCATE(pfield(nni,klayer,1))
98  CASE('ALB','WWW')
99  ALLOCATE(pfield(nni,1,1))
100  CASE('HEA','RHO')
101  ALLOCATE(pfield(nni,ngrid_level,1))
102  END SELECT
103  !
104  pfield(:,:,:) = 0.
105 !
106 !-------------------------------------------------------------------------------------
107 !
108 !* 3. Reading of the physical field for vegetated areas
109 ! -------------------------------------------------
110 !
111 ELSE
112 !
113  SELECT CASE(hsurf(1:3))
114 !
115 !* 3.1 Total snow content (kg/m2)
116 !
117  CASE('WWW')
118  CALL read_grib_snow_veg_and_depth(hfile,kluout,yinmodel,zmask,psnv=zfield1d)
119  !
120  ALLOCATE(pfield(SIZE(zfield1d),1,nvegtype))
121  DO jvegtype=1,nvegtype
122  pfield(:,1,jvegtype)=zfield1d(:)
123  END DO
124  DEALLOCATE(zfield1d)
125 !
126 !
127 !* 3.2 Total snow depth (m)
128 !
129  CASE('DEP')
130  CALL read_grib_snow_veg_and_depth(hfile,kluout,yinmodel,zmask,psnvd=zfield1d)
131  !
132  ALLOCATE(pfield(SIZE(zfield1d),klayer,nvegtype))
133  DO jvegtype=1,nvegtype
134  CALL snow3lgrid(pfield(:,:,jvegtype),zfield1d(:))
135  END DO
136  DEALLOCATE(zfield1d)
137 !
138 !
139 !* 3.3 Profile of heat in the snow
140 !
141  CASE('HEA')
142  !* read temperature
143  CALL read_grib_ts(hfile,kluout,yinmodel,zmask,zfield1d)
144  WHERE (zfield1d/=xundef) zfield1d(:) = min(zfield1d,xtt)
145  !* assumes no liquid water in the snow
146  ALLOCATE(zheat(SIZE(zfield1d)))
147  CALL read_grib_snow_den(hfile,kluout,yinmodel,zmask,zrho)
148  WHERE(zfield1d(:)==xundef)zrho(:)=xundef
149  !
150  CALL snow_t_wliq_to_heat(zheat,zrho,zfield1d)
151  !
152  ALLOCATE(pfield(SIZE(zfield1d),ngrid_level,nvegtype))
153  DO jvegtype=1,nvegtype
154  DO jlayer=1,ngrid_level
155  pfield(:,jlayer,jvegtype)=zheat(:)
156  END DO
157  END DO
158  DEALLOCATE(zfield1d)
159  DEALLOCATE(zheat )
160  DEALLOCATE(zrho )
161 !
162 !* 3.4 Albedo
163 !
164  CASE('ALB')
165  CALL read_grib_snow_alb(hfile,kluout,yinmodel,zmask,zfield1d)
166  ALLOCATE(pfield(SIZE(zfield1d),1,nvegtype))
167  DO jvegtype=1,nvegtype
168  pfield(:,1,jvegtype)=zfield1d(:)
169  END DO
170  DEALLOCATE(zfield1d)
171 !
172 !* 3.5 Density
173 !
174  CASE('RHO')
175  CALL read_grib_snow_den(hfile,kluout,yinmodel,zmask,zfield1d)
176  ALLOCATE(pfield(SIZE(zfield1d),1,nvegtype))
177  DO jvegtype=1,nvegtype
178  pfield(:,1,jvegtype)=zfield1d(:)
179  END DO
180  DEALLOCATE(zfield1d)
181 !
182 !* 3.6 SG1: initial grain is partially rounded
183 !
184  CASE('SG1')
185  ALLOCATE(pfield(nni,ngrid_level,nvegtype))
186  pfield = -20
187 !
188 !* 3.7 SG2: initial grain is partially rounded
189 !
190  CASE('SG2')
191  ALLOCATE(pfield(nni,ngrid_level,nvegtype))
192  pfield = 80
193 !
194 !* 3.8 AGE: snow is 3-days old
195 !
196  CASE('AGE')
197  ALLOCATE(pfield(nni,ngrid_level,nvegtype))
198  pfield = 3
199 !
200 !* 3.9 HIS: 0 by default
201 !
202  CASE('HIS')
203  ALLOCATE(pfield(nni,ngrid_level,nvegtype))
204  pfield = 0
205 !
206  END SELECT
207 !
208 END IF
209 !
210 DEALLOCATE(zmask)
211 !
212 !-------------------------------------------------------------------------------------
213 !
214 !* 4. Interpolation method
215 ! --------------------
216 !
217  cinterp_type='HORIBL'
218 !
219 IF (lhook) CALL dr_hook('PREP_SNOW_GRIB',1,zhook_handle)
220 !
221 !-------------------------------------------------------------------------------------
222 END SUBROUTINE prep_snow_grib
subroutine read_grib_land_mask(HGRIB, KLUOUT, HINMODEL, PMASK)
subroutine read_grib_snow_alb(HGRIB, KLUOUT, HINMODEL, PMASK, PSNVA)
subroutine prep_snow_grib(HPROGRAM, HSURF, HFILE, KLUOUT, KLAYER, PFIELD)
subroutine prep_grib_grid(HGRIB, KLUOUT, HINMODEL, HGRIDTYPE, TPTIME_GRIB)
subroutine read_grib_ts(HGRIB, KLUOUT, HINMODEL, PMASK, PTS)
subroutine read_grib_snow_den(HGRIB, KLUOUT, HINMODEL, PMASK, PSNV)
subroutine read_grib_snow_veg_and_depth(HGRIB, KLUOUT, HINMODEL, PMASK, PSNV, PSNVD)