SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_teb_greenroof_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_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 
45 
46 
47 
49 !-------------------------------------------------------------------------------
50 !
51 ! type of initialization : from cover types (ecoclimap) or parameters prescribed
52 !
53  LOGICAL :: LPAR_GREENROOF ! T: parameters computed from ecoclimap
54 ! ! F: they are read in the file
55 !
56 ! ISBA Scheme Options specific to urban green roofs:
57 !
58  CHARACTER(LEN=3) :: CISBA_GR ! type of ISBA version ('2-L' = default, '3-L', 'DIF')
59  CHARACTER(LEN=4) :: CSCOND_GR ! Thermal conductivity ('DEF '= NP89 implicit method ,
60  ! 'PL98' = Peters-Lidard et al. 1998 used for explicit computation of CG)
61 !
62  LOGICAL :: LTR_ML_GR
63 !-------------------------------------------------------------------------------
64 !
65 ! type of initialization of vegetation: from cover types (ecoclimap) or parameters prescribed
66 !
67  INTEGER :: NLAYER_GR ! number of ground layers
68  INTEGER :: NTIME_GR ! number of time data : for VEG, LAI, EMIS, Z0
69 !
70  INTEGER :: NLAYER_HORT_GR
71  INTEGER :: NLAYER_DUN_GR
72 !
73  REAL, POINTER, DIMENSION(:) :: XSOILGRID_GR ! Soil layer grid as reference for DIF
74 !-------------------------------------------------------------------------------
75 !
76 ! - SGH scheme
77 !
78  CHARACTER(LEN=4) :: CRUNOFF_GR ! surface runoff formulation for green roofs
79 ! ! 'WSAT'
80 ! ! 'DT92'
81 ! ! 'SGH ' Topmodel
82 !
83 !SGH scheme and vertical hydrology
84 !
85  CHARACTER(LEN=3) :: CKSAT_GR ! ksat
86 ! ! 'DEF' = default value
87 ! ! 'SGH' = profil exponentiel
88  CHARACTER(LEN=3) :: CHORT_GR ! Horton runoff
89 ! ! 'DEF' = no Horton runoff
90 ! ! 'SGH' = Horton runoff
91  LOGICAL :: LSOC_GR ! soil organic carbon effect
92 ! ! False = default value
93 ! ! True = SOC profil
94 !
95 !-------------------------------------------------------------------------------
96 !
97 ! Type of green roof (characterization of green roof structure based on GR vegetation)
98 !
99  CHARACTER(LEN=5) :: CTYP_GR ! type of green roof
100 !
101 !-------------------------------------------------------------------------------
102 !
104 
105 
106 
107  CONTAINS
108 
109 !
110 
111 
112 !
113 
114 SUBROUTINE teb_greenroof_options_init(YTEB_GREENROOF_OPTIONS)
115 TYPE(teb_greenroof_options_t), INTENT(INOUT) :: yteb_greenroof_options
116 REAL(KIND=JPRB) :: zhook_handle
117 IF (lhook) CALL dr_hook("MODD_TEB_GREENROOF_N:TEB_GREENROOF_INIT",0,zhook_handle)
118  nullify(yteb_greenroof_options%XSOILGRID_GR)
119 yteb_greenroof_options%LPAR_GREENROOF=.true.
120 yteb_greenroof_options%CISBA_GR=' '
121 yteb_greenroof_options%LTR_ML_GR=.false.
122 yteb_greenroof_options%LSOC_GR=.false.
123 yteb_greenroof_options%CRUNOFF_GR=' '
124 yteb_greenroof_options%CSCOND_GR=' '
125 yteb_greenroof_options%CKSAT_GR=' '
126 yteb_greenroof_options%CHORT_GR=' '
127 yteb_greenroof_options%CTYP_GR=' '
128 yteb_greenroof_options%NLAYER_GR=0
129 yteb_greenroof_options%NLAYER_HORT_GR=0
130 yteb_greenroof_options%NLAYER_DUN_GR=0
131 yteb_greenroof_options%NTIME_GR=0
132 IF (lhook) CALL dr_hook("MODD_TEB_GREENROOF_N:TEB_GREENROOF_OPTIONS_INIT",1,zhook_handle)
133 END SUBROUTINE teb_greenroof_options_init
134 
135 
subroutine teb_greenroof_options_init(YTEB_GREENROOF_OPTIONS)