SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_diag_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_DIAG_TEB_GREENROOF - declaration of diagnostics for ISBA scheme
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !! Based on modd_diag_teb_gardenn
22 !!
23 !! AUTHOR
24 !! ------
25 !! C. de Munck & A. Lemonsu *Meteo France
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 07/2011
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 USE yomhook ,ONLY : lhook, dr_hook
35 USE parkind1 ,ONLY : jprb
36 !
37 IMPLICIT NONE
38 
40 !------------------------------------------------------------------------------
41 !
42 !* variables for one patch
43 !
44  REAL, POINTER, DIMENSION(:) :: XRI ! Bulk-Richardson number (-)
45  REAL, POINTER, DIMENSION(:) :: XCD ! drag coefficient for wind (W/s2)
46  REAL, POINTER, DIMENSION(:) :: XCH ! drag coefficient for heat (W/s)
47  REAL, POINTER, DIMENSION(:) :: XCE ! drag coefficient for vapor (W/s/K)
48  REAL, POINTER, DIMENSION(:) :: XRN ! net radiation at surface (W/m2)
49  REAL, POINTER, DIMENSION(:) :: XH ! sensible heat flux (W/m2)
50  REAL, POINTER, DIMENSION(:) :: XGFLUX ! net soil-vegetation flux (W/m2)
51  REAL, POINTER, DIMENSION(:) :: XTS ! surface temperature (K)
52  REAL, POINTER, DIMENSION(:) :: XTSRAD ! radiative surface temperature (K)
53  REAL, POINTER, DIMENSION(:) :: XQS ! humidity at surface (kg/kg)
54  REAL, POINTER, DIMENSION(:) :: XLWD ! downward long wave radiation (W/m2)
55  REAL, POINTER, DIMENSION(:) :: XLWU ! upward long wave radiation (W/m2)
56  REAL, POINTER, DIMENSION(:) :: XSWD ! downward short wave radiation (W/m2)
57  REAL, POINTER, DIMENSION(:) :: XSWU ! upward short wave radiation (W/m2)
58  REAL, POINTER, DIMENSION(:,:) :: XSWBD ! downward short wave radiation by spectral band (W/m2)
59  REAL, POINTER, DIMENSION(:,:) :: XSWBU ! upward short wave radiation by spectral band (W/m2)
60  REAL, POINTER, DIMENSION(:) :: XFMU ! horizontal momentum flux zonal (m2/s2)
61  REAL, POINTER, DIMENSION(:) :: XFMV ! horizontal momentum flux meridian (m2/s2)
62  !
63  REAL, POINTER, DIMENSION(:) :: XZ0_WITH_SNOW ! roughness length for momentum
64  ! for vegetation and snow (m)
65  REAL, POINTER, DIMENSION(:) :: XZ0H_WITH_SNOW ! roughness length for heat
66  ! for vegetation and snow (m)
67  REAL, POINTER, DIMENSION(:) :: XZ0EFF ! effective roughness length for heat
68  ! for vegetation and snow (m)
69 !
70  REAL, POINTER, DIMENSION(:) :: XLEI ! sublimation latent heat flux (W/m2)
71  REAL, POINTER, DIMENSION(:) :: XLEG ! latent heat of evaporation over the ground (W/m2)
72  REAL, POINTER, DIMENSION(:) :: XLEGI ! surface soil ice sublimation (W/m2)
73  REAL, POINTER, DIMENSION(:) :: XLEV ! latent heat of evaporation over vegetation (W/m2)
74  REAL, POINTER, DIMENSION(:) :: XLES ! latent heat of evaporation over the snow (W/m2)
75  REAL, POINTER, DIMENSION(:) :: XLER ! evaporation from canopy water interception (W/m2)
76  REAL, POINTER, DIMENSION(:) :: XLETR ! evapotranspiration of the vegetation (W/m2)
77  REAL, POINTER, DIMENSION(:) :: XEVAP ! evapotranspiration (W/m2)
78  REAL, POINTER, DIMENSION(:) :: XDRAIN ! soil drainage flux (kg/m2/s)
79  REAL, POINTER, DIMENSION(:) :: XRUNOFF ! sub-grid and supersaturation runoff (kg/m2/s)
80  REAL, POINTER, DIMENSION(:) :: XHORT ! sub-grid Horton runoff from the SGH scheme (kg/m2/s)
81  REAL, POINTER, DIMENSION(:) :: XRRVEG ! precipitation intercepted by the vegetation (kg/m2/s)
82  REAL, POINTER, DIMENSION(:) :: XMELT ! snow melt (kg/m2/s)
83  REAL, POINTER, DIMENSION(:) :: XDRIP ! dripping from the vegetation reservoir (kg/m2/s)
84 !
85 !* pack diag
86 !
87  REAL, POINTER, DIMENSION(:) :: XCG ! heat capacity of the ground
88  REAL, POINTER, DIMENSION(:) :: XC1 ! coefficients for the moisure
89  REAL, POINTER, DIMENSION(:) :: XC2 ! equation.
90  REAL, POINTER, DIMENSION(:) :: XWGEQ ! equilibrium volumetric water content
91  REAL, POINTER, DIMENSION(:) :: XCT ! area-averaged heat capacity
92  REAL, POINTER, DIMENSION(:) :: XRS ! stomatal resistance (s/m)
93  REAL, POINTER, DIMENSION(:) :: XCDN ! neutral drag coefficient (-)
94  REAL, POINTER, DIMENSION(:) :: XHU ! area averaged surface humidity coefficient (-)
95  REAL, POINTER, DIMENSION(:) :: XHUG ! baresoil surface humidity coefficient (-)
96  REAL, POINTER, DIMENSION(:) :: XRESTORE ! surface energy budget restore term (W/m2)
97  REAL, POINTER, DIMENSION(:) :: XUSTAR ! friction velocity (m/s)
98  REAL, POINTER, DIMENSION(:,:) :: XIACAN ! PAR in the canopy at different gauss level (micmolphot/m2/s)
99 !
100 ! for ISBA-ES:3-L
101  REAL, POINTER, DIMENSION(:,:) :: XSNOWTEMP ! snow temperature profile (ISBA-ES:3-L) (K)
102  REAL, POINTER, DIMENSION(:,:) :: XSNOWLIQ ! snow liquid water profile (ISBA-ES:3-L) (m)
103  REAL, POINTER, DIMENSION(:,:) :: XSNOWDZ ! snow layer thicknesses (m)
104  REAL, POINTER, DIMENSION(:) :: XSNOWHMASS ! heat content change due to mass changes in snowpack (J/m2)
105  REAL, POINTER, DIMENSION(:) :: XMELTADV ! advective energy from snow melt water!
106 !
107 !* budget summation variables for one patch
108 !
109 !
110  REAL, POINTER, DIMENSION(:) :: XHV ! Halstead coefficient
111 !
112  REAL, POINTER, DIMENSION(:,:) :: XSWI ! Soil wetness index
113  REAL, POINTER, DIMENSION(:,:) :: XTSWI ! Total soil wetness index
114 !
115  REAL, POINTER, DIMENSION(:) :: XTWSNOW ! Total snow reservoir
116  REAL, POINTER, DIMENSION(:) :: XTDSNOW ! Total snow height
117 !
118  REAL, POINTER, DIMENSION(:) :: XALBT ! Total Albedo
119  REAL, POINTER, DIMENSION(:) :: XEMIST ! averaged emissivity (-)
120 !
121  REAL, POINTER, DIMENSION(:) :: XSEUIL ! Irrigation threshold
122 !
123  REAL, POINTER, DIMENSION(:) :: XGPP ! Gross Primary Production
124  REAL, POINTER, DIMENSION(:) :: XRESP_AUTO ! Autotrophic respiration
125  REAL, POINTER, DIMENSION(:) :: XRESP_ECO ! Ecosystem respiration
126 !
127 !------------------------------------------------------------------------------
128 !
129 
130 END TYPE diag_teb_greenroof_t
131 
132 
133 
134  CONTAINS
135 
136 !
137 
138 
139 
140 
141 SUBROUTINE diag_teb_greenroof_init(YDIAG_TEB_GREENROOF)
142 TYPE(diag_teb_greenroof_t), INTENT(INOUT) :: ydiag_teb_greenroof
143 REAL(KIND=JPRB) :: zhook_handle
144 IF (lhook) CALL dr_hook("MODD_DIAG_TEB_GREENROOF_N:DIAG_TEB_GREENROOF_INIT",0,zhook_handle)
145  nullify(ydiag_teb_greenroof%XRI)
146  nullify(ydiag_teb_greenroof%XCD)
147  nullify(ydiag_teb_greenroof%XCH)
148  nullify(ydiag_teb_greenroof%XCE)
149  nullify(ydiag_teb_greenroof%XRN)
150  nullify(ydiag_teb_greenroof%XH)
151  nullify(ydiag_teb_greenroof%XGFLUX)
152  nullify(ydiag_teb_greenroof%XTS)
153  nullify(ydiag_teb_greenroof%XTSRAD)
154  nullify(ydiag_teb_greenroof%XQS)
155  nullify(ydiag_teb_greenroof%XLWD)
156  nullify(ydiag_teb_greenroof%XLWU)
157  nullify(ydiag_teb_greenroof%XSWD)
158  nullify(ydiag_teb_greenroof%XSWU)
159  nullify(ydiag_teb_greenroof%XSWBD)
160  nullify(ydiag_teb_greenroof%XSWBU)
161  nullify(ydiag_teb_greenroof%XFMU)
162  nullify(ydiag_teb_greenroof%XFMV)
163  nullify(ydiag_teb_greenroof%XZ0_WITH_SNOW)
164  nullify(ydiag_teb_greenroof%XZ0H_WITH_SNOW)
165  nullify(ydiag_teb_greenroof%XZ0EFF)
166  nullify(ydiag_teb_greenroof%XLEI)
167  nullify(ydiag_teb_greenroof%XLEG)
168  nullify(ydiag_teb_greenroof%XLEGI)
169  nullify(ydiag_teb_greenroof%XLEV)
170  nullify(ydiag_teb_greenroof%XLES)
171  nullify(ydiag_teb_greenroof%XLER)
172  nullify(ydiag_teb_greenroof%XLETR)
173  nullify(ydiag_teb_greenroof%XEVAP)
174  nullify(ydiag_teb_greenroof%XDRAIN)
175  nullify(ydiag_teb_greenroof%XRUNOFF)
176  nullify(ydiag_teb_greenroof%XHORT)
177  nullify(ydiag_teb_greenroof%XRRVEG)
178  nullify(ydiag_teb_greenroof%XMELT)
179  nullify(ydiag_teb_greenroof%XDRIP)
180  nullify(ydiag_teb_greenroof%XCG)
181  nullify(ydiag_teb_greenroof%XC1)
182  nullify(ydiag_teb_greenroof%XC2)
183  nullify(ydiag_teb_greenroof%XWGEQ)
184  nullify(ydiag_teb_greenroof%XCT)
185  nullify(ydiag_teb_greenroof%XRS)
186  nullify(ydiag_teb_greenroof%XCDN)
187  nullify(ydiag_teb_greenroof%XHU)
188  nullify(ydiag_teb_greenroof%XHUG)
189  nullify(ydiag_teb_greenroof%XRESTORE)
190  nullify(ydiag_teb_greenroof%XUSTAR)
191  nullify(ydiag_teb_greenroof%XIACAN)
192  nullify(ydiag_teb_greenroof%XSNOWTEMP)
193  nullify(ydiag_teb_greenroof%XSNOWLIQ)
194  nullify(ydiag_teb_greenroof%XSNOWDZ)
195  nullify(ydiag_teb_greenroof%XSNOWHMASS)
196  nullify(ydiag_teb_greenroof%XMELTADV)
197  nullify(ydiag_teb_greenroof%XHV)
198  nullify(ydiag_teb_greenroof%XSWI)
199  nullify(ydiag_teb_greenroof%XTSWI)
200  nullify(ydiag_teb_greenroof%XTWSNOW)
201  nullify(ydiag_teb_greenroof%XTDSNOW)
202  nullify(ydiag_teb_greenroof%XALBT)
203  nullify(ydiag_teb_greenroof%XEMIST)
204  nullify(ydiag_teb_greenroof%XSEUIL)
205  nullify(ydiag_teb_greenroof%XGPP)
206  nullify(ydiag_teb_greenroof%XRESP_AUTO)
207  nullify(ydiag_teb_greenroof%XRESP_ECO)
208 IF (lhook) CALL dr_hook("MODD_DIAG_TEB_GREENROOF_N:DIAG_TEB_GREENROOF_INIT",1,zhook_handle)
209 END SUBROUTINE diag_teb_greenroof_init
210 
211 
212 END MODULE modd_diag_teb_greenroof_n
subroutine diag_teb_greenroof_init(YDIAG_TEB_GREENROOF)