Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | CBVAVNumber |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
REAL(r64) FUNCTION CalcSetpointTempTarget(CBVAVNumber)
! FUNCTION INFORMATION:
! AUTHOR Richard Raustad
! DATE WRITTEN August 2006
! MODIFIED na
! RE-ENGINEERED
! PURPOSE OF THIS FUNCTION:
! Calculate outlet air node temperature setpoint
! METHODOLOGY EMPLOYED:
! Calculate an outlet temperature to satisfy zone loads. This temperature is calculated
! based on 1 zone's VAV box fully opened. The other VAV boxes are partially open (modulated).
! REFERENCES:
! na
! USE STATEMENTS:
USE Psychrometrics, ONLY: PsyCpAirFnWTdb
USE DataZoneEnergyDemands, ONLY: ZoneSysEnergyDemand
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: CBVAVNumber ! Index to changeover-bypass VAV system
! FUNCTION PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! FUNCTION LOCAL VARIABLE DECLARATIONS:
INTEGER :: OutletNode ! Outlet node of CBVAV system
INTEGER :: ZoneNum ! Index to controlled zone
INTEGER :: ZoneNodeNum ! Zone node number of controlled zone
INTEGER :: BoxOutletNodeNum ! CBVAV box outlet node (zone supply inlet node)
REAL(r64) :: DXCoolCoilInletTemp ! Air temperature of CBVAV DX cooling coil air inlet node [C]
REAL(r64) :: OutAirTemp ! Outlet air temperature of CBVAV system [C]
REAL(r64) :: OutAirHumRat ! Outlet air humidity ratio of CBVAV system [C]
REAL(r64) :: ZoneLoad ! Zone load sensed by thermostat [W]
REAL(r64) :: CpSupplyAir ! Specific heat of CBVAV system outlet air [J/kg-K]
REAL(r64) :: QToCoolSetPt ! Zone load to cooling setpoint [W]
REAL(r64) :: QToHeatSetPt ! Zone load to heating setpoint [W]
REAL(r64) :: SupplyAirTemp ! Supply air temperature required to meet load [C]
REAL(r64) :: TSupplyToHeatSetPtMax ! Maximum of the supply air temperatures required to reach the heating setpoint [C]
REAL(r64) :: TSupplyToCoolSetPtMin ! Minimum of the supply air temperatures required to reach the cooling setpoint [C]
REAL(r64) :: SupplyAirTempToHeatSetPt ! Supply air temperature required to reach the heating setpoint [C]
REAL(r64) :: SupplyAirTempToCoolSetPt ! Supply air temperature required to reach the cooling setpoint [C]
DXCoolCoilInletTemp = Node(CBVAV(CBVAVNumber)%DXCoilInletNode)%Temp
OutAirTemp = Node(CBVAV(CBVAVNumber)%AirOutNode)%Temp
OutAirHumRat = Node(CBVAV(CBVAVNumber)%AirOutNode)%HumRat
IF(CBVAV(CBVAVNumber)%HeatCoolMode == CoolingMode)THEN ! Cooling required
CalcSetpointTempTarget = 99999.0d0
ELSE IF(CBVAV(CBVAVNumber)%HeatCoolMode == HeatingMode)THEN ! Heating required
CalcSetpointTempTarget = -99999.0d0
END IF
TSupplyToHeatSetPtMax = -99999.0d0
TSupplyToCoolSetPtMin = 99999.0d0
OutletNode = CBVAV(CBVAVNumber)%AirOutNode
DO ZoneNum = 1, CBVAV(CBVAVNumber)%NumControlledZones
ZoneNodeNum = CBVAV(CBVAVNumber)%ActualZoneNodeNum(ZoneNum)
BoxOutletNodeNum = CBVAV(CBVAVNumber)%CBVAVBoxOutletNode(ZoneNum)
IF ((CBVAV(CBVAVNumber)%ZoneSequenceCoolingNum(ZoneNum) > 0) .AND. &
(CBVAV(CBVAVNumber)%ZoneSequenceHeatingNum(ZoneNum) > 0)) THEN
QToCoolSetPt = ZoneSysEnergyDemand(CBVAV(CBVAVNumber)%ControlledZoneNum(ZoneNum))%&
SequencedOutputRequiredToCoolingSP(CBVAV(CBVAVNumber)%ZoneSequenceCoolingNum(ZoneNum))
QToHeatSetPt = ZoneSysEnergyDemand(CBVAV(CBVAVNumber)%ControlledZoneNum(ZoneNum))%&
SequencedOutputRequiredToHeatingSP(CBVAV(CBVAVNumber)%ZoneSequenceHeatingNum(ZoneNum))
IF (QToHeatSetPt > 0.d0 .AND. QToCoolSetPt > 0.d0) THEN
ZoneLoad = QToHeatSetPt
ELSEIF (QToHeatSetPt < 0.d0 .AND. QToCoolSetPt < 0.d0) THEN
ZoneLoad = QToCoolSetPt
ELSEIF (QToHeatSetPt <= 0.d0 .AND. QToCoolSetPt >= 0.d0) THEN
ZoneLoad = 0.d0
ENDIF
ELSE
ZoneLoad = ZoneSysEnergyDemand(CBVAV(CBVAVNumber)%ControlledZoneNum(ZoneNum))%RemainingOutputRequired
QToCoolSetPt = ZoneSysEnergyDemand(CBVAV(CBVAVNumber)%ControlledZoneNum(ZoneNum))%OutputRequiredToCoolingSP
QToHeatSetPt = ZoneSysEnergyDemand(CBVAV(CBVAVNumber)%ControlledZoneNum(ZoneNum))%OutputRequiredToHeatingSP
ENDIF
CpSupplyAir = PsyCpAirFnWTdb(OutAirHumRat,OutAirTemp)
! Find the supply air temperature that will force the box to full flow
IF(BoxOutletNodeNum .GT. 0)THEN
IF(CpSupplyAir*Node(BoxOutletNodeNum)%MassFlowRateMax .EQ. 0.0d0)THEN
SupplyAirTemp = Node(ZoneNodeNum)%Temp
ELSE
! The target supply air temperature is slightly
SupplyAirTemp = Node(ZoneNodeNum)%Temp + ZoneLoad/(CpSupplyAir*Node(BoxOutletNodeNum)%MassFlowRateMax)
END IF
ELSE
SupplyAirTemp = Node(ZoneNodeNum)%Temp
END IF
! Save the MIN (cooling) or MAX (heating) temperature for coil control
! One box will always operate at maximum damper position minimizing overall system energy use
IF(CBVAV(CBVAVNumber)%HeatCoolMode == CoolingMode)THEN
CalcSetpointTempTarget = MIN(SupplyAirTemp,CalcSetpointTempTarget)
ELSE IF(CBVAV(CBVAVNumber)%HeatCoolMode == HeatingMode)THEN
CalcSetpointTempTarget = MAX(SupplyAirTemp,CalcSetpointTempTarget)
ELSE
! Should use CpAirAtCoolSetpoint or CpAirAtHeatSetpoint here?
! If so, use ZoneThermostatSetPointLo(ZoneNum) and ZoneThermostatSetPointHi(ZoneNum)
! along with the zone humidity ratio
IF(CpSupplyAir*Node(BoxOutletNodeNum)%MassFlowRateMax .EQ. 0.0d0)THEN
SupplyAirTempToHeatSetPt = Node(ZoneNodeNum)%Temp
SupplyAirTempToCoolSetPt = Node(ZoneNodeNum)%Temp
ELSE
SupplyAirTempToHeatSetPt = Node(ZoneNodeNum)%Temp + QToHeatSetPt/(CpSupplyAir*Node(BoxOutletNodeNum)%MassFlowRateMax)
SupplyAirTempToCoolSetPt = Node(ZoneNodeNum)%Temp + QToCoolSetPt/(CpSupplyAir*Node(BoxOutletNodeNum)%MassFlowRateMax)
END IF
TSupplyToHeatSetPtMax = MAX(SupplyAirTempToHeatSetPt, TSupplyToHeatSetPtMax)
TSupplyToCoolSetPtMin = MIN(SupplyAirTempToCoolSetPt, TSupplyToCoolSetPtMin)
END IF
END DO
! Account for floating condition where cooling/heating is required to avoid overshooting setpoint
IF(CBVAV(CBVAVNumber)%HeatCoolMode == 0 .AND. CBVAV(CBVAVNumber)%OpMode == ContFanCycCoil)THEN
IF(OutAirTemp .GT. TSupplyToCoolSetPtMin)THEN
CalcSetpointTempTarget = TSupplyToCoolSetPtMin
CBVAV(CBVAVNumber)%HeatCoolMode = CoolingMode
ELSEIF(OutAirTemp .LT. TSupplyToHeatSetPtMax)THEN
CalcSetpointTempTarget = TSupplyToHeatSetPtMax
CBVAV(CBVAVNumber)%HeatCoolMode = HeatingMode
ELSE
CalcSetpointTempTarget = OutAirTemp
END IF
! Reset setpoint to inlet air temp if unit is OFF and in cycling fan mode
ELSE IF(CBVAV(CBVAVNumber)%HeatCoolMode == 0 .AND. CBVAV(CBVAVNumber)%OpMode == CycFanCycCoil)THEN
CalcSetpointTempTarget = Node(CBVAV(CBVAVNumber)%AirInNode)%Temp
! Reset cooling/heating mode to OFF if mixed air inlet temperature is below/above setpoint temperature.
! HeatCoolMode = 0 for OFF, 1 for cooling, 2 for heating
ELSE IF(CBVAV(CBVAVNumber)%HeatCoolMode == CoolingMode .AND. DXCoolCoilInletTemp .LT. CalcSetpointTempTarget)THEN
CalcSetpointTempTarget = DXCoolCoilInletTemp
CBVAV(CBVAVNumber)%HeatCoolMode = 0
ELSE IF(CBVAV(CBVAVNumber)%HeatCoolMode == HeatingMode .AND. DXCoolCoilInletTemp .GT. CalcSetpointTempTarget)THEN
CalcSetpointTempTarget = DXCoolCoilInletTemp
CBVAV(CBVAVNumber)%HeatCoolMode = 0
END IF
! Limit outlet node temperature to MAX/MIN specified in input
IF(CalcSetpointTempTarget .LT. CBVAV(CBVAVNumber)%MinLATCooling) CalcSetpointTempTarget = CBVAV(CBVAVNumber)%MinLATCooling
IF(CalcSetpointTempTarget .GT. CBVAV(CBVAVNumber)%MaxLATHeating) CalcSetpointTempTarget = CBVAV(CBVAVNumber)%MaxLATHeating
RETURN
END FUNCTION CalcSetpointTempTarget