SURFEX v8.1
General documentation of Surfex
modd_bemn.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 ! ################
6  MODULE modd_bem_n
7 ! ################
8 !
9 !!**** *MODD_BEM_n - declaration of parameters and option for BEM
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 !! B. Bueno *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 10/2010
30 !! G. Pigeon 06/2011 add LSHAD_DAY
31 !! G. Pigeon 07/2011 add LNATVENT_NIGHT
32 !! G. Pigeon 08/2011 change from MODD_BLD -> MODD_BEM
33 !! G. Pigeon 10/2011 add indoor relative surf. and view factors
34 !! G. Pigeon 09/2012 add TRAN_WIN
35 !! G. Pigeon 10/2012 add XF_WIN_WIN
36 !! V. Masson 06/2013 splits module in two
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 USE yomhook ,ONLY : lhook, dr_hook
42 USE parkind1 ,ONLY : jprb
43 !
44 IMPLICIT NONE
45 !
46 !--------------------------------------------------------------------------
47 !
48 TYPE bem_t
49 !
50 ! Floor parameters
51 !
52  REAL, POINTER, DIMENSION(:,:) :: xhc_floor ! floor layers heat capacity (J/K/m3)
53  REAL, POINTER, DIMENSION(:,:) :: xtc_floor ! floor layers thermal conductivity (W/K/m)
54  REAL, POINTER, DIMENSION(:,:) :: xd_floor ! depth of floor layers (m)
55 !
56 ! HVAC parameters
57 !
58  REAL, POINTER, DIMENSION(:) :: xtcool_target ! cooling setpoint of indoor air
59  REAL, POINTER, DIMENSION(:) :: xtheat_target ! heating setpoint of indoor air
60  REAL, POINTER, DIMENSION(:) :: xf_waste_can ! fraction of waste heat released into the canyon
61  REAL, POINTER, DIMENSION(:) :: xeff_heat ! efficiency of the heating system
62 !
63 ! Indoor parameters
64 !
65  REAL, POINTER, DIMENSION(:) :: xti_bld ! building interior temperature (K)
66  REAL, POINTER, DIMENSION(:,:) :: xt_floor ! floor layer temperatures (K)
67  REAL, POINTER, DIMENSION(:,:) :: xt_mass ! Air cooled building internal th. mass temperature (K)
68 !
69  REAL, POINTER, DIMENSION(:) :: xqin ! internal heat gains [W m-2(floor)]
70  REAL, POINTER, DIMENSION(:) :: xqin_frad ! radiant fraction of internal heat gains
71  REAL, POINTER, DIMENSION(:) :: xshgc ! solar heat gain coef. of windows
72  REAL, POINTER, DIMENSION(:) :: xshgc_sh ! solar heat gain coef. of windows + shading
73  REAL, POINTER, DIMENSION(:) :: xu_win ! window U-factor [K m W-2]
74  REAL, POINTER, DIMENSION(:) :: xtran_win ! window transmittance (-)
75  REAL, POINTER, DIMENSION(:) :: xgr ! glazing ratio
76  REAL, POINTER, DIMENSION(:) :: xfloor_height ! building floor height [m]
77  REAL, POINTER, DIMENSION(:) :: xinf ! infiltration/ventilation flow rate [AC/H]
78 !
79 ! New parameters
80 !
81  REAL, POINTER, DIMENSION(:) :: xf_water_cond ! fraction of evaporation for condensers (cooling system)
82  REAL, POINTER, DIMENSION(:) :: xaux_max ! Auxiliar variable for autosize calcs
83  REAL, POINTER, DIMENSION(:) :: xqin_flat ! Latent franction of internal heat gains
84  REAL, POINTER, DIMENSION(:) :: xhr_target ! Relative humidity setpoint
85  REAL, POINTER, DIMENSION(:) :: xt_win2 ! Indoor window temperature [K]
86  REAL, POINTER, DIMENSION(:) :: xqi_bld ! Indoor air specific humidity [kg kg-1]
87  REAL, POINTER, DIMENSION(:) :: xv_vent ! Ventilation flow rate [AC/H]
88  REAL, POINTER, DIMENSION(:) :: xcap_sys_heat ! Capacity of the heating system
89  ! [W m-2(bld)]
90  REAL, POINTER, DIMENSION(:) :: xcap_sys_rat ! Rated capacity of the cooling system
91  ! [W m-2(bld)]
92  REAL, POINTER, DIMENSION(:) :: xt_adp ! Apparatus dewpoint temperature of the
93  ! cooling coil [K]
94  REAL, POINTER, DIMENSION(:) :: xm_sys_rat ! Rated HVAC mass flow rate
95  ! [kg s-1 m-2(bld)]
96  REAL, POINTER, DIMENSION(:) :: xcop_rat ! Rated COP of the cooling system
97  REAL, POINTER, DIMENSION(:) :: xt_win1 ! outdoor window temperature [K]
98  REAL, POINTER, DIMENSION(:) :: xalb_win ! window albedo
99  REAL, POINTER, DIMENSION(:) :: xabs_win ! window absortance
100  REAL, POINTER, DIMENSION(:) :: xt_size_max ! Maximum outdoor air temperature for
101  ! HVAC sizing [K]
102  REAL, POINTER, DIMENSION(:) :: xt_size_min ! Minimum outdoor air temperature for
103  ! HVAC sizing [K]
104  REAL, POINTER, DIMENSION(:) :: xugg_win ! Window glass-to-glass U-factor [K m W-2]
105  LOGICAL, POINTER, DIMENSION(:):: lshade ! flag to activate shading devices -> LOGICAL in the code
106  REAL, POINTER, DIMENSION(:):: xshade ! flag to activate shading devices -> REAL for i/o 0. or 1.
107  CHARACTER(LEN=4), POINTER, DIMENSION(:) :: cnatvent ! flag to activate natural ventilation 'NONE', 'MANU', 'AUTO'
108  REAL, POINTER, DIMENSION(:):: xnatvent ! flag to describe surventilation system for i/o
109  ! 0 for NONE, 1 for MANU and 2 for AUTO
110  LOGICAL, POINTER, DIMENSION(:):: lshad_day !Has shading been necessary this day ?
111  LOGICAL, POINTER, DIMENSION(:):: lnatvent_night !Has nocturnal surventilation been necessary and possible this night ?
112  !
113  !indoor relative surfaces and view factors
114  REAL, POINTER, DIMENSION(:) :: xn_floor ! Number of floors
115  REAL, POINTER, DIMENSION(:) :: xglaz_o_bld ! Window area [m2_win/m2_bld]
116  REAL, POINTER, DIMENSION(:) :: xmass_o_bld ! Mass area [m2_mass/m2_bld]
117  REAL, POINTER, DIMENSION(:) :: xfloor_hw_ratio ! H/W ratio of 1 floor level
118  REAL, POINTER, DIMENSION(:) :: xf_floor_mass ! View factor floor-mass
119  REAL, POINTER, DIMENSION(:) :: xf_floor_wall ! View factor floor-wall
120  REAL, POINTER, DIMENSION(:) :: xf_floor_win ! View factor floor-window
121  REAL, POINTER, DIMENSION(:) :: xf_floor_roof ! View factor floor-roof
122  REAL, POINTER, DIMENSION(:) :: xf_wall_floor ! View factor wall-floor
123  REAL, POINTER, DIMENSION(:) :: xf_wall_mass ! View factor wall-mass
124  REAL, POINTER, DIMENSION(:) :: xf_wall_win ! View factor wall-win
125  REAL, POINTER, DIMENSION(:) :: xf_win_floor ! View factor win-floor
126  REAL, POINTER, DIMENSION(:) :: xf_win_mass ! View factor win-mass
127  REAL, POINTER, DIMENSION(:) :: xf_win_wall ! View factor win-wall
128  REAL, POINTER, DIMENSION(:) :: xf_win_win ! indoor View factor win-win
129  REAL, POINTER, DIMENSION(:) :: xf_mass_floor ! View factor mass-floor
130  REAL, POINTER, DIMENSION(:) :: xf_mass_wall ! View factor mass-wall
131  REAL, POINTER, DIMENSION(:) :: xf_mass_win ! View factor mass-window
132 
133 
134 !
135 END TYPE bem_t
136 !
138  !
139  TYPE(bem_t), POINTER :: al(:) => null()
140  !
141 END TYPE bem_np_t
142 !
143 CONTAINS
144 
145 !----------------------------------------------------------------------------
146 !
147 SUBROUTINE bem_init(YBEM)
148 TYPE(bem_t), INTENT(INOUT) :: YBEM
149 REAL(KIND=JPRB) :: ZHOOK_HANDLE
150 IF (lhook) CALL dr_hook("MODD_BEM_N:BEM_INIT",0,zhook_handle)
151  NULLIFY(ybem%XF_WATER_COND)
152  NULLIFY(ybem%XHC_FLOOR)
153  NULLIFY(ybem%XTC_FLOOR)
154  NULLIFY(ybem%XD_FLOOR)
155  NULLIFY(ybem%XTCOOL_TARGET)
156  NULLIFY(ybem%XTHEAT_TARGET)
157  NULLIFY(ybem%XTI_BLD)
158  NULLIFY(ybem%XT_FLOOR)
159  NULLIFY(ybem%XT_MASS)
160  NULLIFY(ybem%XQIN)
161  NULLIFY(ybem%XQIN_FRAD)
162  NULLIFY(ybem%XSHGC)
163  NULLIFY(ybem%XSHGC_SH)
164  NULLIFY(ybem%XU_WIN)
165  NULLIFY(ybem%XTRAN_WIN)
166  NULLIFY(ybem%XGR)
167  NULLIFY(ybem%XFLOOR_HEIGHT)
168  NULLIFY(ybem%XEFF_HEAT)
169  NULLIFY(ybem%XINF)
170  NULLIFY(ybem%XF_WASTE_CAN)
171  NULLIFY(ybem%XAUX_MAX)
172  NULLIFY(ybem%XQIN_FLAT)
173  NULLIFY(ybem%XHR_TARGET)
174  NULLIFY(ybem%XT_WIN2)
175  NULLIFY(ybem%XQI_BLD)
176  NULLIFY(ybem%XV_VENT)
177  NULLIFY(ybem%XCAP_SYS_HEAT)
178  NULLIFY(ybem%XCAP_SYS_RAT)
179  NULLIFY(ybem%XT_ADP)
180  NULLIFY(ybem%XM_SYS_RAT)
181  NULLIFY(ybem%XCOP_RAT)
182  NULLIFY(ybem%XT_WIN1)
183  NULLIFY(ybem%XALB_WIN)
184  NULLIFY(ybem%XABS_WIN)
185  NULLIFY(ybem%XT_SIZE_MAX)
186  NULLIFY(ybem%XT_SIZE_MIN)
187  NULLIFY(ybem%XUGG_WIN)
188  NULLIFY(ybem%LSHAD_DAY)
189  NULLIFY(ybem%LNATVENT_NIGHT)
190  NULLIFY(ybem%LSHADE)
191  NULLIFY(ybem%XSHADE)
192  NULLIFY(ybem%CNATVENT)
193  NULLIFY(ybem%XNATVENT)
194  NULLIFY(ybem%XN_FLOOR)
195  NULLIFY(ybem%XGLAZ_O_BLD)
196  NULLIFY(ybem%XMASS_O_BLD)
197  NULLIFY(ybem%XFLOOR_HW_RATIO)
198  NULLIFY(ybem%XF_FLOOR_MASS)
199  NULLIFY(ybem%XF_FLOOR_WALL)
200  NULLIFY(ybem%XF_FLOOR_WIN)
201  NULLIFY(ybem%XF_FLOOR_ROOF)
202  NULLIFY(ybem%XF_WALL_FLOOR)
203  NULLIFY(ybem%XF_WALL_MASS)
204  NULLIFY(ybem%XF_WALL_WIN)
205  NULLIFY(ybem%XF_WIN_FLOOR)
206  NULLIFY(ybem%XF_WIN_MASS)
207  NULLIFY(ybem%XF_WIN_WALL)
208  NULLIFY(ybem%XF_WIN_WIN)
209  NULLIFY(ybem%XF_MASS_FLOOR)
210  NULLIFY(ybem%XF_MASS_WALL)
211  NULLIFY(ybem%XF_MASS_WIN)
212 IF (lhook) CALL dr_hook("MODD_BEM_N:BEM_INIT",1,zhook_handle)
213 END SUBROUTINE bem_init
214 !
215 SUBROUTINE bem_np_init(YNBEM,KPATCH)
216 TYPE(bem_np_t), INTENT(INOUT) :: YNBEM
217 INTEGER, INTENT(IN) :: KPATCH
218 INTEGER :: JP
219 REAL(KIND=JPRB) :: ZHOOK_HANDLE
220 IF (lhook) CALL dr_hook("MODD_BEM_N:BEM_NP_INIT",0,zhook_handle)
221 IF (.NOT.ASSOCIATED(ynbem%AL)) THEN
222  ALLOCATE(ynbem%AL(kpatch))
223  DO jp=1,kpatch
224  CALL bem_init(ynbem%AL(jp))
225  ENDDO
226 ELSE
227  DO jp=1,kpatch
228  CALL bem_init(ynbem%AL(jp))
229  ENDDO
230  DEALLOCATE(ynbem%AL)
231 ENDIF
232 IF (lhook) CALL dr_hook("MODD_BEM_N:BEM_NP_INIT",1,zhook_handle)
233 END SUBROUTINE bem_np_init
234 !
235 !
236 END MODULE modd_bem_n
subroutine bem_init(YBEM)
Definition: modd_bemn.F90:148
integer, parameter jprb
Definition: parkind1.F90:32
subroutine bem_np_init(YNBEM, KPATCH)
Definition: modd_bemn.F90:216
logical lhook
Definition: yomhook.F90:15