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, | intent(in) | :: | FileUnit | |||
type(DefinePrimaryAirSystem), | intent(in) | :: | ThisPrimaryAirSystem | |||
type(AirLoopStatsType), | intent(in) | :: | ThisAirLoopStats |
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 WriteAirLoopStatistics( FileUnit, ThisPrimaryAirSystem, ThisAirLoopStats )
! SUBROUTINE INFORMATION:
! AUTHOR Dimitri Curtil
! DATE WRITTEN April 2006
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Writes runtime statistics for controllers on the specified air loop
! to the specified file.
! METHODOLOGY EMPLOYED:
! Needs description, as appropriate.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataAirSystems
USE General, ONLY: TrimSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, INTENT(IN) :: FileUnit
TYPE(DefinePrimaryAirSystem), INTENT(IN) :: ThisPrimaryAirSystem
TYPE(AirLoopStatsType), INTENT(IN) :: ThisAirLoopStats
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: AirLoopControlNum
INTEGER :: NumWarmRestarts
REAL(r64) :: WarmRestartSuccessRatio
INTEGER :: NumCalls
INTEGER :: TotIterations
INTEGER :: MaxIterations
REAL(r64) :: AvgIterations
INTEGER :: iModeNum
! FLOW
WRITE(FileUnit,'(A,A)') TRIM(ThisPrimaryAirSystem%Name), ','
! Number of calls to SimAirLoop() has been invoked over the course of the simulation
! to simulate the specified air loop
WRITE(FileUnit,'(A,A,A)') 'NumCalls', ',', TRIM(TrimSigDigits(ThisAirLoopStats%NumCalls))
! Warm restart success ratio
NumWarmRestarts = ThisAirLoopStats%NumSuccessfulWarmRestarts + ThisAirLoopStats%NumFailedWarmRestarts
IF ( NumWarmRestarts == 0 ) THEN
WarmRestartSuccessRatio = 0.0d0
ELSE
WarmRestartSuccessRatio = REAL(ThisAirLoopStats%NumSuccessfulWarmRestarts,r64) / REAL(NumWarmRestarts,r64)
END IF
WRITE(FileUnit,'(A,A,A)') 'NumWarmRestarts', ',', TRIM(TrimSigDigits(NumWarmRestarts))
WRITE(FileUnit,'(A,A,A)') 'NumSuccessfulWarmRestarts', ',', TRIM(TrimSigDigits(ThisAirLoopStats%NumSuccessfulWarmRestarts))
WRITE(FileUnit,'(A,A,A)') 'NumFailedWarmRestarts', ',', TRIM(TrimSigDigits(ThisAirLoopStats%NumFailedWarmRestarts))
WRITE(FileUnit,'(A,A,A)') 'WarmRestartSuccessRatio', ',', TRIM(TrimSigDigits(WarmRestartSuccessRatio,10))
! Total number of times SimAirLoopComponents() has been invoked over the course of the simulation
! to simulate the specified air loop
WRITE(FileUnit,'(A,A,A)') 'TotSimAirLoopComponents', ',', TRIM(TrimSigDigits(ThisAirLoopStats%TotSimAirLoopComponents))
! Maximum number of times SimAirLoopComponents() has been invoked over the course of the simulation
! to simulate the specified air loop
WRITE(FileUnit,'(A,A,A)') 'MaxSimAirLoopComponents', ',', TRIM(TrimSigDigits(ThisAirLoopStats%MaxSimAirLoopComponents))
! Aggregated number of iterations needed by all controllers to simulate the specified air loop
WRITE(FileUnit,'(A,A,A)') 'TotIterations', ',', TRIM(TrimSigDigits(ThisAirLoopStats%TotIterations))
! Maximum number of iterations needed by controllers to simulate the specified air loop
WRITE(FileUnit,'(A,A,A)') 'MaxIterations', ',', TRIM(TrimSigDigits(ThisAirLoopStats%MaxIterations))
! Average number of iterations needed by controllers to simulate the specified air loop
IF ( ThisAirLoopStats%NumCalls == 0 ) THEN
AvgIterations = 0.0d0
ELSE
AvgIterations = REAL(ThisAirLoopStats%TotIterations,r64)/REAL(ThisAirLoopStats%NumCalls,r64)
END IF
WRITE(FileUnit,'(A,A,A)') 'AvgIterations', ',', TRIM(TrimSigDigits(AvgIterations,10))
! Dump statistics for each controller on this air loop
DO AirLoopControlNum=1,ThisPrimaryAirSystem%NumControllers
WRITE(FileUnit,'(A,A)') TRIM(ThisPrimaryAirSystem%ControllerName(AirLoopControlNum)), ','
! Aggregate iteration trackers across all operating modes
NumCalls = 0
TotIterations = 0
MaxIterations = 0
DO iModeNum=iFirstMode,iLastMode
NumCalls = NumCalls + ThisAirLoopStats%ControllerStats(AirLoopControlNum)%NumCalls(iModeNum)
TotIterations = TotIterations + ThisAirLoopStats%ControllerStats(AirLoopControlNum)%TotIterations(iModeNum)
MaxIterations = MAX( &
MaxIterations, &
ThisAirLoopStats%ControllerStats(AirLoopControlNum)%MaxIterations(iModeNum) &
)
END DO
! Number of times this controller was simulated (should match air loop num calls)
WRITE(FileUnit,'(A,A,A)') 'NumCalls', ',', TRIM(TrimSigDigits(NumCalls))
! Aggregated number of iterations needed by this controller
WRITE(FileUnit,'(A,A,A)') 'TotIterations', ',', TRIM(TrimSigDigits(TotIterations))
! Aggregated number of iterations needed by this controller
WRITE(FileUnit,'(A,A,A)') 'MaxIterations', ',', TRIM(TrimSigDigits(MaxIterations))
! Average number of iterations needed by controllers to simulate the specified air loop
IF ( NumCalls == 0 ) THEN
AvgIterations = 0.0d0
ELSE
AvgIterations = REAL(TotIterations,r64) / REAL(NumCalls,r64)
END IF
WRITE(FileUnit,'(A,A,A)') 'AvgIterations', ',', TRIM(TrimSigDigits(AvgIterations,10))
! Dump iteration trackers for each operating mode
DO iModeNum=iFirstMode,iLastMode
WRITE(FileUnit,'(A,A)') ControllerModeTypes(iModeNum), ','
! Number of times this controller operated in this mode
WRITE(FileUnit,'(A,A,A)') 'NumCalls', ',', &
TRIM(TrimSigDigits(ThisAirLoopStats%ControllerStats(AirLoopControlNum)%NumCalls(iModeNum)))
! Aggregated number of iterations needed by this controller
WRITE(FileUnit,'(A,A,A)') 'TotIterations', ',', &
TRIM(TrimSigDigits(ThisAirLoopStats%ControllerStats(AirLoopControlNum)%TotIterations(iModeNum)))
! Aggregated number of iterations needed by this controller
WRITE(FileUnit,'(A,A,A)') 'MaxIterations', ',', &
TRIM(TrimSigDigits(ThisAirLoopStats%ControllerStats(AirLoopControlNum)%MaxIterations(iModeNum)))
! Average number of iterations needed by controllers to simulate the specified air loop
IF ( ThisAirLoopStats%ControllerStats(AirLoopControlNum)%NumCalls(iModeNum) == 0 ) THEN
AvgIterations = 0.0d0
ELSE
AvgIterations = &
REAL(ThisAirLoopStats%ControllerStats(AirLoopControlNum)%TotIterations(iModeNum),r64) / &
REAL(ThisAirLoopStats%ControllerStats(AirLoopControlNum)%NumCalls(iModeNum),r64)
END IF
WRITE(FileUnit,'(A,A,A)') 'AvgIterations', ',', TRIM(TrimSigDigits(AvgIterations,10))
END DO
END DO
RETURN
END SUBROUTINE WriteAirLoopStatistics