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 | |||
logical, | intent(inout) | :: | SimZoneEquipment |
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 SimAirLoops(FirstHVACIteration,SimZoneEquipment)
! SUBROUTINE INFORMATION
! AUTHOR: Russ Taylor, Dan Fisher, Fred Buhl
! DATE WRITTEN: Oct 1997
! MODIFIED: Dec 1997 Fred Buhl
! MODIFIED: Apr 1998 Richard Liesen
! MODIFIED: Dec 1999 Fred Buhl
! MODIFIED: Feb 2006 Dimitri Curtil (LBNL)
! - Moved air loop simulation to SimAirLoop() routine.
! RE-ENGINEERED: This is new code, not reengineered
! PURPOSE OF THIS SUBROUTINE:
! This is the driver subroutine for the air loop simulation. It simulates
! each primary air system in the problem and passes the outlet node conditions
! on to the attached Zone Equipment inlet nodes.
! METHODOLOGY EMPLOYED:
! For each 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.
! (4) A mass balance check is performed; if it fails, mass balance is imposed
! and steps 1, 2, and 3 are repeated. At the end we should have a correct,
! self consistent primary air system simulation.
!
! REFERENCES: None
! USE STATEMENTS:
USE HVACInterfaceManager, ONLY : UpdateHVACInterface
USE MixedAir, ONLY : SimOAController
USE DataGlobals, ONLY : BeginTimeStepFlag
USE General, ONLY : GetPreviousHVACTime
USE DataConvergParams, ONLY : CalledFromAirSystemSupplySideDeck1, CalledFromAirSystemSupplySideDeck2
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
! TRUE if first full HVAC iteration in an HVAC timestep
LOGICAL, INTENT(IN) :: FirstHVACIteration
! TRUE if Zone Equipment needs to be resimulated.
LOGICAL, INTENT(INOUT) :: SimZoneEquipment
! SUBROUTINE PARAMETER DEFINITIONS: None
! INTERFACE BLOCK DEFINITIONS: None
! DERIVED TYPE DEFINITIONS: None
! SUBROUTINE LOCAL VARIABLE DEFINITIONS
! Last saved HVAC time stamp at beginning of step in seconds.
! Used to control when to reset the statistic counters for each new HVAC step.
REAL(r64), SAVE :: SavedPreviousHVACTime = 0.0d0
REAL(r64) :: rxTime
! Maximum of iteration counters across all air loops
INTEGER, SAVE :: IterMax = 0
! Aggregated number of iterations across all air loops
INTEGER, SAVE :: IterTot = 0
! Aggregated number fo times SimAirLoopComponents() has been invoked across all air loops
INTEGER, SAVE :: NumCallsTot = 0
! Primary Air Sys DO loop index
INTEGER :: AirLoopNum
! Max number of iterations performed by controllers on each air loop
INTEGER :: AirLoopIterMax
! Aggregated number of iterations across all controllers on each air loop
INTEGER :: AirLoopIterTot
! Total number of times SimAirLoopComponents() has been invoked to simulate each air loop
INTEGER :: AirLoopNumCalls
! Primary air system outlet DO loop index
INTEGER :: AirSysOutNum
! DO loop index; there are 2 passes - the 2nd is done only if mass balance fails
INTEGER :: AirLoopPass
! Output variable setup flag
LOGICAL, SAVE :: OutputSetupFlag = .FALSE.
! Flag set by ResolveSysFlow; if TRUE, mass balance failed and there must be a second pass
LOGICAL :: SysReSim
INTEGER :: CalledFrom
! FLOW:
! Set up output variables
IF (.NOT. OutputSetupFlag) THEN
CALL SetupOutputVariable('Air System Simulation Maximum Iteration Count []', IterMax, 'HVAC', 'Sum', 'SimAir')
CALL SetupOutputVariable('Air System Simulation Iteration Count []', IterTot, 'HVAC', 'Sum', 'SimAir')
CALL SetupOutputVariable('Air System Component Model Simulation Calls []', NumCallsTot, 'HVAC', 'Sum', 'SimAir')
OutputSetupFlag = .TRUE.
END IF
! BUG: IterMax should not be aggregated as a Sum output variable
! We need a new aggregation scheme to track the max value across HVAC steps
! instead of suming it up.
IterMax = 0
! Reset counters to capture statistics for the current zone time step
!
! Aggregate statistics over all HVAC time steps, even the rejected ones, to properly
! reflect the numerical work. The condition to detect a new HVAC time step is essentially
! based on the time stamp at the beginning of the current HVAC step (expressed in seconds).
IF ( FirstHVACIteration) THEN
rxTime=GetPreviousHVACTime()
IF (SavedPreviousHVACTime /= rxTime) THEN
SavedPreviousHVACTime = rxTime
IterTot = 0
NumCallsTot = 0
END IF
END IF
! Loop over all the primary air loop; simulate their components (equipment)
! and controllers
DO AirLoopNum = 1, NumPrimaryAirSys ! NumPrimaryAirSys is the number of primary air loops
! Check to see if System Availability Managers are asking for fans to cycle on or shut off
! and set fan on/off flags accordingly.
TurnFansOn = .FALSE.
TurnFansOff = .FALSE.
NightVentOn = .FALSE.
IF (PriAirSysAvailMgr(AirLoopNum)%AvailStatus .EQ. CycleOn) THEN
TurnFansOn = .TRUE.
END IF
IF (PriAirSysAvailMgr(AirLoopNum)%AvailStatus .EQ. ForceOff) THEN
TurnFansOff = .TRUE.
END IF
IF (AirLoopControlInfo(AirLoopNum)%NightVent) THEN
NightVentOn = .TRUE.
END IF
! Set current system number for sizing routines
CurSysNum = AirLoopNum
! RR why is this called here, it's called first in SimAirLoop. Causes no diff's to comment out.
! IF (AirLoopControlInfo(AirLoopNum)%OACtrlNum > 0) THEN
! CALL SimOAController( &
! AirLoopControlInfo(AirLoopNum)%OACtrlName, &
! AirLoopControlInfo(AirLoopNum)%OACtrlNum, &
! FirstHVACIteration, &
! AirLoopNum )
! END IF
! 2 passes; 1 usually suffices; 2 is done if ResolveSysFlow detects a failure of mass balance
SimPasses : DO AirLoopPass=1,2
SysReSim = .FALSE.
! Simulate controllers on air loop with current air mass flow rates
CALL SimAirLoop( &
FirstHVACIteration, AirLoopNum, AirLoopPass, &
AirLoopIterMax, AirLoopIterTot, AirLoopNumCalls &
)
! Update tracker for maximum number of iterations needed by any controller on all air loops
IterMax = MAX(IterMax, AirLoopIterMax)
! Update tracker for aggregated number of iterations needed by all controllers on all air loops
IterTot = IterTot + AirLoopIterTot
! Update tracker for total number of times SimAirLoopComponents() has been invoked across all air loops
NumCallsTot = NumCallsTot + AirLoopNumCalls
! At the end of the first pass, check whether a second pass is needed or not
IF (AirLoopPass.EQ.1) THEN
! If simple system, skip second pass
IF (AirLoopControlInfo(AirLoopNum)%Simple) EXIT SimPasses
CALL ResolveSysFlow(AirLoopNum, SysReSim)
! If mass balance OK, skip second pass
IF (.NOT.SysReSim) EXIT SimPasses
END IF
END DO SimPasses ! end pass loop
! Air system side has been simulated, now transfer conditions across to
! the zone equipment side, looping through all supply air paths for this
! air loop.
DO AirSysOutNum = 1, AirToZoneNodeInfo(AirLoopNum)%NumSupplyNodes
IF (AirSysOutNum == 1) CalledFrom = CalledFromAirSystemSupplySideDeck1
IF (AirSysOutNum == 2) CalledFrom = CalledFromAirSystemSupplySideDeck2
CALL UpdateHVACInterface( AirLoopNum, CalledFrom, &
AirToZoneNodeInfo(AirLoopNum)%AirLoopSupplyNodeNum(AirSysOutNum), &
AirToZoneNodeInfo(AirLoopNum)%ZoneEquipSupplyNodeNum(AirSysOutNum), &
SimZoneEquipment )
END DO ! ...end of DO loop over supply air paths for this air loop.
END DO ! End of Air Loop iteration
! Reset current system number for sizing routines
CurSysNum = 0
RETURN
END SUBROUTINE SimAirLoops