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) | :: | AirLoopNum | |||
integer, | intent(in) | :: | AirLoopPass | |||
integer, | intent(out) | :: | AirLoopIterMax | |||
integer, | intent(out) | :: | AirLoopIterTot | |||
integer, | intent(out) | :: | AirLoopNumCalls |
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 SimAirLoop(FirstHVACIteration, AirLoopNum, AirLoopPass, &
AirLoopIterMax, AirLoopIterTot, AirLoopNumCalls )
! SUBROUTINE INFORMATION
! AUTHOR: Dimitri Curtil (LBNL)
! DATE WRITTEN: March 2006
! - Fine-tuned outer loop over controllers.
! - Added convergence tracing for air loop controllers.
! - Added mechanism for speculative warm restart after first iteration.
! RE-ENGINEERED: This is new code based on the code that used to be part
! of SimAirLoops().
! PURPOSE OF THIS SUBROUTINE:
! This subroutine simulates the desired air loop by solving for all the
! controllers on the air loop in the order they are specified.
! METHODOLOGY EMPLOYED:
! To speed up the simulation, we introduced the possiblity to perform the controller
! simulation on each air loop using a warm restart from the solution obtained
! at the previous HVAC step iteration. This is only attempted if the air mass flow
! rate(s) for the air system have not changed since the last iteration.
! Of course if the warm restart fails, then we perform a normal simulation from
! a cold start. We refer to this scheme as speculative warm restart.
!
! REFERENCES: None
! USE STATEMENTS:
USE DataHVACControllers
USE DataSystemVariables
USE HVACControllers, ONLY : TrackAirLoopControllers, TraceAirLoopControllers
USE General, ONLY : CreateSysTimeIntervalString
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
! TRUE if first full HVAC iteration in an HVAC timestep
LOGICAL, INTENT(IN) :: FirstHVACIteration
! Index of the air loop to simulate
INTEGER, INTENT(IN) :: AirLoopNum
! There are 2 passes - the 2nd is done only if mass balance fails
INTEGER, INTENT(IN) :: AirLoopPass
! Max number of iterations performed by controllers across this air loop
INTEGER, INTENT(OUT) :: AirLoopIterMax
! Aggregated number of iterations across all controllers on this air loop
INTEGER, INTENT(OUT) :: AirLoopIterTot
! Total number of times SimAirLoopComponents() has been invoked to simulate this air loop
INTEGER, INTENT(OUT) :: AirLoopNumCalls
! SUBROUTINE PARAMETER DEFINITIONS: None
! INTERFACE BLOCK DEFINITIONS: None
! DERIVED TYPE DEFINITIONS: None
! SUBROUTINE LOCAL VARIABLE DEFINITIONS
! Maximum number of iterations performed by each controller on this air loop
INTEGER :: IterMax = 0
! Aggregated number of iterations performed by each controller on this air loop
INTEGER :: IterTot = 0
! Number of times SimAirLoopComponents() has been invoked per air loop for either Solve or ReSolve operations
INTEGER :: NumCalls = 0
! TRUE when primary air system & controllers simulation has converged;
LOGICAL :: AirLoopConvergedFlag = .FALSE.
! TRUE when speculative warm restart is allowed; FALSE otherwise.
LOGICAL :: DoWarmRestartFlag = .FALSE.
! If Status<0, no speculative warm restart attempted.
! If Status==0, warm restart failed.
! If Status>0, warm restart succeeded.
INTEGER :: WarmRestartStatus = iControllerWarmRestartNone
! FLOW:
! Reset air loop trackers to zero
AirLoopIterMax = 0
AirLoopIterTot = 0
AirLoopNumCalls = 0
! Perform air loop simulation to satisfy convergence for all controllers
! If first HVAC iteration or new air flow we force a cold restart.
! Otherwise we attempt a speculative warm restart.
!
! TODO: Improve detection of when air flow rate has changed since last air loop simulation
! TODO: Detect whether warm restart is supported on air loop on very first air loop
! simulation only instead of at each HVAC iteration as done now.
DoWarmRestartFlag = &
! Only enabled if there are controllers on the air loop
PrimaryAirSystem(AirLoopNum)%NumControllers > 0 .AND. &
! Check that the speculative warm restart feature is allowed
AirLoopControlInfo(AirLoopNum)%AllowWarmRestartFlag .AND. &
! Never done at first HVAC iteration
.NOT. FirstHVACIteration .AND. &
! Never done during sizing
.NOT. SysSizingCalc .AND. &
! Next condition is true whenever the final check for the air loop was converged
! at the previous SimAirLoop call
AirLoopControlInfo(AirLoopNum)%ConvergedFlag .AND. &
! Next conditions should detect when air mass flow rates have changed
.NOT. AirLoopControlInfo(AirLoopNum)%LoopFlowRateSet .AND. &
.NOT. AirLoopControlInfo(AirLoopNum)%NewFlowRateFlag
IF ( .NOT.DoWarmRestartFlag ) THEN
! Solve controllers with cold start using default initial values
CALL SolveAirLoopControllers( &
FirstHVACIteration, AirLoopPass, AirLoopNum, AirLoopConvergedFlag, &
IterMax, IterTot, NumCalls )
! Update air loop trackers
WarmRestartStatus = iControllerWarmRestartNone
AirLoopNumCalls = AirLoopNumCalls + NumCalls
AirLoopIterMax = MAX(AirLoopIterMax, IterMax)
AirLoopIterTot = AirLoopIterTot + IterTot
ELSE
! First try with speculative warm restart using previous solution
CALL ReSolveAirLoopControllers( &
FirstHVACIteration, AirLoopPass, AirLoopNum, AirLoopConvergedFlag, &
IterMax, IterTot, NumCalls )
! Update air loop trackers
WarmRestartStatus = iControllerWarmRestartSuccess
AirLoopNumCalls = AirLoopNumCalls + NumCalls
AirLoopIterMax = MAX(AirLoopIterMax, IterMax)
AirLoopIterTot = AirLoopIterTot + IterTot
! Retry with cold start using default initial values if speculative warm restart did not work
IF ( .NOT.AirLoopConvergedFlag ) THEN
CALL SolveAirLoopControllers( &
FirstHVACIteration, AirLoopPass, AirLoopNum, AirLoopConvergedFlag, &
IterMax, IterTot, NumCalls )
! Update air loop trackers
WarmRestartStatus = iControllerWarmRestartFail
AirLoopNumCalls = AirLoopNumCalls + NumCalls
AirLoopIterMax = MAX(AirLoopIterMax, IterMax)
AirLoopIterTot = AirLoopIterTot + IterTot
END IF
END IF
! Updates air loop statistics
!
! To enable runtime statistics tracking for each air loop, define the environment variable
! TRACK_AIRLOOP=YES or TRACK_AIRLOOP=Y
IF ( TrackAirLoopEnvFlag ) THEN
CALL TrackAirLoopControllers( &
AirLoopNum, &
WarmRestartStatus, &
AirLoopIterMax, &
AirLoopIterTot, &
AirLoopNumCalls &
)
END IF
! Generate trace for all controllers on this air loop
!
! To enable generating a trace file with the converged solution for all controllers on each air loop,
! define the environment variable TRACE_AIRLOOP=YES or TRACE_AIRLOOP=Y.
IF ( TraceAirLoopEnvFlag ) THEN
CALL TraceAirLoopControllers( &
FirstHVACIteration, &
AirLoopNum, AirLoopPass, AirLoopConvergedFlag, &
AirLoopNumCalls &
)
END IF
! When there is more than 1 controller on an air loop, each controller sensing
! different nodes with potentially different setpoints, it is likely that
! AirLoopConvergedFlag will be false as the individual setpoints will not
! be satisfied once all the controllers have been simulated. Typically, this could
! happen if
! If this is the case then we do not want to try a warm restart as it is very
! unlikely to succeed.
AirLoopControlInfo(AirLoopNum)%ConvergedFlag = AirLoopConvergedFlag
RETURN
END SUBROUTINE SimAirLoop