SURFEX v8.1
General documentation of Surfex
prep_teb_garden_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_teb_garden_grib(HPROGRAM,HSURF,HFILE,KLUOUT,PFIELD)
7 ! #################################################################################
8 !
9 !!**** *PREP_TEB_GARDEN_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 05/2010 READ_GRIB_WGI_ECMWF's interface modified
29 !!------------------------------------------------------------------
30 !
31 
32 !
34 !
36 !
38 !
39 USE modd_prep_teb_garden,ONLY : xgrid_soil, xwr_def
40 USE modd_surf_par, ONLY : xundef
42 !
43 !
44 USE yomhook ,ONLY : lhook, dr_hook
45 USE parkind1 ,ONLY : jprb
46 !
47 USE modi_abor1_sfx
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 declarations of arguments
52 !
53  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
54  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
55  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! name of file
56 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
57 REAL,DIMENSION(:,:,:), POINTER :: PFIELD ! field to interpolate horizontally
58 !
59 !* 0.2 declarations of local variables
60 !
61 REAL, DIMENSION(:) , POINTER :: ZMASK => null() ! Land mask
62 REAL, DIMENSION(:,:), POINTER :: ZFIELD => null() ! field read
63 REAL, DIMENSION(:), POINTER :: ZFIELD1D => null() ! field read
64 REAL, DIMENSION(:,:), POINTER :: ZD => null() ! depth of field in the soil
65 INTEGER :: JVEGTYPE ! loop counter on vegtypes
66 REAL(KIND=JPRB) :: ZHOOK_HANDLE
67 !
68 !-------------------------------------------------------------------------------------
69 !
70 !* 1. Reading of grid
71 ! ---------------
72 !
73 IF (lhook) CALL dr_hook('PREP_TEB_GARDEN_GRIB',0,zhook_handle)
74 !
75 IF (trim(hfile).NE.cgrib_file) cgrib_file=""
76 !
77  CALL read_grib_land_mask(hfile,kluout,cinmodel,zmask)
78 !
79 !* 2. Reading of field
80 ! ----------------
81 !
82 !* 3. Transformation into physical quantity to be interpolated
83 ! --------------------------------------------------------
84 !
85 SELECT CASE(hsurf)
86 !
87 !* 3.1 Profile of temperature in the soil
88 !
89  CASE('TG ')
90  !* reading of the profile and its depth definition
91  SELECT CASE(cinmodel)
92  CASE('ECMWF ')
93  CALL read_grib_tg_ecmwf(hfile,kluout,cinmodel,zmask,zfield,zd)
94  CASE('ARPEGE','ALADIN','MOCAGE')
95  CALL read_grib_tg_meteo_france(hfile,kluout,cinmodel,zmask,zfield,zd)
96  CASE('HIRLAM')
97  CALL read_grib_tg_hirlam(hfile,kluout,cinmodel,zmask,zfield,zd)
98  END SELECT
100 
101  CASE('WG ')
102  !* reading of the profile and its depth definition
103  SELECT CASE(cinmodel)
104  CASE('ECMWF ')
105  CALL read_grib_wg_ecmwf(hfile,kluout,cinmodel,zmask,zfield,zd)
106  CASE('ARPEGE','ALADIN','MOCAGE')
107  CALL read_grib_wg_meteo_france(hfile,kluout,cinmodel,zmask,zfield,zd)
108  CASE('HIRLAM')
109  CALL read_grib_wg_hirlam(hfile,kluout,cinmodel,zmask,zfield,zd)
110  END SELECT
111  CALL soil_profile_grib
112 
113 
114 !* 3.3 Profile of soil ice content
115 
116  CASE('WGI ')
117  !* reading of the profile and its depth definition
118  SELECT CASE(cinmodel)
119  CASE('ECMWF ')
120  CALL read_grib_wgi_ecmwf(hfile,kluout,cinmodel,zmask,zfield,zd)
121  CASE('ARPEGE','ALADIN','MOCAGE')
122  CALL read_grib_wgi_meteo_france(hfile,kluout,cinmodel,zmask,zfield,zd)
123  CASE('HIRLAM')
124  CALL read_grib_wgi_hirlam(hfile,kluout,zfield,zd)
125  END SELECT
126  CALL soil_profile_grib
127 !
128 !* 3.4 Water content intercepted on leaves, LAI
129 !
130  CASE('WR ')
131  ALLOCATE(pfield(nni,1,1))
132  pfield(:,:,:) = xwr_def
133 !
134  CASE('LAI ')
135  ALLOCATE(pfield(nni,1,1))
136  pfield(:,:,:) = xundef
137 !
138 !
139 !* 3.5 Other fields
140 !
141  CASE('ZS ')
142  CALL read_grib_zs_land(hfile,kluout,cinmodel,zmask,zfield1d)
143  ALLOCATE(pfield(SIZE(zfield1d,1),1,1))
144  pfield(:,1,1)=zfield1d(:)
145  DEALLOCATE(zfield1d)
146 
147  CASE DEFAULT
148  CALL abor1_sfx('PREP_TEB_GARDEN_GRIB: OPTION NOT SUPPORTED - '//hsurf)
149 
150 END SELECT
151 !
152 DEALLOCATE(zmask)
153 !
154 !* 4. Interpolation method
155 ! --------------------
156 !
157 !-------------------------------------------------------------------------------------
158 !-------------------------------------------------------------------------------------
159 !
160 IF (lhook) CALL dr_hook('PREP_TEB_GARDEN_GRIB',1,zhook_handle)
161 CONTAINS
162 !
163 !-------------------------------------------------------------------------------------
164 !-------------------------------------------------------------------------------------
165 SUBROUTINE soil_profile_grib
166 !-------------------------------------------------------------------------------------
167 !
168 REAL, DIMENSION(:,:), ALLOCATABLE :: ZOUT ! work array
169 REAL(KIND=JPRB) :: ZHOOK_HANDLE
170 !
171 !-------------------------------------------------------------------------------------
172 !
173  !
174  !* interpolation on fine vertical grid
175  IF (lhook) CALL dr_hook('SOIL_PROFILE_GRIB',0,zhook_handle)
176  ALLOCATE(zout(SIZE(zfield,1),SIZE(xgrid_soil)))
177  CALL interp_grid_nat(zd,zfield,xgrid_soil,zout)
178  !
179  !* extends definition to all vegtypes.
180  ALLOCATE(pfield(SIZE(zfield,1),SIZE(xgrid_soil),1))
181  pfield(:,:,1)=zout(:,:)
182  !* end
183  DEALLOCATE(zout)
184  DEALLOCATE(zfield)
185  DEALLOCATE(zd)
186 IF (lhook) CALL dr_hook('SOIL_PROFILE_GRIB',1,zhook_handle)
187 
188 END SUBROUTINE soil_profile_grib
189 !
190 !-------------------------------------------------------------------------------------
191 END SUBROUTINE prep_teb_garden_grib
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
character(len=28) cgrib_file
subroutine read_grib_tg_meteo_france(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PDT)
subroutine read_grib_zs_land(HGRIB, KLUOUT, HINMODEL, PMASK, PZSL)
subroutine soil_profile_grib
subroutine read_grib_wgi_ecmwf(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
character(len=6) cinmodel
subroutine read_grib_tg_hirlam(HGRIB, KLUOUT, HINMODEL, PMASK, PTG, PDT)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine read_grib_land_mask(HGRIB, KLUOUT, HINMODEL, PMASK)
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_wg_hirlam(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_wgi_hirlam(HGRIB, KLUOUT, PFIELD, PD)
subroutine read_grib_wgi_meteo_france(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine read_grib_wg_ecmwf(HGRIB, KLUOUT, HINMODEL, PMASK, PFIELD, PD)
subroutine prep_teb_garden_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)