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(inout) | :: | ResimExt | |||
logical, | intent(inout) | :: | ResimHB | |||
logical, | intent(inout) | :: | ResimHVAC |
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 Resimulate(ResimExt, ResimHB, ResimHVAC)
! SUBROUTINE INFORMATION:
! AUTHOR Peter Graham Ellis
! DATE WRITTEN August 2005
! MODIFIED Sep 2011 LKL/BG - resimulate only zones needing it for Radiant systems
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is called as necessary by the Demand Manager to resimulate some of the modules that have
! already been simulated for the current timestep. For example, if LIGHTS are demand limited, the lighting
! power is reduced which also impacts the zone internal heat gains and therefore requires that the entire
! zone heat balance must be resimulated.
! METHODOLOGY EMPLOYED:
! If the zone heat balance must be resimulated, all the major subroutines are called sequentially in order
! to recalculate the impacts of demand limiting. This routine is called from ManageHVAC _before_ any variables
! are reported or histories are updated. This routine can be called multiple times without the overall
! simulation moving forward in time.
!
! If only HVAC components are demand limited, then the HVAC system is resimulated, not the entire heat balance.
! Similarly, if ony exterior lights and equipment are demand limited, it is only necessary to resimulate the
! exterior energy use, not the entire heat balance, nor the HVAC system.
!
! Below is the hierarchy of subroutine calls. The calls marked with an asterisk are resimulated here.
!
! ManageSimulation
! ManageWeather
! ManageDemand
! * ManageExteriorEnergyUse
! ManageHeatBalance
! * InitHeatBalance
! PerformSolarCalculations
! ManageSurfaceHeatBalance
! * InitSurfaceHeatBalance
! ManageInternalHeatGains
! * CalcHeatBalanceOutsideSurf
! * CalcHeatBalanceInsideSurf
! ManageAirHeatBalance
! *InitAirHeatBalance
! CalcHeatBalanceAir
! * CalcAirFlow
! * ManageRefrigeratedCaseRacks
! ManageHVAC
! * ManageZoneAirUpdates 'GET ZONE SETPOINTS'
! * ManageZoneAirUpdates 'PREDICT'
! * SimHVAC
! UpdateDataandReport
! ReportAirHeatBalance
! UpdateFinalSurfaceHeatBalance
! UpdateThermalHistories
! UpdateMoistureHistories
! ManageThermalComfort
! ReportSurfaceHeatBalance
! RecKeepHeatBalance
! ReportHeatBalance
! USE STATEMENTS:
USE DataPrecisionGlobals
USE DemandManager, ONLY: DemandManagerExtIterations, DemandManagerHBIterations, DemandManagerHVACIterations
USE ExteriorEnergyUse, ONLY: ManageExteriorEnergyUse
USE HeatBalanceSurfaceManager, ONLY: InitSurfaceHeatBalance
USE HeatBalanceAirManager, ONLY: InitAirHeatBalance
USE RefrigeratedCase, ONLY: ManageRefrigeratedCaseRacks
USE ZoneTempPredictorCorrector, ONLY: ManageZoneAirUpdates
USE DataHeatBalFanSys, ONLY: iGetZoneSetpoints, iPredictStep, iCorrectStep
USE HVACManager, ONLY: SimHVAC, CalcAirFlowSimple
USE DataInterfaces, ONLY: ShowSevereError, ShowContinueErrorTimeStamp, &
CalcHeatBalanceOutsideSurf, CalcHeatBalanceInsideSurf
USE DataHVACGlobals, ONLY: UseZoneTimeStepHistory !, InitDSwithZoneHistory
USE ZoneContaminantPredictorCorrector, ONLY: ManageZoneContaminanUpdates
USE DataContaminantBalance, ONLY: Contaminant
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ResimExt ! Flag to resimulate the exterior energy use simulation
LOGICAL, INTENT(INOUT) :: ResimHB ! Flag to resimulate the heat balance simulation (including HVAC)
LOGICAL, INTENT(INOUT) :: ResimHVAC ! Flag to resimulate the HVAC simulation
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: ZoneTempChange ! Dummy variable needed for calling ManageZoneAirUpdates
! FLOW:
IF (ResimExt) THEN
CALL ManageExteriorEnergyUse
DemandManagerExtIterations = DemandManagerExtIterations + 1
END IF
IF (ResimHB) THEN
! Surface simulation
CALL InitSurfaceHeatBalance
CALL CalcHeatBalanceOutsideSurf
CALL CalcHeatBalanceInsideSurf
! Air simulation
CALL InitAirHeatBalance
CALL ManageRefrigeratedCaseRacks
DemandManagerHBIterations = DemandManagerHBIterations + 1
ResimHVAC = .TRUE. ! Make sure HVAC is resimulated too
END IF
IF (ResimHVAC) THEN
! HVAC simulation
CALL ManageZoneAirUpdates(iGetZoneSetpoints,ZoneTempChange,.FALSE., UseZoneTimeStepHistory, &
0.0D0 )
If (Contaminant%SimulateContaminants) &
CALL ManageZoneContaminanUpdates(iGetZoneSetpoints,.FALSE.,UseZoneTimeStepHistory,0.0D0)
CALL CalcAirFlowSimple
CALL ManageZoneAirUpdates(iPredictStep,ZoneTempChange,.FALSE., UseZoneTimeStepHistory, &
0.0D0 )
If (Contaminant%SimulateContaminants) &
CALL ManageZoneContaminanUpdates(iPredictStep,.FALSE.,UseZoneTimeStepHistory,0.0D0 )
CALL SimHVAC
DemandManagerHVACIterations = DemandManagerHVACIterations + 1
END IF
RETURN
END SUBROUTINE Resimulate