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 | :: | EIRChillNum | ||||
real(kind=r64) | :: | MyLoad | ||||
logical, | intent(in) | :: | RunFlag | |||
logical | :: | FirstIteration | ||||
integer, | intent(in) | :: | EquipFlowCtrl |
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 ControlReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl)
! SUBROUTINE INFORMATION:
! AUTHOR Lixing Gu, FSEC
! DATE WRITTEN July 2006
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Simulate a vapor compression chiller using the reformulated model developed by Mark Hydeman
! METHODOLOGY EMPLOYED:
! Use empirical curve fits to model performance at off-design conditions. This subroutine
! calls Subroutines CalcReformEIRChillerModel and SolveRegulaFalsi to obtain solution.
! The actual chiller performance calculations are in Subroutine CalcReformEIRChillerModel.
! REFERENCES:
! 1. Hydeman, M., P. Sreedharan, N. Webb, and S. Blanc. 2002. "Development and Testing of a Reformulated
! Regression-Based Electric Chiller Model". ASHRAE Transactions, HI-02-18-2, Vol 108, Part 2, pp. 1118-1127.
! USE STATEMENTS:
USE DataGlobals, ONLY : WarmupFlag
USE DataInterfaces, ONLY : ShowFatalError, ShowSevereError, ShowWarningError, ShowContinueErrorTimeStamp, &
ShowRecurringWarningErrorAtEnd, ShowContinueError
USE DataHVACGlobals, ONLY : SmallLoad
USE CurveManager, ONLY : GetCurveMinMaxValues
USE DataBranchAirLoopPlant, ONLY: ControlType_SeriesActive
USE General, ONLY : SolveRegulaFalsi
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: EIRChillNum ! Chiller number
REAL(r64) :: MyLoad ! Operating load [W]
LOGICAL :: FirstIteration ! TRUE when first iteration of timestep
LOGICAL, INTENT(IN) :: RunFlag ! TRUE when chiller operating
INTEGER, INTENT(IN) :: EquipFlowCtrl ! Flow control mode for the equipment
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64),PARAMETER :: Acc = 0.0001D0 ! Accuracy control for SolveRegulaFalsi
INTEGER,PARAMETER :: MaxIter = 500 ! Iteration control for SolveRegulaFalsi
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: CAPFTYTmin ! Minimum condenser leaving temperature allowed by CAPFT curve [C]
REAL(r64) :: CAPFTYTmax ! Maximum condenser leaving temperature allowed by CAPFT curve [C]
REAL(r64) :: EIRFTYTmin ! Minimum condenser leaving temperature allowed by EIRFT curve [C]
REAL(r64) :: EIRFTYTmax ! Maximum condenser leaving temperature allowed by EIRFT curve [C]
REAL(r64) :: EIRFPLRTmin ! Minimum condenser leaving temperature allowed by EIRFPLR curve [C]
REAL(r64) :: EIRFPLRTmax ! Maximum condenser leaving temperature allowed by EIRFPLR curve [C]
REAL(r64) :: Tmin ! Minimum condenser leaving temperature allowed by curve objects [C]
REAL(r64) :: Tmax ! Maximum condenser leaving temperature allowed by curve objects [C]
REAL(r64) :: Par(6) ! Pass parameters for RegulaFalsi solver
REAL(r64) :: FalsiCondOutTemp ! RegulaFalsi condenser outlet temperature result [C]
INTEGER :: SolFla ! Feedback flag from SolveRegulaFalsi
REAL(r64) :: CondTempMin ! Condenser outlet temperature when using Tmin as input to CalcReformEIRChillerModel [C]
REAL(r64) :: CondTempMax ! Condenser outlet temperature when using Tmax as input to CalcReformEIRChillerModel [C]
IF (MyLoad >= 0.d0 .OR. .NOT. RunFlag) THEN
CALL CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl, &
Node(ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum)%Temp)
ELSE
! Find min/max condenser outlet temperature used by curve objects
CAPFTYTmin = ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTYTempMin
EIRFTYTmin = ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTYTempMin
EIRFPLRTmin = ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMin
Tmin = MIN(CAPFTYTmin, EIRFTYTmin, EIRFPLRTmin)
CAPFTYTmax = ElecReformEIRChiller(EIRChillNum)%ChillerCAPFTYTempMax
EIRFTYTmax = ElecReformEIRChiller(EIRChillNum)%ChillerEIRFTYTempMax
EIRFPLRTmax = ElecReformEIRChiller(EIRChillNum)%ChillerEIRFPLRTempMax
Tmax = MAX(CAPFTYTmax, EIRFTYTmax, EIRFPLRTmax)
! Check that condenser outlet temperature is within curve object limits prior to calling RegulaFalsi
CALL CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl,Tmin)
CondTempMin = CondOutletTemp
CALL CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl,Tmax)
CondTempMax = CondOutletTemp
IF(CondTempMin .GT. Tmin .AND. CondTempMax .LT. Tmax)THEN
! Initialize iteration parameters for RegulaFalsi function
Par(1) = EIRChillNum
Par(2) = MyLoad
IF (Runflag) THEN
Par(3) = 1.0d0
ELSE
Par(3) = 0.0d0
END IF
IF (FirstIteration) THEN
Par(4) = 1.0d0
ELSE
Par(4) = 0.0d0
END IF
!Par(5) = FlowLock !DSU
Par(6) = EquipFlowCtrl
CALL SolveRegulaFalsi(Acc, MaxIter, SolFla, FalsiCondOutTemp, CondOutTempResidual, Tmin, Tmax, Par)
IF (SolFla == -1) THEN
IF (.NOT. WarmupFlag) THEN
ElecReformEIRChiller(EIRChillNum)%IterLimitExceededNum = ElecReformEIRChiller(EIRChillNum)%IterLimitExceededNum + 1
IF (ElecReformEIRChiller(EIRChillNum)%IterLimitExceededNum .EQ. 1) THEN
CALL ShowWarningError(TRIM(ElecReformEIRChiller(EIRChillNum)%Name) // &
': Iteration limit exceeded calculating condenser outlet temperature and non-converged temperature is used')
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(ElecReformEIRChiller(EIRChillNum)%Name)// &
': Iteration limit exceeded calculating condenser outlet temperature.', &
ElecReformEIRChiller(EIRChillNum)%IterLimitErrIndex, CondOutletTemp, CondOutletTemp)
END IF
END IF
ELSE IF (SolFla == -2) THEN
IF (.NOT. WarmupFlag) THEN
ElecReformEIRChiller(EIRChillNum)%IterFailed = ElecReformEIRChiller(EIRChillNum)%IterFailed + 1
IF (ElecReformEIRChiller(EIRChillNum)%IterFailed .EQ. 1) THEN
CALL ShowWarningError(TRIM(ElecReformEIRChiller(EIRChillNum)%Name) // &
': Solution found when calculating condenser outlet temperature.'// &
' The inlet temperature will used and the simulation continues...')
CALL ShowContinueError('Please check minimum and maximum values of x in EIRFPLR Curve ' &
//TRIM(ElecReformEIRChiller(EIRChillNum)%EIRFPLRName))
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(ElecReformEIRChiller(EIRChillNum)%Name)// &
': Solution is not found in calculating condenser outlet temperature.', &
ElecReformEIRChiller(EIRChillNum)%IterFailedIndex, CondOutletTemp, CondOutletTemp)
END IF
END IF
CALL CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl, &
Node(ElecReformEIRChiller(EIRChillNum)%CondInletNodeNum)%Temp)
END IF
ELSE
! If iteration is not possible, average the min/max condenser outlet temperature and manually determine solution
CALL CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl,(CondTempMin+CondTempMax)/2.0d0)
CALL CalcReformEIRChillerModel(EIRChillNum,MyLoad,Runflag,FirstIteration,EquipFlowCtrl, CondOutletTemp)
END IF
! Call subroutine to evaluate all performance curve min/max values against evaporator/condenser outlet temps and PLR
CALL CheckMinMaxCurveBoundaries(EIRChillNum, FirstIteration)
END IF
RETURN
END SUBROUTINE ControlReformEIRChillerModel