SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_teb_optionn.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_n - declaration of surface parameters for urban surface
10 !!
11 !! PURPOSE
12 !! -------
13 ! Declaration of surface parameters
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! V. Masson *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2004
30 !! A. Lemonsu 07/2012 Key for urban hydrology
31 !! V. Masson 06/2013 splits module
32 !
33 !* 0. DECLARATIONS
34 ! ------------
35 !
37 !
38 !
39 USE yomhook ,ONLY : lhook, dr_hook
40 USE parkind1 ,ONLY : jprb
41 !
42 IMPLICIT NONE
43 
44 
46 ! TEB scheme option
47 !
48  LOGICAL :: LCANOPY ! T: SBL scheme within the canopy
49  ! F: no atmospheric layers below forcing level
50  LOGICAL :: LGARDEN ! T: Urban green areas (call ISBA from TEB)
51  ! F: No urban green areas
52  CHARACTER(LEN=4) :: CROAD_DIR ! TEB option for road directions
53  ! 'UNIF' : no specific direction
54  ! 'ORIE' : many road ORIEntations
55  ! ( one per TEB patch)
56  CHARACTER(LEN=4) :: CWALL_OPT ! TEB option for walls
57  ! 'UNIF' : uniform walls
58  ! 'TWO ' : two separated walls
59  CHARACTER(LEN=3) :: CBLD_ATYPE ! Type of averaging for walls
60  ! 'ARI' : Characteristics are
61  ! linearly averaged
62  ! 'MAJ ' : Majoritary building in
63  ! grid mesh is chosen
64  CHARACTER(LEN=6) :: CZ0H ! TEB option for z0h roof & road
65  ! 'MASC95' : Mascart et al 1995
66  ! 'BRUT82' : Brustaert 1982
67  ! 'KAND07' : Kanda 2007
68  CHARACTER(LEN=5) :: CCH_BEM ! BEM option for roof/wall outside convective coefficient
69  ! 'DOE-2' : DOE-2 model from
70  ! EnergyPlus Engineering reference, p65
71  CHARACTER(LEN=3) :: CBEM ! TEB option for the building energy model
72  ! 'DEF': DEFault version force-restore model from Masson et al. 2002
73  ! 'BEM': Building Energy Model Bueno et al. 2011
74 
75  CHARACTER(LEN=3) :: CTREE ! TEB option for the high vegetation
76  ! 'DEF': DEFault version without radiative, dynamic effects or turbulent fluxes
77  ! 'RAD': only RADiative effects
78  ! 'DYN': radiative and DYNamic effects
79  ! 'FLX': radiative, dynamic effects, and turbulent fluxes
80  LOGICAL :: LGREENROOF ! T: green roofs (call ISBA from TEB)
81  LOGICAL :: LHYDRO ! T: urban subsoil and hydrology processes
82  LOGICAL :: LSOLAR_PANEL ! T: solar panels on roofs
83 !
84 ! type of initialization of vegetation: from cover types (ecoclimap) or parameters prescribed
85 !
86  LOGICAL :: LECOCLIMAP ! T: parameters computed from ecoclimap
87 ! ! F: they are read in the file
88 !
89 ! General surface:
90 !
91  REAL, POINTER, DIMENSION(:) :: XZS ! orography (m)
92  REAL, POINTER, DIMENSION(:,:) :: XCOVER ! fraction of each ecosystem (-)
93  LOGICAL, POINTER, DIMENSION(:):: LCOVER ! GCOVER(i)=T --> ith cover field is not 0.
94  INTEGER :: NTEB_PATCH ! number of TEB patches
95  REAL, POINTER, DIMENSION(:,:) :: XTEB_PATCH ! fraction of each TEB patch
96 !
97 ! Number of layers
98 !
99  INTEGER :: NROOF_LAYER ! number of layers in roofs
100  INTEGER :: NROAD_LAYER ! number of layers in roads
101  INTEGER :: NWALL_LAYER ! number of layers in walls
102 !
103 ! Date:
104 !
105  TYPE (date_time) :: TTIME ! current date and time
106 !
107 ! Time-step:
108 !
109  REAL :: XTSTEP ! time step for TEB
110 !
111  REAL :: XOUT_TSTEP ! TEB output writing time step
112 !
113 END TYPE teb_options_t
114 
115 
116 
117  CONTAINS
118 !----------------------------------------------------------------------------
119 
120 !
121 
122 
123 
124 
125 SUBROUTINE teb_options_init(YTEB_OPTIONS)
126 TYPE(teb_options_t), INTENT(INOUT) :: yteb_options
127 REAL(KIND=JPRB) :: zhook_handle
128 IF (lhook) CALL dr_hook("MODD_TEB_N:TEB_OPTIONS_INIT",0,zhook_handle)
129  nullify(yteb_options%XZS)
130  nullify(yteb_options%XCOVER)
131  nullify(yteb_options%LCOVER)
132  nullify(yteb_options%XTEB_PATCH)
133 yteb_options%LCANOPY=.false.
134 yteb_options%LGARDEN=.false.
135 yteb_options%CROAD_DIR=' '
136 yteb_options%CWALL_OPT=' '
137 yteb_options%CBLD_ATYPE=' '
138 yteb_options%CZ0H=' '
139 yteb_options%CCH_BEM=' '
140 yteb_options%CBEM=' '
141 yteb_options%CTREE=' '
142 yteb_options%LGREENROOF=.false.
143 yteb_options%LHYDRO=.false.
144 yteb_options%LSOLAR_PANEL=.false.
145 yteb_options%LECOCLIMAP=.false.
146 yteb_options%NTEB_PATCH=0
147 yteb_options%NROOF_LAYER=0
148 yteb_options%NROAD_LAYER=0
149 yteb_options%NWALL_LAYER=0
150 yteb_options%XTSTEP=0.
151 yteb_options%XOUT_TSTEP=0.
152 IF (lhook) CALL dr_hook("MODD_TEB_N:TEB_OPTIONS_INIT",1,zhook_handle)
153 END SUBROUTINE teb_options_init
154 
155 
156 !----------------------------------------------------------------------------
157 END MODULE modd_teb_option_n
subroutine teb_options_init(YTEB_OPTIONS)