SURFEX v8.1
General documentation of Surfex
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 !
35 !
37 USE modd_surf_par, ONLY : xundef
39 USE modd_snow_par, ONLY : xansmin, xansmax, xrhosmax
40 USE modd_csts, ONLY : xtt
41 !
42 !
43 USE yomhook ,ONLY : lhook, dr_hook
44 USE parkind1 ,ONLY : jprb
45 !
46 IMPLICIT NONE
47 !
48 !* 0.1 declarations of arguments
49 !
50  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
51  CHARACTER(LEN=10), INTENT(IN) :: HSURF ! type of field
52  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! name of file
53 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
54 INTEGER, INTENT(IN) :: KLAYER ! Number of layer of output snow scheme
55 REAL,DIMENSION(:,:,:), POINTER :: PFIELD ! field to interpolate horizontally
56 !
57 !* 0.2 declarations of local variables
58 !
59 REAL, DIMENSION(:) , POINTER :: ZMASK => null() ! Land mask
60 REAL, DIMENSION(:), POINTER :: ZFIELD1D => null() ! field read
61 REAL, DIMENSION(:), POINTER :: ZHEAT => null() ! heat in snow
62 REAL, DIMENSION(:), POINTER :: ZRHO => null() ! density of snow
63 INTEGER :: JVEGTYPE ! loop counter on vegtypes
64 INTEGER :: JLAYER ! loop on snow fine grid
65 REAL(KIND=JPRB) :: ZHOOK_HANDLE
66 !
67 !-------------------------------------------------------------------------------------
68 !
69 !* 1. Reading of grid
70 ! ---------------
71 !
72 IF (lhook) CALL dr_hook('PREP_SNOW_GRIB',0,zhook_handle)
73 !
74 IF (trim(hfile).NE.cgrib_file) cgrib_file=""
75 !
76  CALL read_grib_land_mask(hfile,kluout,cinmodel,zmask)
77 !
78 !-------------------------------------------------------------------------------------
79 !
80 !* 2. Reading of the physical field for urban areas
81 ! ---------------------------------------------
82 !
83 IF (hsurf(7:8)=='RO') THEN
84  !
85  SELECT CASE(hsurf(1:3))
86  CASE('DEP')
87  ALLOCATE(pfield(nni,1,1))
88  CASE('ALB','WWW')
89  ALLOCATE(pfield(nni,1,1))
90  CASE('HEA','RHO')
91  ALLOCATE(pfield(nni,1,1))
92  END SELECT
93  !
94  pfield(:,:,:) = 0.
95 !
96 !-------------------------------------------------------------------------------------
97 !
98 !* 3. Reading of the physical field for vegetated areas
99 ! -------------------------------------------------
100 !
101 ELSE
102 !
103  SELECT CASE(hsurf(1:3))
104 !
105 !* 3.1 Total snow content (kg/m2)
106 !
107  CASE('WWW')
108  CALL read_grib_snow_veg_and_depth(hfile,kluout,cinmodel,zmask,psnv=zfield1d)
109  !
110  ALLOCATE(pfield(SIZE(zfield1d),1,1))
111  pfield(:,1,1)=zfield1d(:)
112  DEALLOCATE(zfield1d)
113 !
114 !
115 !* 3.2 Total snow depth (m)
116 !
117  CASE('DEP')
118  CALL read_grib_snow_veg_and_depth(hfile,kluout,cinmodel,zmask,psnvd=zfield1d)
119  !
120  ALLOCATE(pfield(SIZE(zfield1d),1,1))
121  pfield(:,1,1)=zfield1d(:)
122  DEALLOCATE(zfield1d)
123 !
124 !
125 !* 3.3 Profile of heat in the snow
126 !
127  CASE('HEA')
128  !* read temperature
129  CALL read_grib_ts(hfile,kluout,cinmodel,zmask,zfield1d)
130  WHERE (zfield1d/=xundef) zfield1d(:) = min(zfield1d,xtt)
131  !
132  ALLOCATE(pfield(SIZE(zfield1d),1,1))
133  pfield(:,1,1)=zfield1d(:)
134  DEALLOCATE(zfield1d)
135 !
136 !* 3.4 Albedo
137 !
138  CASE('ALB')
139  CALL read_grib_snow_alb(hfile,kluout,cinmodel,zmask,zfield1d)
140  ALLOCATE(pfield(SIZE(zfield1d),1,1))
141  pfield(:,1,1)=zfield1d(:)
142  DEALLOCATE(zfield1d)
143 !
144 !* 3.5 Density
145 !
146  CASE('RHO')
147  CALL read_grib_snow_den(hfile,kluout,cinmodel,zmask,zfield1d)
148  ALLOCATE(pfield(SIZE(zfield1d),1,1))
149  pfield(:,1,1)=zfield1d(:)
150  DEALLOCATE(zfield1d)
151 !
152 !* 3.6 SG1: initial grain is partially rounded
153 !
154  CASE('SG1')
155  ALLOCATE(pfield(nni,1,1))
156  pfield = -20
157 !
158 !* 3.7 SG2: initial grain is partially rounded
159 !
160  CASE('SG2')
161  ALLOCATE(pfield(nni,1,1))
162  pfield = 80
163 !
164 !* 3.8 AGE: snow is 3-days old
165 !
166  CASE('AGE')
167  ALLOCATE(pfield(nni,1,1))
168  pfield = 3
169 !
170 !* 3.9 HIS: 0 by default
171 !
172  CASE('HIS')
173  ALLOCATE(pfield(nni,1,1))
174  pfield = 0
175 !
176  END SELECT
177 !
178 END IF
179 !
180 DEALLOCATE(zmask)
181 !
182 !-------------------------------------------------------------------------------------
183 !
184 !* 4. Interpolation method
185 ! --------------------
186 !
187 IF (lhook) CALL dr_hook('PREP_SNOW_GRIB',1,zhook_handle)
188 !
189 !-------------------------------------------------------------------------------------
190 END SUBROUTINE prep_snow_grib
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
character(len=28) cgrib_file
subroutine read_grib_ts(HGRIB, KLUOUT, HINMODEL, PMASK, PTS)
real, parameter xundef
character(len=6) cinmodel
subroutine prep_snow_grib(HPROGRAM, HSURF, HFILE, KLUOUT, KLAYER, PFIELD)
subroutine read_grib_snow_alb(HGRIB, KLUOUT, HINMODEL, PMASK, PSNVA)
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter ngrid_level
subroutine read_grib_snow_veg_and_depth(HGRIB, KLUOUT, HINMODEL, PMASK, PSNV, PSNVD)
subroutine read_grib_snow_den(HGRIB, KLUOUT, HINMODEL, PMASK, PSNV)
logical lhook
Definition: yomhook.F90:15
subroutine read_grib_land_mask(HGRIB, KLUOUT, HINMODEL, PMASK)
real, save xtt
Definition: modd_csts.F90:66
real, dimension(ngrid_level) xgrid_snow