SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_data_teb_greenroofn.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 ! ##################
7 ! ##################
8 !
9 !!**** *MODD_DATA_ISBA - declaration of DATA surface parameters for ISBA scheme
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 05/2005
29 !! A. Lemonsu / C. de Munck 04/2011 : TEB GreenRoof
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 !
35 USE yomhook ,ONLY : lhook, dr_hook
36 USE parkind1 ,ONLY : jprb
37 !
38 IMPLICIT NONE
39 
41 !-------------------------------------------------------------------------------
42 !
43 
44  REAL, POINTER, DIMENSION(:,:) :: XPAR_OM_GR ! fraction of organic matter (OM) in green roof layer
45  REAL, POINTER, DIMENSION(:,:) :: XPAR_CLAY_GR ! fraction of clay for the non-OM part of the green roof layer
46  REAL, POINTER, DIMENSION(:,:) :: XPAR_SAND_GR ! fraction of sand for the non-OM part of the green roof layer
47  REAL, POINTER, DIMENSION(:,:) :: XPAR_LAI_GR ! LAI of green roof vegetation
48 !
49 !
50 ! Mask and number of grid elements containing patches/tiles:
51 !
52  REAL, POINTER, DIMENSION(:,:) :: XPAR_VEGTYPE ! fraction of each vegetation type for
53  ! each grid mesh (-)
54 !
55 !-------------------------------------------------------------------------------
56 !
57 ! Input Parameters, per patch:
58 !
59 ! - vegetation + bare soil:
60 !
61  REAL, POINTER, DIMENSION(:) :: XPAR_Z0_O_Z0H ! ratio of surface roughness lengths
62  ! (momentum to heat) (-)
63  REAL, POINTER, DIMENSION(:,:) :: XPAR_EMIS ! surface emissivity (-)
64  REAL, POINTER, DIMENSION(:,:) :: XPAR_Z0 ! surface roughness length (m)
65 !
66 ! - vegetation:
67 !
68  REAL, POINTER, DIMENSION(:) :: XPAR_ALBNIR_VEG ! vegetation near-infra-red albedo (-)
69  REAL, POINTER, DIMENSION(:) :: XPAR_ALBVIS_VEG ! vegetation visible albedo (-)
70  REAL, POINTER, DIMENSION(:) :: XPAR_ALBUV_VEG ! vegetation UV albedo (-)
71 !
72 ! - vegetation: default option (Jarvis) and general parameters:
73 !
74  REAL, POINTER, DIMENSION(:,:) :: XPAR_VEG ! vegetation cover fraction (-)
75  REAL, POINTER, DIMENSION(:) :: XPAR_WRMAX_CF ! coefficient for maximum water
76  ! interception
77  ! storage capacity on the vegetation (-)
78  REAL, POINTER, DIMENSION(:) :: XPAR_RSMIN ! minimum stomatal resistance (s/m)
79  REAL, POINTER, DIMENSION(:) :: XPAR_GAMMA ! coefficient for the calculation
80  ! of the surface stomatal
81  ! resistance
82  REAL, POINTER, DIMENSION(:) :: XPAR_CV ! vegetation thermal inertia coefficient (K m2/J)
83  REAL, POINTER, DIMENSION(:) :: XPAR_RGL ! maximum solar radiation
84  ! usable in photosynthesis (W/m2)
85  REAL, POINTER, DIMENSION(:,:) :: XPAR_ROOTFRAC ! root fraction profile ('DIF' option)
86 !
87 !-------------------------------------------------------------------------------
88 !
89 ! - vegetation: Ags parameters ('AGS', 'LAI', 'AST', 'LST', 'NIT', 'NCB' options)
90 !
91  REAL, POINTER, DIMENSION(:) :: XPAR_BSLAI ! ratio d(biomass)/d(lai) (kg/m2)
92  REAL, POINTER, DIMENSION(:) :: XPAR_LAIMIN ! minimum LAI (Leaf Area Index) (m2/m2)
93  REAL, POINTER, DIMENSION(:) :: XPAR_SEFOLD ! e-folding time for senescence (s)
94  REAL, POINTER, DIMENSION(:) :: XPAR_H_TREE ! height of trees (m)
95  REAL, POINTER, DIMENSION(:) :: XPAR_GMES ! mesophyll conductance (m s-1)
96  REAL, POINTER, DIMENSION(:) :: XPAR_RE25 ! Ecosystem respiration parameter (kg m2 s-1)
97 !
98 !-------------------------------------------------------------------------------
99 !
100 ! - vegetation: Ags Stress parameters ('AST', 'LST', 'NIT', 'NCB' options)
101 !
102  LOGICAL, POINTER, DIMENSION(:) :: LDATA_STRESS ! vegetation response type to water
103  ! stress (true:defensive false:offensive) (-)
104  REAL, POINTER, DIMENSION(:) :: XPAR_F2I ! critical normilized soil water
105  ! content for stress parameterisation
106  REAL, POINTER, DIMENSION(:) :: XPAR_GC ! cuticular conductance (m s-1)
107  REAL, POINTER, DIMENSION(:) :: XPAR_DMAX ! maximum air saturation deficit
108  ! tolerate by vegetation (kg/kg)
109 !
110  REAL, POINTER, DIMENSION(:) :: XPAR_BSLAI_ST ! ratio d(biomass)/d(lai) (kg/m2)
111  REAL, POINTER, DIMENSION(:) :: XPAR_SEFOLD_ST ! e-folding time for senescence (s)
112  REAL, POINTER, DIMENSION(:) :: XPAR_GMES_ST ! mesophyll conductance (m s-1)
113  REAL, POINTER, DIMENSION(:) :: XPAR_GC_ST ! cuticular conductance (m s-1)
114  REAL, POINTER, DIMENSION(:) :: XPAR_DMAX_ST ! maximum air saturation deficit
115 !-------------------------------------------------------------------------------
116 !
117 ! - vegetation: Ags Nitrogen-model parameters ('NIT', 'NCB' option)
118 !
119  REAL, POINTER, DIMENSION(:) :: XPAR_CE_NITRO ! leaf aera ratio sensitivity to
120  ! nitrogen concentration (m2/kg)
121  REAL, POINTER, DIMENSION(:) :: XPAR_CF_NITRO ! lethal minimum value of leaf area
122  ! ratio (m2/kg)
123  REAL, POINTER, DIMENSION(:) :: XPAR_CNA_NITRO ! nitrogen concentration of active
124  ! biomass (kg/kg)
125 !
126 !-------------------------------------------------------------------------------
127 !
128 ! - soil: primary parameters
129 !
130  REAL, POINTER, DIMENSION(:,:) :: XPAR_DG ! soil layer thicknesses (m)
131  ! NOTE: in Force-Restore mode, the
132  ! uppermost layer thickness is superficial
133  ! and is only explicitly used for soil
134  ! water phase changes (m)
135 !
136  REAL, POINTER,DIMENSION(:) :: XPAR_DICE ! depth of the soil column for the calculation
137  ! of the frozen soil fraction (m)
138 !
139 ! - bare soil albedo
140 !
141  REAL, POINTER, DIMENSION(:) :: XPAR_ALBNIR_SOIL ! soil near-infra-red albedo (-)
142  REAL, POINTER, DIMENSION(:) :: XPAR_ALBVIS_SOIL ! soil visible albedo (-)
143  REAL, POINTER, DIMENSION(:) :: XPAR_ALBUV_SOIL ! soil UV albedo (-)
144  REAL, POINTER, DIMENSION(:) :: XPAR_ALBNIR_DRY ! dry soil near-infra-red albedo (-)
145  REAL, POINTER, DIMENSION(:) :: XPAR_ALBVIS_DRY ! dry soil visible albedo (-)
146  REAL, POINTER, DIMENSION(:) :: XPAR_ALBUV_DRY ! dry soil UV albedo (-)
147  REAL, POINTER, DIMENSION(:) :: XPAR_ALBNIR_WET ! wet soil near-infra-red albedo (-)
148  REAL, POINTER, DIMENSION(:) :: XPAR_ALBVIS_WET ! wet soil visible albedo (-)
149  REAL, POINTER, DIMENSION(:) :: XPAR_ALBUV_WET ! wet soil UV albedo (-)
150 !
151 !-------------------------------------------------------------------------------
152 !
153 !- Vegetation: Ags Prognostic (YPHOTO = ('LAI', 'LST', 'NIT', or 'NCB') or prescribed (YPHOTO='NON', 'AGS' or 'AST')
154 !
155  REAL, POINTER, DIMENSION(:,:) :: XPAR_LAI ! Leaf Area Index (m2/m2)
156 !
157 !-------------------------------------------------------------------------------
158 !
159 
160 END TYPE data_teb_greenroof_t
161 
162 
163 
164  CONTAINS
165 
166 !
167 
168 
169 
170 
171 SUBROUTINE data_teb_greenroof_init(YDATA_TEB_GREENROOF)
172 TYPE(data_teb_greenroof_t), INTENT(INOUT) :: ydata_teb_greenroof
173 REAL(KIND=JPRB) :: zhook_handle
174 IF (lhook) CALL dr_hook("MODD_DATA_TEB_GREENROOF_N:DATA_TEB_GREENROOF_INIT",0,zhook_handle)
175  nullify(ydata_teb_greenroof%XPAR_OM_GR)
176  nullify(ydata_teb_greenroof%XPAR_CLAY_GR)
177  nullify(ydata_teb_greenroof%XPAR_SAND_GR)
178  nullify(ydata_teb_greenroof%XPAR_LAI_GR)
179  nullify(ydata_teb_greenroof%XPAR_VEGTYPE)
180  nullify(ydata_teb_greenroof%XPAR_Z0_O_Z0H)
181  nullify(ydata_teb_greenroof%XPAR_EMIS)
182  nullify(ydata_teb_greenroof%XPAR_Z0)
183  nullify(ydata_teb_greenroof%XPAR_ALBNIR_VEG)
184  nullify(ydata_teb_greenroof%XPAR_ALBVIS_VEG)
185  nullify(ydata_teb_greenroof%XPAR_ALBUV_VEG)
186  nullify(ydata_teb_greenroof%XPAR_VEG)
187  nullify(ydata_teb_greenroof%XPAR_WRMAX_CF)
188  nullify(ydata_teb_greenroof%XPAR_RSMIN)
189  nullify(ydata_teb_greenroof%XPAR_GAMMA)
190  nullify(ydata_teb_greenroof%XPAR_CV)
191  nullify(ydata_teb_greenroof%XPAR_RGL)
192  nullify(ydata_teb_greenroof%XPAR_ROOTFRAC)
193  nullify(ydata_teb_greenroof%XPAR_BSLAI)
194  nullify(ydata_teb_greenroof%XPAR_LAIMIN)
195  nullify(ydata_teb_greenroof%XPAR_SEFOLD)
196  nullify(ydata_teb_greenroof%XPAR_H_TREE)
197  nullify(ydata_teb_greenroof%XPAR_GMES)
198  nullify(ydata_teb_greenroof%XPAR_RE25)
199  nullify(ydata_teb_greenroof%LDATA_STRESS)
200  nullify(ydata_teb_greenroof%XPAR_F2I)
201  nullify(ydata_teb_greenroof%XPAR_GC)
202  nullify(ydata_teb_greenroof%XPAR_DMAX)
203  nullify(ydata_teb_greenroof%XPAR_BSLAI_ST)
204  nullify(ydata_teb_greenroof%XPAR_SEFOLD_ST)
205  nullify(ydata_teb_greenroof%XPAR_GMES_ST)
206  nullify(ydata_teb_greenroof%XPAR_GC_ST)
207  nullify(ydata_teb_greenroof%XPAR_DMAX_ST)
208  nullify(ydata_teb_greenroof%XPAR_CE_NITRO)
209  nullify(ydata_teb_greenroof%XPAR_CF_NITRO)
210  nullify(ydata_teb_greenroof%XPAR_CNA_NITRO)
211  nullify(ydata_teb_greenroof%XPAR_DG)
212  nullify(ydata_teb_greenroof%XPAR_DICE)
213  nullify(ydata_teb_greenroof%XPAR_ALBNIR_SOIL)
214  nullify(ydata_teb_greenroof%XPAR_ALBVIS_SOIL)
215  nullify(ydata_teb_greenroof%XPAR_ALBUV_SOIL)
216  nullify(ydata_teb_greenroof%XPAR_ALBNIR_DRY)
217  nullify(ydata_teb_greenroof%XPAR_ALBVIS_DRY)
218  nullify(ydata_teb_greenroof%XPAR_ALBUV_DRY)
219  nullify(ydata_teb_greenroof%XPAR_ALBNIR_WET)
220  nullify(ydata_teb_greenroof%XPAR_ALBVIS_WET)
221  nullify(ydata_teb_greenroof%XPAR_ALBUV_WET)
222  nullify(ydata_teb_greenroof%XPAR_LAI)
223 IF (lhook) CALL dr_hook("MODD_DATA_TEB_GREENROOF_N:DATA_TEB_GREENROOF_INIT",1,zhook_handle)
224 END SUBROUTINE data_teb_greenroof_init
225 
226 
227 END MODULE modd_data_teb_greenroof_n
subroutine data_teb_greenroof_init(YDATA_TEB_GREENROOF)