SURFEX v8.1
General documentation of Surfex
prep_teb_garden.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 (DTCO, UG, U, USS, GCP, TG, TOP, IO, S, K, P, PEK, &
7  HPROGRAM,HATMFILE,HATMFILETYPE,HPGDFILE,HPGDFILETYPE,KPATCH,YDCTL)
8 ! #################################################################################
9 !
10 !!**** *PREP_TEB_GARDEN* - Prepares ISBA fields
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !! Modified by P. Le Moigne (11/2004): AGS fields
30 !! Modified by B. Decharme (2008) : Floodplains
31 !! Modified by B. Decharme (01/2009): Consistency with Arpege deep soil
32 !! temperature
33 !! Modified by B. Decharme (03/2009): Consistency with Arpege permanent
34 !! snow/ice treatment
35 !! P. Marguinaud10/2014, Support for a 2-part PREP
36 !!------------------------------------------------------------------
37 !
38 !
41 USE modd_surf_atm_n, ONLY : surf_atm_t
42 USE modd_sso_n, ONLY : sso_t
44 !
45 USE modd_sfx_grid_n, ONLY : grid_t
46 !
48 !
51 !
52 USE modi_prep_hor_teb_garden_field
53 USE modi_prep_ver_teb_veg
54 !
55 USE modd_surf_atm, ONLY : lvertshift
56 !
57  ! A FAIRE :
58  ! IL FAUT RAJOUTER TSNOW
59  ! ----------------------
60 USE modd_csts, ONLY : xtt
61 USE modd_snow_par, ONLY : xz0sn
62 USE modd_isba_par, ONLY : xwgmin
63 USE modd_co2v_par, ONLY : xanfminit, xca_nit, xcc_nit
64 USE modd_surf_par, ONLY : xundef
65 !
66 USE mode_prep_ctl, ONLY : prep_ctl
67 !
69 USE mode_pos_surf
70 !
71 USE yomhook ,ONLY : lhook, dr_hook
72 USE parkind1 ,ONLY : jprb
73 !
74 IMPLICIT NONE
75 !
76 !* 0.1 declarations of arguments
77 !
78 !
79 !
80 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
81 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
82 TYPE(surf_atm_t), INTENT(INOUT) :: U
83 TYPE(sso_t), INTENT(INOUT) :: USS
84 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
85 TYPE(grid_t), INTENT(INOUT) :: TG
86 TYPE(teb_options_t), INTENT(INOUT) :: TOP
87 !
88 TYPE(isba_options_t), INTENT(INOUT) :: IO
89 TYPE(isba_s_t), INTENT(INOUT) :: S
90 TYPE(isba_k_t), INTENT(INOUT) :: K
91 TYPE(isba_p_t), INTENT(INOUT) :: P
92 TYPE(isba_pe_t), INTENT(INOUT) :: PEK
93 !
94 type(prep_ctl), INTENT(INOUT) :: ydctl
95 !
96  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
97  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! name of the Atmospheric file
98  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! type of the Atmospheric file
99  CHARACTER(LEN=28), INTENT(IN) :: HPGDFILE ! name of the Atmospheric file
100  CHARACTER(LEN=6), INTENT(IN) :: HPGDFILETYPE! type of the Atmospheric file
101 !
102 INTEGER, INTENT(IN) :: KPATCH
103 !
104 !* 0.2 declarations of local variables
105 !
106 REAL(KIND=JPRB) :: ZHOOK_HANDLE
107 !
108 !-------------------------------------------------------------------------------------
109 !
110 !* 1. Default of configuration
111 !
112 !* 1.1 Default
113 !
114 !
115 !-------------------------------------------------------------------------------------
116 !
117 !* 2. Reading and horizontal interpolations
118 !
119 !
120 !* 2.1 Soil Water reservoirs
121 !
122 IF (lhook) CALL dr_hook('PREP_TEB_GARDEN',0,zhook_handle)
123  CALL prep_hor_teb_garden_field(dtco, ug, u, uss, gcp, io, s, k, p, pek, tg, top, &
124  hprogram,'WG ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,kpatch,ydctl)
125 !
126 !* 2.2 Soil ice reservoirs
127 !
128  CALL prep_hor_teb_garden_field(dtco, ug, u, uss, gcp, io, s, k, p, pek, tg, top, &
129  hprogram,'WGI ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,kpatch,ydctl)
130 !
131 !* 2.3 Leaves interception water reservoir
132 !
133  CALL prep_hor_teb_garden_field(dtco, ug, u, uss, gcp, io, s, k, p, pek, tg, top, &
134  hprogram,'WR ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,kpatch,ydctl)
135 !
136 !* 2.4 Temperature profile
137 !
138  CALL prep_hor_teb_garden_field(dtco, ug, u, uss, gcp, io, s, k, p, pek, tg, top, &
139  hprogram,'TG ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,kpatch,ydctl)
140 !
141 !* 2.5 Snow variables
142 !
143  CALL prep_hor_teb_garden_field(dtco, ug, u, uss, gcp, io, s, k, p, pek, tg, top, &
144  hprogram,'SN_VEG ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,kpatch,ydctl)
145 
146 !
147 !* 2.6 LAI
148 !
149 IF (io%CPHOTO/='NON') &
150  CALL prep_hor_teb_garden_field(dtco, ug, u, uss, gcp, io, s, k, p, pek, tg, top, &
151  hprogram,'LAI ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,kpatch,ydctl)
152 !
153 !-------------------------------------------------------------------------------------
154 !
155 !* 3. Physical limitation:
156 !
157 ! If whole ice reservoir is empty (grib from ecmwf case) and surface temperature is
158 ! lower than -10C, then ice content is maximum and water content minimum
159 !
160 IF (all(pek%XWGI(:,:)==0.)) THEN
161  WHERE(pek%XTG(:,1:SIZE(pek%XWG,2)) < xtt-10.)
162  pek%XWGI(:,:) = k%XWSAT(:,:)-xwgmin
163  pek%XWG (:,:) = xwgmin
164  END WHERE
165 ENDIF
166 !
167 ! No ice for force restore third layer:
168 IF (io%CISBA == '3-L') THEN
169  WHERE(pek%XWG(:,3)/=xundef.AND.pek%XWGI(:,3)/=xundef)
170  pek%XWG(:,3) = min(pek%XWG(:,3)+pek%XWGI(:,3),k%XWSAT(:,3))
171  pek%XWGI(:,3) = 0.
172  END WHERE
173 ENDIF
174 !
175 ! Total water content should not exceed saturation:
176 WHERE(pek%XWG(:,:) /= xundef .AND. (pek%XWG(:,:) + pek%XWGI(:,:)) > k%XWSAT(:,:) )
177  pek%XWGI(:,:) = k%XWSAT(:,:) - pek%XWG(:,:)
178 END WHERE
179 !
180 !-------------------------------------------------------------------------------------
181 !
182 !* 3. Vertical interpolations of all variables
183 !
184 IF(lvertshift)THEN
185  CALL prep_ver_teb_veg(p, pek, io, top%XZS)
186 ENDIF
187 !
188 !
189 !-------------------------------------------------------------------------------------
190 !
191 !* 5. Half prognostic fields
192 !
193 ALLOCATE(pek%XRESA(SIZE(pek%XLAI)))
194 pek%XRESA = 100.
195 !
196 !-------------------------------------------------------------------------------------
197 !
198 !* 6. Isba-Ags prognostic fields
199 !
200 IF (io%CPHOTO /= 'NON') THEN
201 !
202  ALLOCATE(pek%XAN(SIZE(pek%XLAI)))
203  pek%XAN = 0.
204 !
205  ALLOCATE(pek%XANDAY(SIZE(pek%XLAI)))
206  pek%XANDAY = 0.
207 !
208  ALLOCATE(pek%XANFM(SIZE(pek%XLAI)))
209  pek%XANFM = xanfminit
210 !
211  ALLOCATE(pek%XLE(SIZE(pek%XLAI)))
212  pek%XLE = 0.
213 !
214 ENDIF
215 !
216 IF (io%CPHOTO == 'AST') THEN
217 !
218  ALLOCATE(pek%XBIOMASS(SIZE(pek%XLAI),io%NNBIOMASS))
219  pek%XBIOMASS(:,1) = 0.
220 !
221  ALLOCATE(pek%XRESP_BIOMASS(SIZE(pek%XLAI),io%NNBIOMASS))
222  pek%XRESP_BIOMASS(:,:) = 0.
223 !
224 ELSEIF (io%CPHOTO == 'NIT' .OR. io%CPHOTO == 'NCB') THEN
225 !
226  ALLOCATE(pek%XBIOMASS(SIZE(pek%XLAI),io%NNBIOMASS))
227  pek%XBIOMASS(:,1) = pek%XLAI(:) * p%XBSLAI_NITRO(:)
228  pek%XBIOMASS(:,2) = max( 0., (pek%XBIOMASS(:,1)/ (xcc_nit/10.**xca_nit)) &
229  **(1.0/(1.0-xca_nit)) - pek%XBIOMASS(:,1) )
230  pek%XBIOMASS(:,3:io%NNBIOMASS) = 0.
231 !
232  ALLOCATE(pek%XRESP_BIOMASS(SIZE(pek%XLAI),io%NNBIOMASS))
233  pek%XRESP_BIOMASS(:,:) = 0.
234 !
235 ENDIF
236 !
237 !-------------------------------------------------------------------------------------
238 !
239 IF (lhook) CALL dr_hook('PREP_TEB_GARDEN',1,zhook_handle)
240 !
241 !-------------------------------------------------------------------------------------
242 !
243 END SUBROUTINE prep_teb_garden
subroutine prep_hor_teb_garden_field(DTCO, UG, U, USS, GCP, IO, S, K, P, PEK, TG, TOP, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, KPATCH, YDCTL)
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine prep_teb_garden(DTCO, UG, U, USS, GCP, TG, TOP, IO, S, K, P, PEK, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, KPATCH, YDCTL)
logical lhook
Definition: yomhook.F90:15
subroutine prep_ver_teb_veg(P, PEK, IO, PZS)
logical lvertshift
real, save xtt
Definition: modd_csts.F90:66