Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
logical, | public | :: | LCANOPY | ||||
logical, | public | :: | LGARDEN | ||||
character(len=4), | public | :: | CROAD_DIR | ||||
character(len=4), | public | :: | CWALL_OPT | ||||
character(len=3), | public | :: | CBLD_ATYPE | ||||
character(len=6), | public | :: | CZ0H | ||||
character(len=5), | public | :: | CCH_BEM | ||||
character(len=3), | public | :: | CBEM | ||||
character(len=3), | public | :: | CTREE | ||||
logical, | public | :: | LGREENROOF | ||||
logical, | public | :: | LHYDRO | ||||
logical, | public | :: | LSOLAR_PANEL | ||||
logical, | public | :: | LECOCLIMAP | ||||
real, | public, | POINTER, DIMENSION(:) | :: | XZS | |||
real, | public, | POINTER, DIMENSION(:,:) | :: | XCOVER | |||
logical, | public, | POINTER, DIMENSION(:) | :: | LCOVER | |||
integer, | public | :: | NTEB_PATCH | ||||
real, | public, | POINTER, DIMENSION(:,:) | :: | XTEB_PATCH | |||
integer, | public | :: | NROOF_LAYER | ||||
integer, | public | :: | NROAD_LAYER | ||||
integer, | public | :: | NWALL_LAYER | ||||
type(DATE_TIME), | public | :: | TTIME | ||||
real, | public | :: | XTSTEP | ||||
real, | public | :: | XOUT_TSTEP |
TYPE TEB_OPTIONS_t
! TEB scheme option
!
LOGICAL :: LCANOPY ! T: SBL scheme within the canopy
! F: no atmospheric layers below forcing level
LOGICAL :: LGARDEN ! T: Urban green areas (call ISBA from TEB)
! F: No urban green areas
CHARACTER(LEN=4) :: CROAD_DIR ! TEB option for road directions
! 'UNIF' : no specific direction
! 'ORIE' : many road ORIEntations
! ( one per TEB patch)
CHARACTER(LEN=4) :: CWALL_OPT ! TEB option for walls
! 'UNIF' : uniform walls
! 'TWO ' : two separated walls
CHARACTER(LEN=3) :: CBLD_ATYPE ! Type of averaging for walls
! 'ARI' : Characteristics are
! linearly averaged
! 'MAJ ' : Majoritary building in
! grid mesh is chosen
CHARACTER(LEN=6) :: CZ0H ! TEB option for z0h roof & road
! 'MASC95' : Mascart et al 1995
! 'BRUT82' : Brustaert 1982
! 'KAND07' : Kanda 2007
CHARACTER(LEN=5) :: CCH_BEM ! BEM option for roof/wall outside convective coefficient
! 'DOE-2' : DOE-2 model from
! EnergyPlus Engineering reference, p65
CHARACTER(LEN=3) :: CBEM ! TEB option for the building energy model
! 'DEF': DEFault version force-restore model from Masson et al. 2002
! 'BEM': Building Energy Model Bueno et al. 2011
CHARACTER(LEN=3) :: CTREE ! TEB option for the high vegetation
! 'DEF': DEFault version without radiative, dynamic effects or turbulent fluxes
! 'RAD': only RADiative effects
! 'DYN': radiative and DYNamic effects
! 'FLX': radiative, dynamic effects, and turbulent fluxes
LOGICAL :: LGREENROOF ! T: green roofs (call ISBA from TEB)
LOGICAL :: LHYDRO ! T: urban subsoil and hydrology processes
LOGICAL :: LSOLAR_PANEL ! T: solar panels on roofs
!
! type of initialization of vegetation: from cover types (ecoclimap) or parameters prescribed
!
LOGICAL :: LECOCLIMAP ! T: parameters computed from ecoclimap
! ! F: they are read in the file
!
! General surface:
!
REAL, POINTER, DIMENSION(:) :: XZS ! orography (m)
REAL, POINTER, DIMENSION(:,:) :: XCOVER ! fraction of each ecosystem (-)
LOGICAL, POINTER, DIMENSION(:):: LCOVER ! GCOVER(i)=T --> ith cover field is not 0.
INTEGER :: NTEB_PATCH ! number of TEB patches
REAL, POINTER, DIMENSION(:,:) :: XTEB_PATCH ! fraction of each TEB patch
!
! Number of layers
!
INTEGER :: NROOF_LAYER ! number of layers in roofs
INTEGER :: NROAD_LAYER ! number of layers in roads
INTEGER :: NWALL_LAYER ! number of layers in walls
!
! Date:
!
TYPE (DATE_TIME) :: TTIME ! current date and time
!
! Time-step:
!
REAL :: XTSTEP ! time step for TEB
!
REAL :: XOUT_TSTEP ! TEB output writing time step
!
END TYPE TEB_OPTIONS_t