!LKL Discrepancy < 0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | VRFTUNum | |||
integer, | intent(in) | :: | ZoneNum | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
real(kind=r64), | intent(inout) | :: | OnOffAirFlowRatio | |||
real(kind=r64), | intent(out) | :: | QZnReq |
SUBROUTINE InitVRF(VRFTUNum, ZoneNum, FirstHVACIteration, OnOffAirFlowRatio, QZnReq)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad, FSEC
! DATE WRITTEN August 2010
! MODIFIED July 2012, Chandan Sharma - FSEC: Added zone sys avail managers
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is for initializations of the VRF Components.
! METHODOLOGY EMPLOYED:
! Uses the status flags to trigger initializations.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataZoneEquipment, ONLY: ZoneEquipInputsFilled,CheckZoneEquipmentList,VRFTerminalUnit_Num
USE DataHeatBalFanSys, ONLY: TempControlType, ZT, ZoneThermostatSetPointHi, ZoneThermostatSetPointLo
USE InputProcessor, ONLY: SameString
USE ScheduleManager, ONLY: GetCurrentScheduleValue
USE DataEnvironment, ONLY: StdBaroPress, StdRhoAir, OutDryBulbTemp, OutWetBulbTemp
USE MixedAir, ONLY: SimOAMixer, SimOAController
USE DataZoneEquipment, ONLY: ZoneEquipList
USE DataSizing, ONLY: AutoSize
USE Fans, ONLY: GetFanVolFlow
USE General, ONLY: TrimSigDigits, RoundSigDigits
USE FluidProperties, ONLY: GetDensityGlycol
USE PlantUtilities, ONLY: InitComponentNodes
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
Integer, Intent(IN) :: VRFTUNum
INTEGER, INTENT (IN) :: ZoneNum
LOGICAL, INTENT(IN) :: FirstHVACIteration
REAL(r64), INTENT(InOut) :: OnOffAirFlowRatio
REAL(r64), INTENT(Out) :: QZnReq
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: InNode ! TU inlet node
INTEGER :: OutNode ! TU outlet node
INTEGER :: OutsideAirNode ! TU mixer outside air inlet node
LOGICAL, SAVE :: MyOneTimeFlag = .true. ! False after allocating and initializing subroutine variables
LOGICAL, SAVE :: ZoneEquipmentListNotChecked = .TRUE. ! False after the Zone Equipment List has been checked for items
LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyEnvrnFlag ! Flag for initializing at beginning of each new environment
LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MySizeFlag ! False after TU has been sized
LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyBeginTimeStepFlag ! Flag to sense beginning of time step
LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyVRFFlag ! used for sizing VRF inputs one time
LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyVRFCondFlag ! used to reset timer counter
INTEGER :: NumTULoop ! loop counter, number of TU's in list
INTEGER :: ELLoop ! loop counter, number of zone equipment lists
INTEGER :: ListLoop ! loop counter, number of equipment is each list
INTEGER :: VRFCond ! index to VRF condenser
INTEGER :: TUIndex ! index to TU
INTEGER :: TUListNum ! index to VRF AC system terminal unit list
INTEGER :: TUListIndex ! pointer to TU list for this VRF system
INTEGER :: IndexToTUInTUList ! index to TU in TerminalUnilList
REAL(r64) :: RhoAir ! air density at InNode
REAL(r64), SAVE :: CurrentEndTime ! end time of current time step
REAL(r64), SAVE :: CurrentEndTimeLast ! end time of last time step
REAL(r64), SAVE :: TimeStepSysLast ! system time step on last time step
REAL(r64) :: TempOutput ! Sensible output of TU
REAL(r64) :: LoadToCoolingSP ! thermostat load to cooling setpoint (W)
REAL(r64) :: LoadToHeatingSP ! thermostat load to heating setpoint (W)
LOGICAL :: EnableSystem ! use to turn on secondary operating mode if OA temp limits exceeded
REAL(r64) :: rho ! density of water (kg/m3)
REAL(r64):: OutsideDryBulbTemp ! Outdoor air temperature at external node height
! FLOW:
! ALLOCATE and Initialize subroutine variables
IF (MyOneTimeFlag) THEN
ALLOCATE(MyEnvrnFlag(NumVRFTU))
ALLOCATE(MySizeFlag(NumVRFTU))
ALLOCATE(MyVRFFlag(NumVRFTU))
ALLOCATE(MyBeginTimeStepFlag(NumVRFCond))
ALLOCATE(MaxDeltaT(NumVRFCond))
ALLOCATE(MinDeltaT(NumVRFCond))
ALLOCATE(LastModeCooling(NumVRFCond))
ALLOCATE(LastModeHeating(NumVRFCond))
ALLOCATE(HeatingLoad(NumVRFCond))
ALLOCATE(CoolingLoad(NumVRFCond))
ALLOCATE(NumCoolingLoads(NumVRFCond))
ALLOCATE(SumCoolingLoads(NumVRFCond))
ALLOCATE(NumHeatingLoads(NumVRFCond))
ALLOCATE(SumHeatingLoads(NumVRFCond))
ALLOCATE(MyVRFCondFlag(NumVRFCond))
MyEnvrnFlag = .TRUE.
MySizeFlag = .TRUE.
MyVRFFlag = .TRUE.
MyBeginTimeStepFlag = .TRUE.
MaxDeltaT = 0.d0
MinDeltaT = 0.d0
LastModeCooling = .FALSE.
LastModeHeating = .TRUE.
NumCoolingLoads = 0
SumCoolingLoads = 0.d0
NumHeatingLoads = 0
SumHeatingLoads = 0.d0
MyOneTimeFlag = .FALSE.
MyVRFCondFlag = .TRUE.
END IF ! IF (MyOneTimeFlag) THEN
! identify VRF condenser connected to this TU
VRFCond = VRFTU(VRFTUNum)%VRFSysNum
TUListIndex = VRF(VRFCond)%ZoneTUListPtr
InNode = VRFTU(VRFTUNum)%VRFTUInletNodeNum
OutNode = VRFTU(VRFTUNum)%VRFTUOutletNodeNum
OutsideAirNode = VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum
IndexToTUInTUList = VRFTU(VRFTUNum)%IndexToTUInTUList
! set condenser inlet temp, used as surrogate for OAT (used to check limits of operation)
IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
OutsideDryBulbTemp = Node(VRF(VRFCond)%CondenserNodeNum)%Temp
ELSE
IF(OutsideAirNode .EQ. 0)THEN
OutsideDryBulbTemp = OutDryBulbTemp
ELSE
OutsideDryBulbTemp = Node(OutsideAirNode)%Temp
END IF
END IF
IF (ALLOCATED(ZoneComp)) THEN
ZoneComp(VRFTerminalUnit_Num)%ZoneCompAvailMgrs(VRFTUNum)%ZoneNum = ZoneNum
VRFTU(VRFTUNum)%AvailStatus = ZoneComp(VRFTerminalUnit_Num)%ZoneCompAvailMgrs(VRFTUNum)%AvailStatus
ENDIF
! If all VRF Terminal Units on this VRF AC System have been simulated, reset the IsSimulated flag
! The condenser will be simulated after all terminal units have been simulated (see Sub SimulateVRF)
IF(ALL(TerminalUnitList(TUListIndex)%IsSimulated))THEN
! this should be the first time through on the next iteration. All TU's and condenser have been simulated.
! reset simulation flag for each terminal unit
TerminalUnitList(TUListIndex)%IsSimulated = .FALSE.
! after all TU's have been simulated, reset operating mode flag if necessary
IF(LastModeHeating(VRFCond) .AND. CoolingLoad(VRFCond))THEN
LastModeCooling(VRFCond) = .TRUE.
LastModeHeating(VRFCond) = .FALSE.
! SwitchedMode(VRFCond) = .TRUE.
END IF
IF(LastModeCooling(VRFCond) .AND. HeatingLoad(VRFCond))THEN
LastModeHeating(VRFCond) = .TRUE.
LastModeCooling(VRFCond) = .FALSE.
! SwitchedMode(VRFCond) = .TRUE.
END IF
END IF ! IF(ALL(TerminalUnitList(VRFTU(VRFTUNum)%TUListIndex)%IsSimulated))THEN
! one-time check to see if VRF TU's are on Zone Equipment List or issue warning
IF(ZoneEquipmentListNotChecked)THEN
IF(ZoneEquipInputsFilled)THEN
ZoneEquipmentListNotChecked=.FALSE.
DO TUListNum = 1, NumVRFTULists
DO NumTULoop=1,TerminalUnitList(TUListNum)%NumTUInList
TUIndex = TerminalUnitList(TUListNum)%ZoneTUPtr(NumTULoop)
EquipList: DO ELLoop=1,NumOfZones ! NumofZoneEquipLists
IF (ZoneEquipList(ELLoop)%Name == ' ') CYCLE ! dimensioned by NumOfZones. Only valid ones have names.
DO ListLoop=1,ZoneEquipList(ELLoop)%NumOfEquipTypes
IF (.NOT. SameString(ZoneEquipList(ELLoop)%EquipType(ListLoop),cVRFTUTypes(VRFTU(TUIndex)%VRFTUType_Num)))CYCLE
IF (.NOT. SameString(ZoneEquipList(ELLoop)%EquipName(ListLoop), VRFTU(TUIndex)%Name)) CYCLE
VRFTU(TUIndex)%ZoneNum = ELLoop
IF(VRF(VRFTU(TUIndex)%VRFSysNum)%MasterZonePTR == ELLoop)THEN
VRF(VRFTU(TUIndex)%VRFSysNum)%MasterZoneTUIndex = TUIndex
END IF
EXIT EquipList
ENDDO
ENDDO EquipList
ENDDO
IF (CheckZoneEquipmentList(cVRFTUTypes(VRFTU(TUIndex)%VRFTUType_Num),VRFTU(TUIndex)%Name)) CYCLE
CALL ShowSevereError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(TUIndex)%VRFTUType_Num))//','//TRIM(VRFTU(TUIndex)%Name)// &
'] is not on any ZoneHVAC:EquipmentList. It will not be simulated.')
CALL ShowContinueError('...The VRF AC System associated with this terminal unit may also not be simulated.')
ENDDO
END IF ! IF(ZoneEquipInputsFilled) THEN
ENDIF ! IF(ZoneEquipmentListNotChecked)THEN
! Size TU
IF (MySizeFlag(VRFTUNum)) THEN
IF ( .NOT. SysSizingCalc) THEN
CALL SizeVRF(VRFTUNum)
TerminalUnitList(TUListIndex)%TerminalUnitNotSizedYet(IndexToTUInTUList) = .FALSE.
MySizeFlag(VRFTUNum) = .FALSE.
END IF ! IF ( .NOT. SysSizingCalc) THEN
END IF ! IF (MySizeFlag(VRFTUNum)) THEN
! Do the Begin Environment initializations
IF (BeginEnvrnFlag .and. MyEnvrnFlag(VRFTUNum)) THEN
!Change the Volume Flow Rates to Mass Flow Rates
RhoAir = StdRhoAir
! set the mass flow rates from the input volume flow rates
VRFTU(VRFTUNum)%MaxCoolAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxCoolAirVolFlow
VRFTU(VRFTUNum)%CoolOutAirMassFlow = RhoAir*VRFTU(VRFTUNum)%CoolOutAirVolFlow
VRFTU(VRFTUNum)%MaxHeatAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxHeatAirVolFlow
VRFTU(VRFTUNum)%HeatOutAirMassFlow = RhoAir*VRFTU(VRFTUNum)%HeatOutAirVolFlow
VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow
VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow
VRFTU(VRFTUNum)%NoCoolHeatOutAirMassFlow = RhoAir*VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
! set the node max and min mass flow rates
! outside air mixer is optional, check that node num > 0
IF(OutsideAirNode .GT. 0)THEN
Node(OutsideAirNode)%MassFlowRateMax = MAX(VRFTU(VRFTUNum)%CoolOutAirMassFlow,VRFTU(VRFTUNum)%HeatOutAirMassFlow)
Node(OutsideAirNode)%MassFlowRateMin = 0.0d0
Node(OutsideAirNode)%MassFlowRateMinAvail = 0.0d0
END IF
Node(OutNode)%MassFlowRateMax = MAX(VRFTU(VRFTUNum)%MaxCoolAirMassFlow,VRFTU(VRFTUNum)%MaxHeatAirMassFlow)
Node(OutNode)%MassFlowRateMin = 0.0d0
Node(OutNode)%MassFlowRateMinAvail = 0.0d0
Node(InNode)%MassFlowRateMax = MAX(VRFTU(VRFTUNum)%MaxCoolAirMassFlow,VRFTU(VRFTUNum)%MaxHeatAirMassFlow)
Node(InNode)%MassFlowRateMin = 0.0d0
Node(InNode)%MassFlowRateMinAvail = 0.0d0
IF(VRFTU(VRFTUNum)%VRFTUOAMixerRelNodeNum .GT. 0)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRelNodeNum)%MassFlowRateMinAvail = 0.0d0
END IF
MyEnvrnFlag(VRFTUNum) = .FALSE.
IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
rho = GetDensityGlycol(PlantLoop(VRF(VRFCond)%SourceLoopNum)%FluidName, &
InitconvTemp, &
PlantLoop(VRF(VRFCond)%SourceLoopNum)%FluidIndex, &
'InitVRF')
VRF(VRFCond)%WaterCondenserDesignMassFlow = VRF(VRFCond)%WaterCondVolFlowRate * rho
CALL InitComponentNodes( 0.d0,VRF(VRFCond)%WaterCondenserDesignMassFlow, &
VRF(VRFCond)%CondenserNodeNum, &
VRF(VRFCond)%CondenserOutletNodeNum, &
VRF(VRFCond)%SourceLoopNum, &
VRF(VRFCond)%SourceLoopSideNum, &
VRF(VRFCond)%SourceBranchNum, &
VRF(VRFCond)%SourceCompNum)
END IF
! IF(MyVRFCondFlag(VRFCond))THEN
VRF(VRFCond)%HRTimer = 0.d0
VRF(VRFCond)%ModeChange = .FALSE.
VRF(VRFCond)%HRModeChange = .FALSE.
MyVRFCondFlag(VRFCond) = .FALSE.
! END IF
END IF ! IF (BeginEnvrnFlag .and. MyEnvrnFlag(VRFTUNum)) THEN
! reset environment flag for next environment
IF (.not. BeginEnvrnFlag) THEN
MyEnvrnFlag(VRFTUNum) = .TRUE.
MyVRFCondFlag(VRFCond) = .TRUE.
ENDIF
! one-time checks of flow rate vs fan flow rate
IF(MyVRFFlag(VRFTUNum))THEN
IF(.NOT. SysSizingCalc)THEN
IF(VRFTU(VRFTUNum)%ActualFanVolFlowRate /= Autosize)THEN
IF (VRFTU(VRFTUNum)%MaxCoolAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('... has Supply Air Flow Rate During Cooling Operation > Max Fan Volume Flow Rate, should be <=')
CALL ShowContinueError('... Supply Air Flow Rate During Cooling Operation = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxCoolAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Max Fan Volume Flow Rate = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
CALL ShowContinueError('...the supply air flow rate during cooling operation will be reduced'// &
' to match and the simulation continues.')
VRFTU(VRFTUNum)%MaxCoolAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
ENDIF
IF (VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('... has Supply Air Flow Rate When No Cooling is Needed > Max Fan Volume Flow Rate, should be <=')
CALL ShowContinueError('... Supply Air Flow Rate When No Cooling is Needed = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Max Fan Volume Flow Rate = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
CALL ShowContinueError('...the supply air flow rate when no cooling is needed will be reduced'// &
' to match and the simulation continues.')
VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
ENDIF
IF(VRFTU(VRFTUNum)%CoolOutAirVolFlow .GT. VRFTU(VRFTUNum)%MaxCoolAirVolFlow)THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('...The Outdoor Air Flow Rate During Cooling Operation exceeds the Supply Air'// &
' Flow Rate During Cooling Operation.')
CALL ShowContinueError('...Outdoor Air Flow Rate During Cooling Operation = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%CoolOutAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Supply Air Flow Rate During Cooling Operation = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxCoolAirVolFlow,4))//' m3/s')
CALL ShowContinueError('...the outdoor air flow rate will be reduced to match and the simulation continues.')
VRFTU(VRFTUNum)%CoolOutAirVolFlow = VRFTU(VRFTUNum)%MaxCoolAirVolFlow
END IF
IF (VRFTU(VRFTUNum)%MaxHeatAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('... has Supply Air Flow Rate During Heating Operation > Max Fan Volume Flow Rate, should be <=')
CALL ShowContinueError('... Supply Air Flow Rate During Heating Operation = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxHeatAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Max Fan Volume Flow Rate = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
CALL ShowContinueError('...the supply air flow rate during cooling operation will be reduced'// &
' to match and the simulation continues.')
VRFTU(VRFTUNum)%MaxHeatAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
ENDIF
IF (VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('... has Supply Air Flow Rate When No Heating is Needed > Max Fan Volume Flow Rate, should be <=')
CALL ShowContinueError('... Supply Air Flow Rate When No Heating is Needed = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Max Fan Volume Flow Rate = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
CALL ShowContinueError('...the supply air flow rate when no cooling is needed will be reduced'// &
' to match and the simulation continues.')
VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
ENDIF
IF(VRFTU(VRFTUNum)%HeatOutAirVolFlow .GT. VRFTU(VRFTUNum)%MaxHeatAirVolFlow)THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('...The Outdoor Air Flow Rate During Heating Operation exceeds the Supply Air'// &
' Flow Rate During Heating Operation.')
CALL ShowContinueError('...Outdoor Air Flow Rate During Heating Operation = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%HeatOutAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Supply Air Flow Rate During Heating Operation = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxHeatAirVolFlow,4))//' m3/s')
CALL ShowContinueError('...the outdoor air flow rate will be reduced to match and the simulation continues.')
VRFTU(VRFTUNum)%HeatOutAirVolFlow = VRFTU(VRFTUNum)%MaxHeatAirVolFlow
END IF
IF (VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
//TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
CALL ShowContinueError('... has a Outdoor Air Flow Rate When No Cooling or Heating is Needed > '// &
'Max Fan Volume Flow Rate, should be <=')
CALL ShowContinueError('... Outdoor Air Flow Rate When No Cooling or Heating is Needed = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow,4))//' m3/s')
CALL ShowContinueError('... Max Fan Volume Flow Rate = '// &
TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
CALL ShowContinueError('...the outdoor air flow rate when no cooling or heating is needed will be reduced'// &
' to match and the simulation continues.')
VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
ENDIF
IF(VRFTU(VRFTUNum)%ActualFanVolFlowRate .GT. 0.0d0)THEN
VRFTU(VRFTUNum)%HeatingSpeedRatio = VRFTU(VRFTUNum)%MaxHeatAirVolFlow/VRFTU(VRFTUNum)%ActualFanVolFlowRate
VRFTU(VRFTUNum)%CoolingSpeedRatio = VRFTU(VRFTUNum)%MaxCoolAirVolFlow/VRFTU(VRFTUNum)%ActualFanVolFlowRate
END IF
MyVRFFlag(VRFTUNum) = .FALSE.
ELSE
CALL GetFanVolFlow(VRFTU(VRFTUNum)%FanIndex,VRFTU(VRFTUNum)%ActualFanVolFlowRate)
END IF
END IF
END IF ! IF(MyVRFFlag(VRFTUNum))THEN
! calculate end time of current time step to determine if max capacity reset is required
CurrentEndTime = CurrentTime + SysTimeElapsed
! Initialize the maximum allowed terminal unit capacity. Total terminal unit capacity must not
! exceed the available condenser capacity. This variable is used to limit the terminal units
! providing more capacity than allowed. Example: TU loads are 1-ton, 2-ton, 3-ton, and 4-ton connected
! to a condenser having only 9-tons available. This variable will be set to 3-tons and the 4-ton
! terminal unit will be limited to 3-tons (see SimVRFCondenser where this variable is calculated).
IF(CurrentEndTime .GT. CurrentEndTimeLast .OR. TimeStepSysLast .GT. TimeStepSys .OR. &
FirstHVACIteration .AND. MyBeginTimeStepFlag(VRFCond))THEN
MaxCoolingCapacity(VRFCond) = MaxCap
MaxHeatingCapacity(VRFCond) = MaxCap
MyBeginTimeStepFlag(VRFCond) = .FALSE.
END IF
IF(.NOT. FirstHVACIteration)MyBeginTimeStepFlag(VRFCond) = .TRUE.
! Do the following initializations (every time step).
TimeStepSysLast = TimeStepSys
CurrentEndTimeLast = CurrentEndTime
! TUListNum = VRFTU(VRFTUNum)%TUListIndex
IF (VRFTU(VRFTUNum)%FanOpModeSchedPtr .GT. 0) THEN
IF (GetCurrentScheduleValue(VRFTU(VRFTUNum)%FanOpModeSchedPtr) .EQ. 0.0d0) THEN
VRFTU(VRFTUNum)%OpMode = CycFanCycCoil
ELSE
VRFTU(VRFTUNum)%OpMode = ContFanCycCoil
END IF
END IF
! if condenser is off, all terminal unit coils are off
!!!LKL Discrepancy < 0
IF (GetCurrentScheduleValue(VRF(VRFCond)%SchedPtr) .EQ. 0.0d0) THEN
HeatingLoad(VRFCond) = .FALSE.
CoolingLoad(VRFCond) = .FALSE.
ELSE
!*** Operating Mode Initialization done at beginning of each iteration ***!
!*** assumes all TU's and Condeser were simulated last iteration ***!
!*** this code is done ONCE each iteration when all TU's IsSimulated flag is FALSE ***!
! Determine operating mode prior to simulating any terminal units connected to a VRF condenser
! this should happen at the beginning of a time step where all TU's are polled to see what
! mode the heat pump condenser will operate in
IF(.NOT. ANY(TerminalUnitList(TUListIndex)%IsSimulated))THEN
CALL InitializeOperatingMode(FirstHVACIteration,VRFCond,TUListIndex,OnOffAirFlowRatio)
END IF ! IF(.NOT. ANY(TerminalUnitList(TUListNum)%IsSimulated))THEN
!*** End of Operating Mode Initialization done at beginning of each iteration ***!
! disable VRF system when outside limits of operation based on OAT
EnableSystem = .FALSE. ! flag used to switch operating modes when OAT is outside operating limits
IF(CoolingLoad(VRFCond))THEN
IF((OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATCooling .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATCooling) .AND. &
ANY(TerminalUnitList(TUListIndex)%CoolingCoilPresent))THEN
CoolingLoad(VRFCond) = .FALSE.
! test if heating load exists, account for thermostat control type
SELECT CASE(VRF(VRFCond)%ThermostatPriority)
CASE(LoadPriority, ZonePriority)
IF(SumHeatingLoads(VRFCond) .GT. 0.d0)EnableSystem = .TRUE.
CASE(ThermostatOffsetPriority)
IF(MinDeltaT(VRFCond) .LT. 0.d0)EnableSystem = .TRUE.
CASE(ScheduledPriority, MasterThermostatPriority)
! can't switch modes if scheduled (i.e., would be switching to unscheduled mode)
! or master TSTAT used (i.e., master zone only has a specific load - can't switch)
CASE DEFAULT
END SELECT
IF(EnableSystem)THEN
IF((OutsideDryBulbTemp .GE. VRF(VRFCond)%MinOATHeating .AND. OutsideDryBulbTemp .LE. VRF(VRFCond)%MaxOATHeating) .AND. &
ANY(TerminalUnitList(TUListIndex)%HeatingCoilPresent))THEN
HeatingLoad(VRFCond) = .TRUE.
ELSE
IF(ANY(TerminalUnitList(TUListIndex)%CoolingCoilAvailable))THEN
IF(VRF(VRFCond)%CoolingMaxTempLimitIndex == 0)THEN
CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Cooling Mode Limits have '// &
'been exceeded and VRF system is disabled.')
IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
ELSE
CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
END IF
CALL ShowContinueError('... Cooling Minimum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MinOATCooling,3)))
CALL ShowContinueError('... Cooling Maximum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATCooling,3)))
CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Cooling Mode limits.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'// &
TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max cooling temperature limit error continues...', &
VRF(VRFCond)%CoolingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
END IF
END IF
ELSE
IF(ANY(TerminalUnitList(TUListIndex)%CoolingCoilAvailable))THEN
IF(VRF(VRFCond)%CoolingMaxTempLimitIndex == 0)THEN
CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Cooling Mode Limits have '// &
'been exceeded and VRF system is disabled.')
IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
ELSE
CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
END IF
CALL ShowContinueError('... Cooling Minimum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MinOATCooling,3)))
CALL ShowContinueError('... Cooling Maximum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATCooling,3)))
CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Cooling Mode limits.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'// &
TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max cooling temperature limit error continues...', &
VRF(VRFCond)%CoolingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
END IF
END IF
END IF
ELSEIF(HeatingLoad(VRFCond))THEN
IF((OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATHeating .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATHeating) .AND. &
ANY(TerminalUnitList(TUListIndex)%HeatingCoilPresent))THEN
HeatingLoad(VRFCond) = .FALSE.
! test if heating load exists, account for thermostat control type
SELECT CASE(VRF(VRFCond)%ThermostatPriority)
CASE(LoadPriority, ZonePriority)
IF(SumCoolingLoads(VRFCond) .LT. 0.d0)EnableSystem = .TRUE.
CASE(ThermostatOffsetPriority)
IF(MaxDeltaT(VRFCond) .GT. 0.d0)EnableSystem = .TRUE.
CASE(ScheduledPriority, MasterThermostatPriority)
CASE DEFAULT
END SELECT
IF(EnableSystem)THEN
IF((OutsideDryBulbTemp .GE. VRF(VRFCond)%MinOATCooling .AND. OutsideDryBulbTemp .LE. VRF(VRFCond)%MaxOATCooling) .AND. &
ANY(TerminalUnitList(TUListIndex)%CoolingCoilPresent))THEN
CoolingLoad(VRFCond) = .TRUE.
ELSE
IF(ANY(TerminalUnitList(TUListIndex)%HeatingCoilAvailable))THEN
IF(VRF(VRFCond)%HeatingMaxTempLimitIndex == 0)THEN
CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Heating Mode Limits '// &
'have been exceeded and VRF system is disabled.')
IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
ELSE
CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
ENDIF
CALL ShowContinueError('... Heating Minimum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MinOATHeating,3)))
CALL ShowContinueError('... Heating Maximum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATHeating,3)))
CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Heating Mode limits.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'// &
TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max heating temperature limit error continues...', &
VRF(VRFCond)%HeatingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
END IF
END IF
ELSE
IF(ANY(TerminalUnitList(TUListIndex)%HeatingCoilAvailable))THEN
IF(VRF(VRFCond)%HeatingMaxTempLimitIndex == 0)THEN
CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Heating Mode Limits '// &
'have been exceeded and VRF system is disabled.')
IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
ELSE
CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
END IF
CALL ShowContinueError('... Heating Minimum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MinOATHeating,3)))
CALL ShowContinueError('... Heating Maximum Outdoor Unit Inlet Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATHeating,3)))
CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Heating Mode limits.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'// &
TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max heating temperature limit error continues...', &
VRF(VRFCond)%HeatingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
END IF
END IF
END IF
END IF
END IF ! IF (GetCurrentScheduleValue(VRF(VRFCond)%SchedPtr) .EQ. 0.0) THEN
! initialize terminal unit flow rate
IF(HeatingLoad(VRFCond) .OR. &
(VRF(VRFCond)%HeatRecoveryUsed .AND. TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList)))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
Node(OutsideAirNode)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
ELSE
Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
END IF
ELSE IF(CoolingLoad(VRFCond) .OR. &
(VRF(VRFCond)%HeatRecoveryUsed .AND. TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList)))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
Node(OutsideAirNode)%MassFlowRate = VRFTU(VRFTUNum)%CoolOutAirMassFlow
ELSE
Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
END IF
ELSE
IF(LastModeCooling(VRFCond))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
Node(OutsideAirNode)%MassFlowRate = VRFTU(VRFTUNum)%NoCoolHeatOutAirMassFlow
ELSE
Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
END IF
ELSEIF(LastModeHeating(VRFCond))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
Node(OutsideAirNode)%MassFlowRate = VRFTU(VRFTUNum)%NoCoolHeatOutAirMassFlow
ELSE
Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
END IF
END IF
END IF
IF(VRFTU(VRFTUNum)%OAMixerUsed)CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
OnOffAirFlowRatio = 1.0d0
! these flags are used in Subroutine CalcVRF to turn on the correct coil (heating or cooling)
! valid operating modes
! Heat Pump (heat recovery flags are set to FALSE):
! CoolingLoad(VRFCond) - TU can only operate in this mode if heat recovery is not used and there is a cooling load
! HeatingLoad(VRFCond) - TU can only operate in this mode if heat recovery is not used and there is a heating load
! Heat Recovery (heat pump flags are set same as for Heat Pump operation):
! TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) - TU will operate in this mode if heat recovery is used
! TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) - TU will operate in this mode if heat recovery is used
QZnReq = ZoneSysEnergyDemand(VRFTU(VRFTUNum)%ZoneNum)%RemainingOutputRequired
IF(ABS(QZnReq) .LT. SmallLoad) QZnReq = 0.d0
LoadToCoolingSP = ZoneSysEnergyDemand(VRFTU(VRFTUNum)%ZoneNum)%RemainingOutputReqToCoolSP
! set initial terminal unit operating mode for heat recovery
! operating mode for non-heat recovery set above using CoolingLoad(VRFCond) or HeatingLoad(VRFCond) variables
! first turn off terminal unit
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
! then set according to LoadToXXXXingSP variables
IF(LoadToCoolingSP .LT. -1.d0*SmallLoad)THEN
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
END IF
LoadToHeatingSP = ZoneSysEnergyDemand(VRFTU(VRFTUNum)%ZoneNum)%RemainingOutputReqToHeatSP
IF(LoadToHeatingSP .GT. SmallLoad)THEN
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
END IF
IF(LoadToCoolingSP > 0.d0 .AND. LoadToHeatingSP < 0.d0)QZnReq=0.d0
! next check for overshoot when constant fan mode is used
! check operating load to see if OA will overshoot setpoint temperature when constant fan mode is used
IF(VRFTU(VRFTUNum)%OpMode == ContFanCycCoil)THEN
CALL SetCompFlowRate(VRFTUNum, VRFCond, .TRUE.)
CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
! If the Terminal Unit has a net cooling capacity (TempOutput < 0) and
! the zone temp is above the Tstat heating setpoint (QToHeatSetPt < 0)
! see if the terminal unit operation will exceed the setpoint
!
! 4 tests here to cover all possibilities:
! IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .LT. 0.0d0)THEN
! ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .GT. 0.0d0)THEN
! ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .LT. 0.0d0)THEN
! ELSE IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .GT. 0.0d0)THEN
! END IF
! could compress these to 2 complex IF's but logic inside each would get more complex
!
IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .LT. 0.0d0)THEN
! If the net cooling capacity overshoots the heating setpoint count as heating load
IF(TempOutput < LoadToHeatingSP)THEN
! Don't count as heating load unless mode is allowed. Also check for floating zone.
IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleCoolingSetPoint .AND. &
TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
IF(.NOT. LastModeHeating(VRFCond))THEN
! system last operated in cooling mode, change air flows and repeat coil off capacity test
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
ELSE
Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
END IF
CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
! if zone temp will overshoot, pass the LoadToHeatingSP as the load to meet
IF(TempOutput < LoadToHeatingSP)THEN
QZnReq = LoadToHeatingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
ELSE
! last mode was heating, zone temp will overshoot heating setpoint, reset QznReq to LoadtoHeatingSP
QZnReq = LoadToHeatingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
END IF
ELSE IF(TempOutput > LoadToCoolingSP .AND. LoadToCoolingSP < 0.d0)THEN
! If the net cooling capacity does not meet the zone cooling load enable cooling
QZnReq = LoadToCoolingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
ELSE IF(TempOutput < LoadToCoolingSP .AND. LoadToCoolingSP < 0.d0)THEN
! If the net cooling capacity meets the zone cooling load but does not overshoot heating setpoint
QZnReq = 0.d0
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
! If the terminal unit has a net heating capacity and the zone temp is below the Tstat cooling setpoint
! see if the terminal unit operation will exceed the setpoint
ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .GT. 0.0d0)THEN
! If the net heating capacity overshoots the cooling setpoint count as cooling load
IF(TempOutput > LoadToCoolingSP)THEN
! Don't count as cooling load unless mode is allowed. Also check for floating zone.
IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleHeatingSetPoint .AND. &
TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
IF(.NOT. LastModeCooling(VRFCond))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%CoolOutAirMassFlow
CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
ELSE
Node(VRFTU(VRFTUNum)%VRFTUInletNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
END IF
CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
! if zone temp will overshoot, pass the LoadToCoolingSP as the load to meet
IF(TempOutput > LoadToCoolingSP)THEN
QZnReq = LoadToCoolingSP
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
END IF
ELSE
QZnReq = LoadToCoolingSP
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
END IF
END IF
ELSE IF(TempOutput .LT. LoadToHeatingSP)THEN
! Don't count as heating load unless mode is allowed. Also check for floating zone.
IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleCoolingSetPoint .AND. &
TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
IF(.NOT. LastModeHeating(VRFCond))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
ELSE
Node(VRFTU(VRFTUNum)%VRFTUInletNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
END IF
CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
! if zone temp will overshoot, pass the LoadToHeatingSP as the load to meet
IF(TempOutput < LoadToHeatingSP)THEN
QZnReq = LoadToHeatingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
ELSE
QZnReq = LoadToHeatingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
END IF
ELSE IF(TempOutput > LoadToHeatingSP .AND. TempOutput < LoadToCoolingSP)THEN
! If the net capacity does not overshoot either setpoint
QZnReq = 0.d0
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
ELSE
! If the net heating capacity meets the zone heating load but does not overshoot cooling setpoint
QZnReq = 0.d0
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
! If the terminal unit has a net heating capacity and the zone temp is above the Tstat cooling setpoint
! see if the terminal unit operation will exceed the setpoint
ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .LT. 0.0d0)THEN
! If the net heating capacity overshoots the cooling setpoint count as cooling load
! Don't count as cooling load unless mode is allowed. Also check for floating zone.
IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleHeatingSetPoint .AND. &
TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
IF(.NOT. LastModeCooling(VRFCond))THEN
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%CoolOutAirMassFlow
CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
ELSE
Node(VRFTU(VRFTUNum)%VRFTUInletNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
END IF
CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
! if zone temp will overshoot, pass the LoadToCoolingSP as the load to meet
IF(TempOutput > LoadToCoolingSP)THEN
QZnReq = LoadToCoolingSP
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
END IF
! last mode was cooling, zone temp will overshoot cooling setpoint, reset QznReq to LoadtoCoolingSP
ELSE
QZnReq = LoadToCoolingSP
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
END IF
END IF
! If the Terminal Unit has a net cooling capacity (TempOutput < 0) and
! the zone temp is below the Tstat heating setpoint (QToHeatSetPt > 0)
! see if the terminal unit operation will exceed the setpoint
ELSE IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .GT. 0.0d0)THEN
! Don't count as heating load unless mode is allowed. Also check for floating zone.
IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleCoolingSetPoint .AND. &
TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
IF(.NOT. LastModeHeating(VRFCond))THEN
! system last operated in cooling mode, change air flows and repeat coil off capacity test
IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
ELSE
Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
END IF
CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
! if zone temp will overshoot, pass the LoadToHeatingSP as the load to meet
IF(TempOutput < LoadToHeatingSP)THEN
QZnReq = LoadToHeatingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
ELSE
! last mode was heating, zone temp will overshoot heating setpoint, reset QznReq to LoadtoHeatingSP
QZnReq = LoadToHeatingSP
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
END IF
END IF
END IF ! IF(VRFTU(VRFTUNum)%OpMode == ContFanCycCoil)THEN
IF(VRF(VRFCond)%HeatRecoveryUsed)THEN
IF(OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATHeatRecovery .OR. &
OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATHeatRecovery)THEN
IF(ANY(TerminalUnitList(TUListIndex)%HRCoolRequest) .OR. &
ANY(TerminalUnitList(TUListIndex)%HRHeatRequest))THEN
IF(VRF(VRFCond)%HRMaxTempLimitIndex == 0)THEN
CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Outdoor Temperature in Heat Recovery Mode Limits '// &
'have been exceeded and VRF heat recovery is disabled.')
CALL ShowContinueError('... Outdoor Dry-Bulb Temperature = '// &
TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
CALL ShowContinueError('... Heat Recovery Minimum Outdoor Dry-Bulb Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MinOATHeatRecovery,3)))
CALL ShowContinueError('... Heat Recovery Maximum Outdoor Dry-Bulb Temperature = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATHeatRecovery,3)))
CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Heat Recovery Mode limits.')
CALL ShowContinueError('...the system will operate in heat pump mode when applicable.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'// &
TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Recovery min/max outdoor temperature limit error continues...', &
VRF(VRFCond)%HRMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
END IF
! Allow heat pump mode to operate if within limits
IF(OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATCooling .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATCooling)THEN
! Disable cooling mode only, heating model will still be allowed
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
IF(OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATHeating .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATHeating)THEN
! Disable heating mode only, cooling model will still be allowed
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
END IF
END IF
ELSE
TerminalUnitList(TUListIndex)%HRHeatRequest = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest = .FALSE.
END IF
! Override operating mode when using EMS
! this logic seems suspect, uses a "just run it on" mentality. Nee to test using EMS.
IF (VRF(VRFCond)%EMSOverrideHPOperatingMode) THEN
IF(VRF(VRFCond)%EMSValueForHPOperatingMode == 0.d0)THEN ! Off
HeatingLoad(VRFCond) = .FALSE.
CoolingLoad(VRFCond) = .FALSE.
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
ELSE IF(VRF(VRFCond)%EMSValueForHPOperatingMode == 1.d0)THEN ! Cooling
HeatingLoad(VRFCond) = .FALSE.
CoolingLoad(VRFCond) = .TRUE.
QZnReq = LoadToCoolingSP
IF(VRF(VRFCond)%HeatRecoveryUsed)THEN
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
END IF
ELSE IF(VRF(VRFCond)%EMSValueForHPOperatingMode == 2.d0)THEN ! Heating
HeatingLoad(VRFCond) = .TRUE.
CoolingLoad(VRFCond) = .FALSE.
QZnReq = LoadToHeatingSP
IF(VRF(VRFCond)%HeatRecoveryUsed)THEN
TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
END IF
ELSE
IF(VRF(VRFCond)%HPOperatingModeErrorIndex == 0)THEN
CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
CALL ShowContinueError('...InitVRF: Illegal HP operating mode = '// &
TRIM(TrimSigDigits(VRF(VRFCond)%EMSValueForHPOperatingMode,0)))
CALL ShowContinueError('...InitVRF: VRF HP operating mode will not be controlled by EMS.')
END IF
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'// &
TRIM(VRF(VRFCond)%Name)//'" -- Illegal HP operating mode error continues...', &
VRF(VRFCond)%HPOperatingModeErrorIndex,VRF(VRFCond)%EMSValueForHPOperatingMode, &
VRF(VRFCond)%EMSValueForHPOperatingMode)
END IF
ENDIF
! set the TU flow rate. Check for heat recovery operation first, these will be FALSE if HR is not used.
IF(TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList))THEN
CompOnMassFlow = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
OACompOnMassFlow = VRFTU(VRFTUNum)%CoolOutAirMassFlow
OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
ELSE IF(TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList))THEN
CompOnMassFlow = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
OACompOnMassFlow = VRFTU(VRFTUNum)%HeatOutAirMassFlow
OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
ELSE IF(CoolingLoad(VRFCond) .and. QZnReq /= 0.d0)THEN
CompOnMassFlow = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
OACompOnMassFlow = VRFTU(VRFTUNum)%CoolOutAirMassFlow
OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
ELSE IF(HeatingLoad(VRFCond) .and. QZnReq /= 0.d0)THEN
CompOnMassFlow = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
OACompOnMassFlow = VRFTU(VRFTUNum)%HeatOutAirMassFlow
OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
ELSE
IF(LastModeCooling(VRFCond))THEN
CompOnMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
OACompOnMassFlow = VRFTU(VRFTUNum)%CoolOutAirMassFlow
END IF
IF(LastModeHeating(VRFCond))THEN
CompOnMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
OACompOnMassFlow = VRFTU(VRFTUNum)%HeatOutAirMassFlow
END IF
OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
END IF
IF(VRFTU(VRFTUNum)%OpMode .EQ. CycFanCycCoil)THEN
CompOffMassFlow = 0.d0
OACompOffMassFlow = 0.d0
END IF
CALL SetAverageAirFlow(VRFTUNum, 0.d0, OnOffAirFlowRatio)
RETURN
END SUBROUTINE InitVRF