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 | ||
---|---|---|---|---|---|---|
logical, | intent(in) | :: | FirstHVACIteration | |||
integer, | intent(in) | :: | AirLoopPass | |||
integer, | intent(in) | :: | AirLoopNum | |||
logical, | intent(out) | :: | AirLoopConvergedFlag | |||
integer, | intent(out) | :: | IterMax | |||
integer, | intent(out) | :: | IterTot | |||
integer, | intent(out) | :: | NumCalls |
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 SolveAirLoopControllers(FirstHVACIteration, AirLoopPass, AirLoopNum, AirLoopConvergedFlag, &
IterMax, IterTot, NumCalls)
! SUBROUTINE INFORMATION
! AUTHOR: Dimitri Curtil (LBNL)
! DATE WRITTEN: Feb 2006
! MODIFIED:
! RE-ENGINEERED: This is reengineered code that used to be in SimAirLoops()
! PURPOSE OF THIS SUBROUTINE:
! This subroutine solves for the controllers on the specfied air loop assuming a cold start.
! METHODOLOGY EMPLOYED:
! For the specified primary air system:
! (1) each component in the system is simulated in natural order, beginning at
! the return air inlet and progressing to the supply air outlets. Node data
! is passed in the same direction.
! (2) The controllers and their actions are simulated.
! (3) Steps 2 and 3 are repeated until the control criteria are satisfied.
! REFERENCES: None
! USE STATEMENTS:
USE DataHVACControllers
USE HVACControllers, ONLY : ManageControllers
USE General, ONLY : CreateSysTimeIntervalString
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
! TRUE if first full HVAC iteration in an HVAC timestep
LOGICAL, INTENT(IN) :: FirstHVACIteration
! DO loop index; there are 2 passes the 2nd is done only if mass balance fails
INTEGER, INTENT(IN) :: AirLoopPass
! Index of the air loop being simulated
INTEGER, INTENT(IN) :: AirLoopNum
! TRUE when primary air system & controllers simulation has converged;
LOGICAL, INTENT(OUT) :: AirLoopConvergedFlag
! Max number of iterations performed by controllers across this air loop
INTEGER, INTENT(OUT) :: IterMax
! Aggregated number of iterations across all controllers on this air loop
INTEGER, INTENT(OUT) :: IterTot
! Total number of times SimAirLoopComponents() has been invoked
INTEGER, INTENT(OUT) :: NumCalls
! SUBROUTINE PARAMETER DEFINITIONS:
! Maximum iterations of an air system/controllers simulation sequence
INTEGER, PARAMETER :: MaxIter = 50
! INTERFACE BLOCK DEFINITIONS: None
! DERIVED TYPE DEFINITIONS: None
! SUBROUTINE LOCAL VARIABLE DEFINITIONS
! TRUE if controller supports speculative warm restart
LOGICAL :: AllowWarmRestartFlag
! TRUE when controller has converged
LOGICAL :: ControllerConvergedFlag
! TRUE when air loop has been evaluated with latest actuated variables
LOGICAL :: IsUpToDateFlag
! Iteration counter
INTEGER :: Iter = 0
! Controller DO loop index
INTEGER :: AirLoopControlNum
! Number of times that the maximum iterations was exceeded
INTEGER, SAVE :: ErrCount = 0
! Number of times that the maximum iterations was exceeded
INTEGER, SAVE :: MaxErrCount = 0
! Placeholder for environment name used in error reporting
CHARACTER(LEN=MaxNameLength*2),SAVE :: ErrEnvironmentName=' '
! A character string equivalent of ErrCount
CHARACTER(LEN=20) :: CharErrOut
! FLOW:
! To track number of calls to SimAirLoopComponents() for each air loop
! Represents the most computationally expensive operation in the iteration.
! Best metric to use to assess the runtime performance of air loop simulation
NumCalls = 0
IterMax = 0
IterTot = 0
AirLoopConvergedFlag = .TRUE.
IsUpToDateFlag = .FALSE.
PrimaryAirSystem(AirLoopNum)%ControlConverged = .FALSE.
AllowWarmRestartFlag = .TRUE.
AirLoopControlInfo(AirLoopNum)%AllowWarmRestartFlag = .TRUE.
! When using controllers, size air loop coils so ControllerProps (e.g., Min/Max Actuated) can be set
IF(PrimaryAirSystem(AirLoopNum)%SizeAirloopCoil)THEN
IF(PrimaryAirSystem(AirLoopNum)%NumControllers>0) &
CALL SimAirLoopComponents( AirLoopNum, FirstHVACIteration )
PrimaryAirSystem(AirLoopNum)%SizeAirloopCoil = .FALSE.
END IF
! This call to ManageControllers reinitializes the controllers actuated variables to zero
! E.g., actuator inlet water flow
DO AirLoopControlNum = 1,PrimaryAirSystem(AirLoopNum)%NumControllers
CALL ManageControllers( &
PrimaryAirSystem(AirLoopNum)%ControllerName(AirLoopControlNum), &
PrimaryAirSystem(AirLoopNum)%ControllerIndex(AirLoopControlNum), &
FirstHVACIteration, AirLoopNum, AirLoopPass, &
iControllerOpColdStart, ControllerConvergedFlag, IsUpToDateFlag, AllowWarmRestartFlag )
! Detect whether the speculative warm restart feature is supported by each controller
! on this air loop.
AirLoopControlInfo(AirLoopNum)%AllowWarmRestartFlag = &
AirLoopControlInfo(AirLoopNum)%AllowWarmRestartFlag .AND. AllowWarmRestartFlag
END DO
! Evaluate air loop components with new actuated variables
NumCalls = NumCalls + 1
CALL SimAirLoopComponents( AirLoopNum, FirstHVACIteration )
IsUpToDateFlag = .TRUE.
! Loop over the air sys controllers until convergence or MaxIter iterations
DO AirLoopControlNum = 1,PrimaryAirSystem(AirLoopNum)%NumControllers
Iter = 0
ControllerConvergedFlag = .FALSE.
! if the controller can be locked out by the economizer operation and the economizer is active, leave the controller inactive
IF (AirLoopControlInfo(AirLoopNum)%EconoActive .and. &
PrimaryAirSystem(AirLoopNum)%CanBeLockedOutByEcono(AirLoopControlNum)) THEN
ControllerConvergedFlag = .TRUE.
CYCLE
END IF
! For each controller in sequence, iterate until convergence
DO WHILE (.NOT. ControllerConvergedFlag)
Iter = Iter + 1
CALL ManageControllers( &
PrimaryAirSystem(AirLoopNum)%ControllerName(AirLoopControlNum), &
PrimaryAirSystem(AirLoopNum)%ControllerIndex(AirLoopControlNum), &
FirstHVACIteration, AirLoopNum, AirLoopPass, &
iControllerOpIterate, ControllerConvergedFlag, IsUpToDateFlag )
PrimaryAirSystem(AirLoopNum)%ControlConverged(AirLoopControlNum) = ControllerConvergedFlag
IF ( .NOT.ControllerConvergedFlag ) THEN
! Only check abnormal termination if not yet converged
! The iteration counter has been exceeded.
IF (Iter > MaxIter) THEN
! Indicate that this air loop is not converged
AirLoopConvergedFlag = .FALSE.
! The warning message will be suppressed during the warm up days.
IF ( .NOT.WarmUpFlag ) THEN
ErrCount = ErrCount + 1
IF (ErrCount < 15) THEN
ErrEnvironmentName = EnvironmentName
WRITE(CharErrOut,*) MaxIter
CharErrOut=ADJUSTL(CharErrOut)
CALL ShowWarningError ( &
'SolveAirLoopControllers: Maximum iterations ('//TRIM(CharErrOut)//') exceeded for '// &
TRIM(PrimaryAirSystem(AirLoopNum)%Name)//', at '// &
TRIM(EnvironmentName)//', '//TRIM(CurMnDy)//' '// &
TRIM(CreateSysTimeIntervalString()) &
)
ELSE
IF (EnvironmentName /= ErrEnvironmentName) THEN
MaxErrCount = 0
ErrEnvironmentName = EnvironmentName
END IF
CALL ShowRecurringWarningErrorAtEnd( &
'SolveAirLoopControllers: Exceeding Maximum iterations for '// &
TRIM(PrimaryAirSystem(AirLoopNum)%Name)//' during '// &
TRIM(EnvironmentName)//' continues', MaxErrCount &
)
END IF
END IF
! It is necessary to execute this statement anytime, even if the warning message is suppressed.
! To continue the simulation it must be able to goto the Exit statement
EXIT ! It will not converge this time
END IF
! Re-evaluate air loop components with new actuated variables
NumCalls = NumCalls + 1
CALL SimAirLoopComponents( AirLoopNum, FirstHVACIteration )
IsUpToDateFlag = .TRUE.
END IF
END DO ! End of the Convergence Iteration
! Update tracker for max iteration counter across all controllers on this air loops
IterMax = MAX(IterMax, Iter)
! Update tracker for aggregated counter of air loop inner iterations across controllers
! on this air loop
IterTot = IterTot + Iter
END DO ! End of controller loop
! Once the controllers are converged then need to simulate the components once
! more to ensure that they are simulated with the latest values.
IF ( .NOT.IsUpToDateFlag .OR. .NOT.AirLoopConvergedFlag ) THEN
NumCalls = NumCalls + 1
CALL SimAirLoopComponents( AirLoopNum, FirstHVACIteration )
IsUpToDateFlag = .TRUE.
END IF
! Check that all active controllers are still convergence
DO AirLoopControlNum = 1,PrimaryAirSystem(AirLoopNum)%NumControllers
ControllerConvergedFlag = .FALSE.
CALL ManageControllers( &
PrimaryAirSystem(AirLoopNum)%ControllerName(AirLoopControlNum), &
PrimaryAirSystem(AirLoopNum)%ControllerIndex(AirLoopControlNum), &
FirstHVACIteration, AirLoopNum, AirLoopPass, &
iControllerOpEnd, ControllerConvergedFlag, IsUpToDateFlag )
PrimaryAirSystem(AirLoopNum)%ControlConverged(AirLoopControlNum) = ControllerConvergedFlag
AirLoopConvergedFlag = AirLoopConvergedFlag .AND. ControllerConvergedFlag
END DO
RETURN
END SUBROUTINE SolveAirLoopControllers