SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_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_TEB_GREENROOF - declaration of ISBA scheme packed surface parameters for urban green roofs
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! AUTHOR
23 !! ------
24 !! A. Lemonsu *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 09/2009
29 !! C. de Munck 06/2011
30 !! V. Masson 06/2013 splits module in 4
31 !!
32 !-------------------------------------------------------------------------------
33 !
34 !* 0. DECLARATIONS
35 ! ------------
36 !
38 !
39 !
40 USE yomhook ,ONLY : lhook, dr_hook
41 USE parkind1 ,ONLY : jprb
42 !
43 IMPLICIT NONE
44 
46 !-------------------------------------------------------------------------------
47 !
48 ! Prognostic variables:
49 !
50 ! - Snow Cover:
51 !
52  TYPE(surf_snow) :: TSNOW ! snow state:
53  ! scheme type/option (-)
54  ! number of layers (-)
55  ! snow (& liq. water) content (kg/m2)
56  ! heat content (J/m2)
57  ! temperature (K)
58  ! density (kg m-3)
59 !
60 ! - Soil and vegetation heat and water:
61 !
62  REAL, POINTER, DIMENSION(:) :: XWR ! liquid water retained on the
63  ! foliage of the vegetation
64  ! canopy (kg/m2)
65  REAL, POINTER, DIMENSION(:,:) :: XTG ! surface and sub-surface soil
66  ! temperature profile (K)
67  REAL, POINTER, DIMENSION(:,:) :: XWG ! soil volumetric water content profile (m3/m3)
68  REAL, POINTER, DIMENSION(:,:) :: XWGI ! soil liquid water equivalent volumetric
69  ! ice content profile (m3/m3)
70  REAL, POINTER, DIMENSION(:) :: XRESA ! aerodynamic resistance (s/m)
71 !
72 
73 ! - Vegetation: Ags Prognostic (YPHOTO = 'AGS', 'LAI', 'AST', 'LST', 'NIT', 'NCB')
74 !
75  REAL, POINTER, DIMENSION(:) :: XAN ! net CO2 assimilation (mg/m2/s)
76  REAL, POINTER, DIMENSION(:) :: XANDAY ! daily net CO2 assimilation (mg/m2)
77  REAL, POINTER, DIMENSION(:) :: XANFM ! maximum leaf assimilation (mg/m2/s)
78  REAL, POINTER, DIMENSION(:) :: XLE ! evapotranspiration (W/m2)
79  REAL, POINTER, DIMENSION(:) :: XFAPARC ! Fapar of vegetation (cumul)
80  REAL, POINTER, DIMENSION(:) :: XFAPIRC ! Fapir of vegetation (cumul)
81  REAL, POINTER, DIMENSION(:) :: XLAI_EFFC ! Effective LAI (cumul)
82  REAL, POINTER, DIMENSION(:) :: XMUS ! cos zenithal angle (cumul)
83 !
84 ! - Vegetation: Ags Prognostic (YPHOTO = 'NIT', 'NCB')
85 !
86  REAL, POINTER, DIMENSION(:,:) :: XRESP_BIOMASS ! daily cumulated respiration of
87  ! biomass (kg/m2/s)
88  REAL, POINTER, DIMENSION(:,:) :: XBIOMASS ! biomass of previous day (kg/m2)
89 !
90 ! - SGH scheme
91 !
92  REAL, POINTER, DIMENSION(:) :: XKSAT_ICE ! hydraulic conductivity at saturation
93  ! over frozen area (m s-1)
94 !-------------------------------------------------------------------------------
95 !
96 ! - Snow and flood fractions and total albedo at time t:
97 !
98  REAL, POINTER, DIMENSION(:) :: XPSNG ! Snow fraction over ground
99  REAL, POINTER, DIMENSION(:) :: XPSNV ! Snow fraction over vegetation
100  REAL, POINTER, DIMENSION(:) :: XPSNV_A ! Snow fraction over vegetation
101  REAL, POINTER, DIMENSION(:) :: XPSN ! Total Snow fraction
102 !
103  REAL, POINTER, DIMENSION(:) :: XSNOWFREE_ALB ! snow free albedo (-)
104  REAL, POINTER, DIMENSION(:) :: XSNOWFREE_ALB_VEG ! snow free albedo for vegetation (-)
105  REAL, POINTER, DIMENSION(:) :: XSNOWFREE_ALB_SOIL ! snow free albedo for soil (-)
106 !
107 !-------------------------------------------------------------------------------
108 !
109 END TYPE teb_greenroof_1p_t
110 !
112  !
113  TYPE(teb_greenroof_1p_t), POINTER :: ALP(:) => NULL()
114  TYPE(teb_greenroof_1p_t), POINTER :: CUR => NULL()
115  !
116 END TYPE teb_greenroof_t
117 !
118  CONTAINS
119 !
120 !
121 SUBROUTINE teb_greenroof_goto_patch(YTEB_GREENROOF,KTO_PATCH)
122  TYPE(teb_greenroof_t), INTENT(INOUT) :: yteb_greenroof
123 INTEGER, INTENT(IN) :: kto_patch
124 REAL(KIND=JPRB) :: zhook_handle
125 !
126 ! Current patch is set to patch KTO_PATCH
127 IF (lhook) CALL dr_hook('MODD_TEB_GREENROOF_N:TEB_GREENROOF_GOTO_PATCH',0,zhook_handle)
128 
129 yteb_greenroof%CUR => yteb_greenroof%ALP(kto_patch)
130 
131 IF (lhook) CALL dr_hook('MODD_TEB_GREENROOF_N:TEB_GREENROOF_GOTO_PATCH',1,zhook_handle)
132 !
133 END SUBROUTINE teb_greenroof_goto_patch
134 !
135 SUBROUTINE teb_greenroof_init(YTEB_GREENROOF,KPATCH)
136 TYPE(teb_greenroof_t), INTENT(INOUT) :: yteb_greenroof
137 INTEGER, INTENT(IN) :: kpatch
138 INTEGER :: jp
139 REAL(KIND=JPRB) :: zhook_handle
140 IF (lhook) CALL dr_hook("MODD_TEB_GREENROOF_N:TEB_GREENROOF_INIT",0,zhook_handle)
141  ALLOCATE(yteb_greenroof%ALP(kpatch))
142  yteb_greenroof%CUR => yteb_greenroof%ALP(1)
143 DO jp=1,kpatch
144  nullify(yteb_greenroof%ALP(jp)%XWR)
145  nullify(yteb_greenroof%ALP(jp)%XTG)
146  nullify(yteb_greenroof%ALP(jp)%XWG)
147  nullify(yteb_greenroof%ALP(jp)%XWGI)
148  nullify(yteb_greenroof%ALP(jp)%XRESA)
149  nullify(yteb_greenroof%ALP(jp)%XAN)
150  nullify(yteb_greenroof%ALP(jp)%XANDAY)
151  nullify(yteb_greenroof%ALP(jp)%XANFM)
152  nullify(yteb_greenroof%ALP(jp)%XLE)
153  nullify(yteb_greenroof%ALP(jp)%XFAPARC)
154  nullify(yteb_greenroof%ALP(jp)%XFAPIRC)
155  nullify(yteb_greenroof%ALP(jp)%XLAI_EFFC)
156  nullify(yteb_greenroof%ALP(jp)%XMUS)
157  nullify(yteb_greenroof%ALP(jp)%XRESP_BIOMASS)
158  nullify(yteb_greenroof%ALP(jp)%XBIOMASS)
159  nullify(yteb_greenroof%ALP(jp)%XKSAT_ICE)
160  nullify(yteb_greenroof%ALP(jp)%XPSNG)
161  nullify(yteb_greenroof%ALP(jp)%XPSNV)
162  nullify(yteb_greenroof%ALP(jp)%XPSNV_A)
163  nullify(yteb_greenroof%ALP(jp)%XPSN)
164  nullify(yteb_greenroof%ALP(jp)%XSNOWFREE_ALB)
165  nullify(yteb_greenroof%ALP(jp)%XSNOWFREE_ALB_VEG)
166  nullify(yteb_greenroof%ALP(jp)%XSNOWFREE_ALB_SOIL)
167 ENDDO
168 IF (lhook) CALL dr_hook("MODD_TEB_GREENROOF_N:TEB_GREENROOF_INIT",1,zhook_handle)
169 END SUBROUTINE teb_greenroof_init
170 
171 
172 END MODULE modd_teb_greenroof_n
subroutine teb_greenroof_goto_patch(YTEB_GREENROOF, KTO_PATCH)
subroutine teb_greenroof_init(YTEB_GREENROOF, KPATCH)