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.
!LKL Discrepancy < 0
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | VRFTUNum | |||
real(kind=r64), | intent(in) | :: | QZnReq | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
real(kind=r64), | intent(out) | :: | PartLoadRatio | |||
real(kind=r64), | intent(inout) | :: | OnOffAirFlowRatio |
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.
SUBROUTINE ControlVRF(VRFTUNum,QZnReq,FirstHVACIteration,PartLoadRatio, OnOffAirFlowRatio)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad
! DATE WRITTEN July 2005
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Determine the part load fraction of the heat pump for this time step.
! METHODOLOGY EMPLOYED:
! Use RegulaFalsi technique to iterate on part-load ratio until convergence is achieved.
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: SolveRegulaFalsi, RoundSigDigits, TrimSigDigits
USE HeatingCoils, ONLY: SimulateHeatingCoilComponents
USE DataEnvironment, ONLY: OutDryBulbTemp
USE ScheduleManager, ONLY: GetCurrentScheduleValue
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: VRFTUNum ! Index to VRF terminal unit
REAL(r64), INTENT (IN) :: QZnReq ! Index to zone number
LOGICAL, INTENT (IN) :: FirstHVACIteration ! flag for 1st HVAC iteration in the time step
REAL(r64), INTENT (OUT) :: PartLoadRatio ! unit part load ratio
REAL(r64), INTENT (INOUT) :: OnOffAirFlowRatio ! ratio of compressor ON airflow to AVERAGE airflow over timestep
! SUBROUTINE PARAMETER DEFINITIONS:
!
INTEGER, PARAMETER :: MaxIte = 500 ! maximum number of iterations
REAL(r64), PARAMETER :: MinPLF = 0.0d0 ! minimum part load factor allowed
REAL(r64), PARAMETER :: ErrorTol = 0.001d0 ! tolerance for RegulaFalsi iterations
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: FullOutput ! unit full output when compressor is operating [W]
REAL(r64) :: TempOutput ! unit output when iteration limit exceeded [W]
REAL(r64) :: NoCompOutput ! output when no active compressor [W]
INTEGER :: SolFla ! Flag of RegulaFalsi solver
REAL(r64), DIMENSION(6) :: Par ! Parameters passed to RegulaFalsi
CHARACTER(len=20) :: IterNum ! Max number of iterations for warning message
REAL(r64) :: TempMinPLR ! min PLR used in Regula Falsi call
REAL(r64) :: TempMaxPLR ! max PLR used in Regula Falsi call
LOGICAL :: ContinueIter ! used when convergence is an issue
INTEGER :: VRFCond ! index to VRF condenser
INTEGER :: IndexToTUInTUList ! index to TU in specific list for the VRF system
INTEGER :: TUListIndex ! index to TU list for this VRF system
LOGICAL :: VRFCoolingMode
LOGICAL :: VRFHeatingMode
LOGICAL :: HRCoolingMode
LOGICAL :: HRHeatingMode
PartLoadRatio = 0.d0
LoopDXCoolCoilRTF = 0.d0
LoopDXHeatCoilRTF = 0.d0
VRFCond = VRFTU(VRFTUNum)%VRFSysNum
IndexToTUInTUList = VRFTU(VRFTUNum)%IndexToTUInTUList
TUListIndex = VRF(VRFCond)%ZoneTUListPtr
VRFCoolingMode = CoolingLoad(VRFCond)
VRFHeatingMode = HeatingLoad(VRFCond)
HRCoolingMode = TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList)
HRHeatingMode = TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList)
! The RETURNS here will jump back to SimVRF where the CalcVRF routine will simulate with lastest PLR
! do nothing else if TU is scheduled off
!!!LKL Discrepancy < 0
IF (GetCurrentScheduleValue(VRFTU(VRFTUNum)%SchedPtr) .EQ. 0.0d0) RETURN
! do nothing if TU has no load (TU will be modeled using PLR=0)
IF (QZnReq == 0.d0) RETURN
! Set EMS value for PLR and return
IF (VRFTU(VRFTUNum)%EMSOverridePartLoadFrac) THEN
PartLoadRatio = VRFTU(VRFTUNum)%EMSValueForPartLoadFrac
RETURN
ENDIF
! Get result when DX coil is off
PartLoadRatio = 0.0d0
CALL CalcVRF(VRFTUNum, FirstHVACIteration, 0.0d0, NoCompOutput, OnOffAirFlowRatio)
IF(VRFCoolingMode .AND. HRHeatingMode)THEN
! IF the system is in cooling mode, but the terminal unit requests heating (heat recovery)
IF(NoCompOutput .GE. QZnReq)RETURN
ELSE IF(VRFHeatingMode .AND. HRCoolingMode)THEN
! IF the system is in heating mode, but the terminal unit requests cooling (heat recovery)
IF(NoCompOutput .LE. QZnReq)RETURN
ELSE IF(VRFCoolingMode .OR. HRCoolingMode)THEN
! IF the system is in cooling mode and/or the terminal unit requests cooling
IF(NoCompOutput .LE. QZnReq)RETURN
ELSE IF(VRFHeatingMode .OR. HRHeatingMode)THEN
! IF the system is in heating mode and/or the terminal unit requests heating
IF(NoCompOutput .GE. QZnReq)RETURN
END IF
! Otherwise the coil needs to turn on. Get full load result
PartLoadRatio = 1.0d0
CALL CalcVRF(VRFTUNum, FirstHVACIteration, PartLoadRatio, FullOutput, OnOffAirFlowRatio)
PartLoadRatio = 0.0d0
IF ((VRFCoolingMode .AND. .NOT. VRF(VRFCond)%HeatRecoveryUsed) .OR. &
(VRF(VRFCond)%HeatRecoveryUsed .AND. HRCoolingMode)) THEN
! Since we are cooling, we expect FullOutput < NoCompOutput
! If the QZnReq <= FullOutput the unit needs to run full out
IF (QZnReq <= FullOutput) THEN
! if no coil present in terminal unit, no need to reset PLR?
IF(VRFTU(VRFTUNum)%CoolingCoilPresent)PartLoadRatio = 1.0d0
RETURN
END IF
ELSE IF((VRFHeatingMode .AND. .NOT. VRF(VRFCond)%HeatRecoveryUsed) .OR. &
(VRF(VRFCond)%HeatRecoveryUsed .AND. HRHeatingMode)) THEN
! Since we are heating, we expect FullOutput > NoCompOutput
! If the QZnReq >= FullOutput the unit needs to run full out
IF (QZnReq >= FullOutput) THEN
! if no coil present in terminal unit, no need reset PLR?
IF(VRFTU(VRFTUNum)%HeatingCoilPresent)PartLoadRatio = 1.0d0
RETURN
END IF
ELSE
! VRF terminal unit is off, PLR already set to 0 above
! shouldn't actually get here
RETURN
END IF
! The coil will not operate at PLR=0 or PLR=1, calculate the operating part-load ratio
IF ((VRFHeatingMode .OR. HRHeatingMode) .OR. (VRFCoolingMode .OR. HRCoolingMode)) THEN
Par(1) = VRFTUNum
Par(2)=0.0d0
Par(4)=0.0d0
IF (FirstHVACIteration) THEN
Par(3) = 1.0d0
ELSE
Par(3) = 0.0d0
END IF
! Par(4) = OpMode
Par(5) = QZnReq
Par(6) = OnOffAirFlowRatio
CALL SolveRegulaFalsi(ErrorTol, MaxIte, SolFla, PartLoadRatio, PLRResidual, &
0.0d0, 1.0d0, Par)
IF (SolFla == -1) THEN
! Very low loads may not converge quickly. Tighten PLR boundary and try again.
TempMaxPLR = -0.1d0
ContinueIter = .TRUE.
DO WHILE(ContinueIter .AND. TempMaxPLR .LT. 1.0d0)
TempMaxPLR = TempMaxPLR + 0.1d0
CALL CalcVRF(VRFTUNum,FirstHVACIteration,TempMaxPLR,TempOutput,OnOffAirFlowRatio)
IF(VRFHeatingMode .AND. TempOutput .GT. QZnReq)ContinueIter = .FALSE.
IF(VRFCoolingMode .AND. TempOutput .LT. QZnReq)ContinueIter = .FALSE.
END DO
TempMinPLR = TempMaxPLR
ContinueIter = .TRUE.
DO WHILE(ContinueIter .AND. TempMinPLR .GT. 0.0d0)
TempMaxPLR = TempMinPLR
TempMinPLR = TempMinPLR - 0.01d0
CALL CalcVRF(VRFTUNum,FirstHVACIteration,TempMinPLR,TempOutput,OnOffAirFlowRatio)
IF(VRFHeatingMode .AND. TempOutput .LT. QZnReq)ContinueIter = .FALSE.
IF(VRFCoolingMode .AND. TempOutput .GT. QZnReq)ContinueIter = .FALSE.
END DO
CALL SolveRegulaFalsi(ErrorTol, MaxIte, SolFla, PartLoadRatio, PLRResidual, &
TempMinPLR, TempMaxPLR, Par)
IF (SolFla == -1) THEN
IF (.NOT. FirstHVACIteration .AND. .NOT. WarmupFlag) THEN
IF(VRFTU(VRFTUNum)%IterLimitExceeded == 0)THEN
WRITE(IterNum,*) MaxIte
IterNum=ADJUSTL(IterNum)
Call ShowWarningMessage(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'//TRIM(VRFTU(VRFTUNum)%Name)//'"')
CALL ShowContinueError(' Iteration limit exceeded calculating terminal unit part-load ratio, '// &
'maximum iterations = '//TRIM(IterNum))
CALL ShowContinueErrorTimeStamp(' Part-load ratio returned = '//TRIM(RoundSigDigits(PartLoadRatio,3)))
CALL CalcVRF(VRFTUNum,FirstHVACIteration,TempMinPLR,TempOutput,OnOffAirFlowRatio)
CALL ShowContinueError(' Load requested = '//TRIM(TrimSigDigits(QZnReq,5))//', Load delivered = ' &
//TRIM(TrimSigDigits(TempOutput,5)))
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'// &
TRIM(VRFTU(VRFTUNum)%Name)//'" -- Terminal unit Iteration limit exceeded error continues...', &
VRFTU(VRFTUNum)%IterLimitExceeded)
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'// &
TRIM(VRFTU(VRFTUNum)%Name)//'" -- Terminal unit Iteration limit exceeded error continues...', &
VRFTU(VRFTUNum)%IterLimitExceeded)
END IF
END IF
ELSE IF (SolFla == -2) THEN
IF (.NOT. FirstHVACIteration .AND. .NOT. WarmupFlag) THEN
IF(VRFTU(VRFTUNum)%FirstIterfailed == 0)THEN
Call ShowWarningMessage(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'//TRIM(VRFTU(VRFTUNum)%Name)//'"')
CALL ShowContinueError('Terminal unit part-load ratio calculation failed: ' &
//'PLR limits of 0 to 1 exceeded')
CALL ShowContinueError('Please fill out a bug report and forward to the EnergyPlus support group.')
CALL ShowContinueErrorTimeStamp(' ')
IF (WarmupFlag) CALL ShowContinueError ('Error occurred during warmup days.')
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'// &
TRIM(VRFTU(VRFTUNum)%Name)//'" -- Terminal unit part-load ratio limits of 0 to 1 exceeded error continues...', &
VRFTU(VRFTUNum)%FirstIterfailed)
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'// &
TRIM(VRFTU(VRFTUNum)%Name)//'" -- Terminal unit part-load ratio limits of 0 to 1 exceeded error continues...', &
VRFTU(VRFTUNum)%FirstIterfailed)
END IF
END IF
PartLoadRatio = MAX(MinPLF, ABS(QZnReq - NoCompOutput) / ABS(FullOutput - NoCompOutput))
END IF
ELSE IF (SolFla == -2) THEN
IF (.NOT. FirstHVACIteration .AND. .NOT. WarmupFlag) THEN
IF(VRFTU(VRFTUNum)%FirstIterfailed == 0)THEN
Call ShowWarningMessage(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'//TRIM(VRFTU(VRFTUNum)%Name)//'"')
CALL ShowContinueError('Terminal unit part-load ratio calculation failed: ' &
//'PLR limits of 0 to 1 exceeded')
CALL ShowContinueError('Please fill out a bug report and forward to the EnergyPlus support group.')
CALL ShowContinueErrorTimeStamp(' ')
IF (WarmupFlag) CALL ShowContinueError ('Error occurred during warmup days.')
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'// &
TRIM(VRFTU(VRFTUNum)%Name)//'" -- Terminal unit part-load ratio limits of 0 to 1 exceeded error continues...', &
VRFTU(VRFTUNum)%FirstIterfailed)
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//' "'// &
TRIM(VRFTU(VRFTUNum)%Name)//'" -- Terminal unit part-load ratio limits of 0 to 1 exceeded error continues...', &
VRFTU(VRFTUNum)%FirstIterfailed)
END IF
END IF
IF(FullOutput - NoCompOutput .EQ. 0.d0)THEN
PartLoadRatio = 0.d0
ELSE
PartLoadRatio = MIN(1.d0,MAX(MinPLF, ABS(QZnReq - NoCompOutput) / ABS(FullOutput - NoCompOutput)))
END IF
END IF
END IF
RETURN
END SUBROUTINE ControlVRF