SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_isba_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_isba_grib(HPROGRAM,HSURF,HFILE,KLUOUT,PFIELD,OKEY)
7 ! #################################################################################
8 !
9 !!**** *PREP_ISBA_GRIB* - initializes ISBA fields 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 !! S. Riette 04/2010 READ_GRIB_WGI_ECMWF interface changed
29 !!------------------------------------------------------------------
30 !
32 !
34 !
35 USE modi_prep_grib_grid
37 !
38 USE modd_prep, ONLY : cingrid_type, cinterp_type
39 USE modd_prep_isba, ONLY : xgrid_soil, xwr_def, xwrv_def, &
40  xwrvn_def, xqc_def
41 USE modd_surf_par, ONLY : xundef
42 USE modd_grid_grib, ONLY : cgrib_file, nni
43 !
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 !
48 USE modi_abor1_sfx
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 declarations of arguments
53 !
54  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
55  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
56  CHARACTER(LEN=28), INTENT(IN) :: hfile ! name of file
57 INTEGER, INTENT(IN) :: kluout ! logical unit of output listing
58 REAL,DIMENSION(:,:,:), POINTER :: pfield ! field to interpolate horizontally
59 LOGICAL, OPTIONAL, INTENT(INOUT) :: okey
60 !
61 !* 0.2 declarations of local variables
62 !
63 TYPE (date_time) :: tztime_grib ! current date and time
64  CHARACTER(LEN=6) :: yinmodel ! model from which GRIB file originates
65 REAL, DIMENSION(:) , POINTER :: zmask => null() ! Land mask
66 REAL, DIMENSION(:,:), POINTER :: zfield => null() ! field read
67 REAL, DIMENSION(:), POINTER :: zfield1d => null() ! field read
68 REAL, DIMENSION(:,:), POINTER :: zd => null() ! layer thicknesses
69 INTEGER :: jvegtype ! loop counter on vegtypes
70 REAL(KIND=JPRB) :: zhook_handle
71 !
72 !-------------------------------------------------------------------------------------
73 !
74 !* 1. Reading of grid
75 ! ---------------
76 !
77 IF (lhook) CALL dr_hook('PREP_ISBA_GRIB',0,zhook_handle)
78 !
79 IF (trim(hfile).NE.cgrib_file) cgrib_file=""
80 !
81  CALL prep_grib_grid(hfile,kluout,yinmodel,cingrid_type,tztime_grib)
82 !
83  CALL read_grib_land_mask(hfile,kluout,yinmodel,zmask)
84 !
85 !
86 !* 2. Reading of field
87 ! ----------------
88 !
89 !* 3. Transformation into physical quantity to be interpolated
90 ! --------------------------------------------------------
91 !
92 SELECT CASE(hsurf)
93 !
94 !* 3.1 Profile of temperature in the soil
95 !
96  CASE('TG ')
97  !* reading of the profile and its depth definition
98  SELECT CASE(yinmodel)
99  CASE('ECMWF ')
100  IF(present(okey))okey=.false.
101  CALL read_grib_tg_ecmwf(hfile,kluout,yinmodel,zmask,zfield,zd)
102  CASE('ARPEGE','ALADIN','MOCAGE')
103  CALL read_grib_tg_meteo_france(hfile,kluout,yinmodel,zmask,zfield,zd)
104  CASE('HIRLAM')
105  CALL read_grib_tg_hirlam(hfile,kluout,yinmodel,zmask,zfield,zd)
106  END SELECT
107  CALL soil_profile_grib
108 
109  CASE('WG ')
110  !* reading of the profile and its depth definition
111  SELECT CASE(yinmodel)
112  CASE('ECMWF ')
113  IF(present(okey))okey=.false.
114  CALL read_grib_wg_ecmwf(hfile,kluout,yinmodel,zmask,zfield,zd)
115  CASE('ARPEGE','ALADIN','MOCAGE')
116  CALL read_grib_wg_meteo_france(hfile,kluout,yinmodel,zmask,zfield,zd)
117  CASE('HIRLAM')
118  CALL read_grib_wg_hirlam(hfile,kluout,yinmodel,zmask,zfield,zd)
119  END SELECT
120  CALL soil_profile_grib
121 
122 !* 3.3 Profile of soil ice content
123 
124  CASE('WGI ')
125  !* reading of the profile and its depth definition
126  SELECT CASE(yinmodel)
127  CASE('ECMWF ')
128  IF(present(okey))okey=.false.
129  CALL read_grib_wgi_ecmwf(hfile,kluout,yinmodel,zmask,zfield,zd)
130  CASE('ARPEGE','ALADIN','MOCAGE')
131  CALL read_grib_wgi_meteo_france(hfile,kluout,yinmodel,zmask,zfield,zd)
132  CASE('HIRLAM')
133  CALL read_grib_wgi_hirlam(hfile,kluout,zfield,zd)
134  END SELECT
135  CALL soil_profile_grib
136 !
137 !* 3.4 Water content intercepted on leaves, LAI
138 !
139  CASE('WR ')
140  ALLOCATE(pfield(nni,1,1))
141  pfield(:,:,:) = xwr_def
142 !
143  CASE('LAI ')
144  ALLOCATE(pfield(nni,1,1))
145  pfield(:,:,:) = xundef
146 !
147 !
148 !* 3.5 Other fields
149 !
150  CASE('ZS ')
151  CALL read_grib_zs_land(hfile,kluout,yinmodel,zmask,zfield1d)
152  ALLOCATE(pfield(SIZE(zfield1d,1),1,1))
153  pfield(:,1,1)=zfield1d(:)
154  DEALLOCATE(zfield1d)
155 !
156  CASE('ICE_STO')
157  ALLOCATE(pfield(nni,1,1))
158  pfield(:,:,:) = 0.0
159 !
160 !* 3.6 MEB fields
161 !
162  CASE('WRV ')
163  ALLOCATE(pfield(nni,1,1))
164  pfield(:,:,:) = xwrv_def
165 !
166  CASE('WRVN ')
167  ALLOCATE(pfield(nni,1,1))
168  pfield(:,:,:) = xwrvn_def
169 !
170  CASE('QC ')
171  ALLOCATE(pfield(nni,1,1))
172  pfield(:,:,:) = xqc_def
173 !
174  CASE('TV ','TC ')
175  !* reading of the profile and its depth definition
176  SELECT CASE(yinmodel)
177  CASE('ECMWF ')
178  IF(present(okey))okey=.false.
179  CALL read_grib_tg_ecmwf(hfile,kluout,yinmodel,zmask,zfield,zd)
180  CASE('ARPEGE','ALADIN','MOCAGE')
181  CALL read_grib_tg_meteo_france(hfile,kluout,yinmodel,zmask,zfield,zd)
182  CASE('HIRLAM')
183  CALL read_grib_tg_hirlam(hfile,kluout,yinmodel,zmask,zfield,zd)
184  END SELECT
185  ALLOCATE(pfield(nni,1,1))
186  pfield(:,1,1) =zfield(:,1)
187  DEALLOCATE(zfield)
188  DEALLOCATE(zd)
189 !
190  CASE default
191  CALL abor1_sfx('PREP_ISBA_GRIB: '//trim(hsurf)//" initialization not implemented !")
192 !
193 END SELECT
194 !
195 DEALLOCATE(zmask)
196 !
197 !* 4. Interpolation method
198 ! --------------------
199 !
200  cinterp_type='HORIBL'
201 !
202 !-------------------------------------------------------------------------------------
203 !-------------------------------------------------------------------------------------
204 !
205 IF (lhook) CALL dr_hook('PREP_ISBA_GRIB',1,zhook_handle)
206  CONTAINS
207 !
208 !-------------------------------------------------------------------------------------
209 !-------------------------------------------------------------------------------------
211 !-------------------------------------------------------------------------------------
212 !
213 REAL, DIMENSION(:,:), ALLOCATABLE :: zout ! work array
214 REAL(KIND=JPRB) :: zhook_handle
215 !
216 !-------------------------------------------------------------------------------------
217 !
218  !
219  !* interpolation on fine vertical grid
220  IF (lhook) CALL dr_hook('SOIL_PROFILE_GRIB',0,zhook_handle)
221  ALLOCATE(zout(SIZE(zfield,1),SIZE(xgrid_soil)))
222  CALL interp_grid_nat(zd,zfield,xgrid_soil,zout)
223  !
224  !* extends definition to all vegtypes.
225  ALLOCATE(pfield(SIZE(zfield,1),SIZE(xgrid_soil),1))
226  pfield(:,:,1)=zout(:,:)
227  !* end
228  DEALLOCATE(zout)
229  DEALLOCATE(zfield)
230  DEALLOCATE(zd)
231 IF (lhook) CALL dr_hook('SOIL_PROFILE_GRIB',1,zhook_handle)
232 
233 END SUBROUTINE soil_profile_grib
234 !
235 !-------------------------------------------------------------------------------------
236 END SUBROUTINE prep_isba_grib
subroutine prep_isba_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD, OKEY)
subroutine read_grib_zs_land(HGRIB, KLUOUT, HINMODEL, PMASK, PZSL)
subroutine read_grib_wg_hirlam(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_tg_meteo_france(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PDT)
subroutine soil_profile_grib
subroutine read_grib_wgi_meteo_france(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_land_mask(HGRIB, KLUOUT, HINMODEL, PMASK)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine read_grib_wgi_hirlam(HGRIB, KLUOUT, PFIELD, PD)
subroutine read_grib_wg_meteo_france(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_tg_ecmwf(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PD)
subroutine read_grib_wgi_ecmwf(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_wg_ecmwf(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_tg_hirlam(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PDT)
subroutine prep_grib_grid(HGRIB, KLUOUT, HINMODEL, HGRIDTYPE, TPTIME_GRIB)