SURFEX v8.1
General documentation of Surfex
dx_air_cooling_coil_cv.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 SUBROUTINE dx_air_cooling_coil_cv(PT_CANYON, PQ_CANYON, PPS, PRHOA, &
6  PT_IN, PQ_IN, PCOP_RAT, PCAP_SYS_RAT, &
7  PT_ADP, PF_WATER_COND, &
8  PM_SYS, PH_BLD_COOL, PH_WASTE, PLE_WASTE, &
9  PCOP, PCAP_SYS, PT_OUT, PQ_OUT, &
10  PDX_POWER, PT_BLD_COOL )
11 !
12 USE mode_thermos
13 USE mode_psychro
14 !
15 USE modd_csts, ONLY : xcpd
16 !
17 USE yomhook ,ONLY : lhook, dr_hook
18 USE parkind1 ,ONLY : jprb
19 !
20 ! Extracted from EP_Engineer_ref p. 518
21 !
22 REAL, INTENT(IN) :: PT_CANYON ! Canyon air temperature [K]
23 REAL, INTENT(IN) :: PQ_CANYON ! Canyon air humidity ratio [kg kg-1]
24 REAL, INTENT(IN) :: PPS ! Canyon air pressure [Pa]
25 REAL, INTENT(IN) :: PRHOA ! Canyon air density [kg m-3]
26 REAL, INTENT(IN) :: PT_IN ! Actual inlet air temperature [K]
27 REAL, INTENT(IN) :: PQ_IN ! Actual inlet air humidity ratio [kg kg-1]
28 REAL, INTENT(IN) :: PCOP_RAT ! Rated COP
29 REAL, INTENT(IN) :: PCAP_SYS_RAT ! Rated capacity [W]
30 REAL, INTENT(IN) :: PT_ADP ! Apparatus dewpoint [K]
31 REAL, INTENT(IN) :: PF_WATER_COND ! fraction of evaporation of the condenser
32 REAL, INTENT(INOUT) :: PM_SYS ! HVAC air mass flow rate [kg s-1]
33 REAL, INTENT(INOUT) :: PH_BLD_COOL ! Sensible cooling load
34 REAL, INTENT(OUT) :: PH_WASTE ! Sensible heat rejected by the condenser [W]
35 REAL, INTENT(OUT) :: PLE_WASTE ! Latent heat rejected by the condenser [W]
36 REAL, INTENT(OUT) :: PCOP ! Actual COP
37 REAL, INTENT(OUT) :: PCAP_SYS ! Actual capacity [W]
38 REAL, INTENT(OUT) :: PT_OUT ! Actual outlet temperature [K]
39 REAL, INTENT(OUT) :: PQ_OUT ! Actual outlet humidity ratio [kg kg-1]
40 REAL, INTENT(OUT) :: PDX_POWER ! Electrical power consumed by the DX unit [W]
41 REAL, INTENT(OUT) :: PT_BLD_COOL ! Total energy supplied by the DX unit [W]
42 !
43 REAL :: ZTWB_CANYON ! Canyon air wet-bulb temperature [ K]
44 REAL :: ZCAPTEMP ! Total cooling capacity modifier curve function of temperature
45 REAL :: ZTW_IN ! Wet-bulb temperature of the air entering the coil [ K]
46 REAL :: ZT_COND ! Dry-bulb or wet-bulb air temperature entering the condenser [K]
47 REAL :: ZEIRTEMP ! Energy input ratio modifier curve function of temperature
48 REAL :: ZPLR ! Part load ratio
49 REAL :: ZPARTLOADF ! Part load fraction correlation
50 REAL :: ZSHR ! Actual coil sensible heat rate
51 REAL :: ZH_ADP ! Enthalpy of air at ADP conditions [J/kg]
52 REAL :: ZH_OUT ! Enthalpy of air leaving the cooling coil [J/kg]
53 REAL :: ZH_IN ! Enthalpy of air entering the cooling coil [J/kg]
54 ! Performance curves coefficients
55 REAL :: ZA1
56 REAL :: ZB1
57 REAL :: ZC1
58 REAL :: ZD1
59 REAL :: ZE1
60 REAL :: ZF1
61 ! Total cooling capacity modifier curve function of flow fraction (desactivated)
62 !REAL :: ZCAPFLOW
63 !REAL :: ZA2
64 !REAL :: ZB2
65 !REAL :: ZC2
66 REAL :: ZA3
67 REAL :: ZB3
68 REAL :: ZC3
69 REAL :: ZD3
70 REAL :: ZE3
71 REAL :: ZF3
72 ! Energy input ratio modifier curve function of flow fraction (desactivated)
73 !REAL :: ZEIRFLOW
74 !REAL :: ZA4
75 !REAL :: ZB4
76 !REAL :: ZC4
77 REAL :: ZA5
78 REAL :: ZB5
79 REAL :: ZC5
80 REAL(KIND=JPRB) :: ZHOOK_HANDLE
81 !
82 IF (lhook) CALL dr_hook('DX_AIR_COOLING_COIL_CV',0,zhook_handle)
83 !
84 !* A. Definitions
85 ! -----------
86 !
87 !
88 !* B. Performance curves
89 ! ------------------
90 ! Total cooling capacity modifier curve function of temperature
91 ! Obtained from default vaules of EnergyPlus SingleSpeedDX
92 ! DOE-2.1E, COOL-CAP-FT for PTAC w/ SI temps
93 ! FurnaceDX DX Coil Cap-FT, Minimum Value of x, 12.77778;
94 ! Maximum Value of x, 23.88889;
95 ! Minimum Value of y, 23.88889;
96 ! Maximum Value of y, 46.11111
97 za1 = 0.942587793 !- Coefficient1 Constant
98 zb1 = 0.009543347 !- Coefficient2 x
99 zc1 = 0.00068377 !- Coefficient3 x**2
100 zd1 = -0.011042676 !- Coefficient4 y
101 ze1 = 0.000005249 !- Coefficient5 y**2
102 zf1 = -0.00000972 !- Coefficient6 x*y
103 ! Total cooling capacity modifier curve function of flow fraction
104 ! DOE-2.1E, RATED-CCAP-FFLOW for PTAC
105 ! FurnaceDX DX Coil Cap-FF, Minimum Value of x, 0.5;
106 ! Maximum Value of x, 1.5;
107 !ZA2 = 0.8 !- Coefficient1 Constant
108 !ZB2 = 0.2 !- Coefficient2 x
109 !ZC2 = 0 !- Coefficient3 x**2
110 ! Energy input ratio modifier curve function of temperature
111 ! DOE-2.1E, COOL-EIR-FT for PTAC w/ SI temps
112 ! FurnaceDX DX Coil EIR-FT, Minimum Value of x, 12.77778;
113 ! Maximum Value of x, 23.88889;
114 ! Minimum Value of y, 23.88889;
115 ! Maximum Value of y, 46.11111
116 za3 = 0.342414409 !- Coefficient1 Constant
117 zb3 = 0.034885008 !- Coefficient2 x
118 zc3 = -0.0006237 !- Coefficient3 x**2
119 zd3 = 0.004977216 !- Coefficient4 y
120 ze3 = 0.000437951 !- Coefficient5 y**2
121 zf3 = -0.000728028 !- Coefficient6 x*y
122 ! Energy input ratio modifier curve function of flow fraction
123 ! DOE-2.1E, RATED-CEIR-FFLOW for PTAC
124 ! FurnaceDX DX Coil EIR-FF, Minimum Value of x, 0.5;
125 ! Maximum Value of x, 1.5;
126 !ZA4 = 1.1552 !- Coefficient1 Constant
127 !ZB4 = -0.1808 !- Coefficient2 x
128 !ZC4 = 0.0256 !- Coefficient3 x**2
129 ! Part load fraction correlation
130 ! PLF = l.- Cd(1.-PLR) where Cd = 0.15
131 ! FurnaceDX DX Coil PLF, Minimum Value of x, 0.0;
132 ! Maximum Value of x, 1.0;
133 za5 = 0.85 !- Coefficient1 Constant
134 zb5 = 0.15 !- Coefficient2 x
135 zc5 = 0 !- Coefficient3 x**2
136 !
137 !
138 !* C. Total cooling capacity
139 ! ----------------------
140 !
141 IF (pm_sys/prhoa/pcap_sys_rat < 0.00004027) THEN
142  pm_sys = 0.00004027*pcap_sys_rat*prhoa
143 ! PRINT*,'ERROR: HVAC supply air flow rate must be greater than 0.00004027m3/s/W'
144 ELSE IF (pm_sys/prhoa/pcap_sys_rat > 0.00006041) THEN
145  pm_sys = 0.00006041*pcap_sys_rat*prhoa
146 ! PRINT*,'ERROR: HVAC supply air flow rate must be lower than 0.00006041m3/s/W'
147 END IF
148 !
149 ! Wet-bulb temperature entering the cooling coil
150 ztw_in = twb_from_tpq(pt_in, pps, pq_in)
151 !
152 ! Dry-bulb temperature of the air entering an air-cooled condenser
153 ! or wet-bulb temp entering a water-cooled condenser
154 ztwb_canyon = twb_from_tpq(pt_canyon, pps, pq_canyon)
155 zt_cond = ztwb_canyon + (pt_canyon - ztwb_canyon)*(1. - pf_water_cond)
156 !
157 ! Total cooling capacity modifier curve function of temperature
158 zcaptemp = za1 + (ztw_in -273.15) * (zb1 + zc1*(ztw_in -273.15)) &
159  + (zt_cond-273.15) * (zd1 + ze1*(zt_cond-273.15)) &
160  + (ztw_in -273.15) * (zt_cond-273.15) * zf1
161 !
162 ! Total cooling capacity
163 pcap_sys = pcap_sys_rat * zcaptemp
164 !
165 !* D. Coil outlet conditions
166 ! ----------------------
167 !
168 ! Inlet air enthalpy
169 zh_in = enth_fn_t_q(pt_in,pq_in)
170 ! Apparatus dewpoint enthalpy
171 zh_adp = enth_fn_t_q(pt_adp,qsat(pt_adp,pps))
172 !
173 ! Cooling coil sensible heat rate
174 IF (zh_in - zh_adp < 10.) THEN
175  !
176  zshr = 1.
177  !
178  pt_out = pt_adp
179  pq_out = pq_in
180  zh_out = enth_fn_t_q(pt_out,pq_out)
181  pt_bld_cool = 0.0
182  !
183 ELSE
184  !
185  zshr = min(xcpd*(pt_in - pt_adp)/(zh_in - zh_adp), 1.) !
186  !
187  ! Thermal load limited by the system capacity
188  IF ( ph_bld_cool > pcap_sys * zshr ) ph_bld_cool = pcap_sys * zshr
189  !
190  ! Outlet air temperature
191  pt_out = pt_in - ph_bld_cool / pm_sys / xcpd
192  IF (pt_out < pt_adp) pt_out = pt_adp
193  !
194  ! Outlet air enthalpy
195  zh_out = zh_in - xcpd * (pt_in - pt_out) / zshr
196  !
197  ! Outlet air humidity ratio
198  pq_out = q_fn_t_enth(pt_out, zh_out)
199  !
200  ! Total thermal energy supplied by the cooling coil
201  pt_bld_cool = pm_sys*(zh_in - zh_out)
202  !
203 END IF
204 !
205 !
206 !* D. HVAC efficiency and electrical power consumed by the DX unit
207 ! ------------------------------------------------------------
208 !
209 ! Energy input ratio modifier curve function of temperature
210 zeirtemp = za3 + (ztw_in -273.15) * (zb3 + zc3*(ztw_in -273.15)) &
211  + (zt_cond-273.15) * (zd3 + ze3*(zt_cond-273.15)) &
212  + (ztw_in -273.15) * (zt_cond-273.15) * zf3
213 !
214 ! HVAC coefficient of performance
215 pcop = pcop_rat / zeirtemp
216 !
217 ! Part load fraction correlation
218 zplr = ph_bld_cool / (pcap_sys * zshr)
219 !
220 IF (zplr > 1.0) zplr = 1.0
221 !
222 zpartloadf = za5 + zb5 * zplr + zc5 * zplr**2
223 IF ( zpartloadf < min(0.7, zplr) ) zpartloadf = min(0.7, zplr)
224 !
225 ! Electrical power consumed by the DX unit
226 ! (compressors plus outdoor condenser fans)
227 pdx_power = pcap_sys / pcop * zplr / zpartloadf
228 !
229 !
230 !* E. Waste heat emissions
231 ! --------------------
232 !
233 ! Total heat rejected by the condenser
234 ple_waste = (pt_bld_cool + pdx_power) * pf_water_cond
235 ph_waste = (pt_bld_cool + pdx_power) * (1. - pf_water_cond)
236 !
237 IF (lhook) CALL dr_hook('DX_AIR_COOLING_COIL_CV',1,zhook_handle)
238 !
239 END SUBROUTINE dx_air_cooling_coil_cv
real, save xcpd
Definition: modd_csts.F90:63
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine dx_air_cooling_coil_cv(PT_CANYON, PQ_CANYON, PPS, PRHOA, PT_IN, PQ_IN, PCOP_RAT, PCAP_SYS_RAT, PT_ADP, PF_WATER_COND, PM_SYS, PH_BLD_COOL, PH_WASTE, PLE_WASTE, PCOP, PCAP_SYS, PT_OUT, PQ_OUT, PDX_POWER, PT_BLD_COOL)