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 | ||
---|---|---|---|---|---|---|
character(len=*) | :: | FluidCoolerType | ||||
character(len=*) | :: | FluidCoolerName | ||||
integer | :: | CompIndex | ||||
logical | :: | RunFlag | ||||
logical, | intent(in) | :: | InitLoopEquip | |||
real(kind=r64) | :: | MaxCap | ||||
real(kind=r64) | :: | MinCap | ||||
real(kind=r64) | :: | OptCap |
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 SimFluidCoolers(FluidCoolerType,FluidCoolerName, CompIndex, RunFlag,InitLoopEquip, &
MaxCap,MinCap,OptCap)
! SUBROUTINE INFORMATION:
! AUTHOR Chandan Sharma
! DATE WRITTEN August 2008
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Main fluid cooler driver subroutine. Gets called from PlantCondLoopSupplySideManager
! METHODOLOGY EMPLOYED:
! After being called by PlantCondLoopSupplySideManager, this subroutine
! calls GetFluidCoolerInput to get all fluid cooler input info (one time only),
! then calls the appropriate subroutine to calculate fluid cooler performance,
! update records (node info) and writes output report info.
! REFERENCES:
! Based on SimTowers subroutine by Fred Buhl, May 2002; Richard Raustad, FSEC, Feb 2005
! USE STATEMENTS:
USE InputProcessor, ONLY: FindItemInList
USE DataPlant, ONLY: PlantSizesOkayToFinalize
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=*) :: FluidCoolerType
CHARACTER(len=*) :: FluidCoolerName
INTEGER :: CompIndex
LOGICAL :: RunFlag
LOGICAL, INTENT(IN) :: InitLoopEquip
REAL(r64) :: OptCap
REAL(r64) :: MaxCap
REAL(r64) :: MinCap
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
LOGICAL, SAVE :: GetInput = .TRUE.
INTEGER :: FluidCoolerNum
!GET INPUT
IF (GetInput) THEN
CALL GetFluidCoolerInput
GetInput = .FALSE.
END IF
!INITIALIZE
! Find the correct Equipment
IF (CompIndex == 0) THEN
FluidCoolerNum = FindItemInList(FluidCoolerName,SimpleFluidCooler%Name,NumSimpleFluidCoolers)
IF (FluidCoolerNum == 0) THEN
CALL ShowFatalError('SimFluidCoolers: Unit not found = '//TRIM(FluidCoolerName))
ENDIF
CompIndex=FluidCoolerNum
ELSE
FluidCoolerNum=CompIndex
IF (FluidCoolerNum > NumSimpleFluidCoolers .or. FluidCoolerNum < 1) THEN
CALL ShowFatalError('SimFluidCoolers: Invalid CompIndex passed = '// &
TRIM(TrimSigDigits(FluidCoolerNum))// &
', Number of Units = '//TRIM(TrimSigDigits(NumSimpleFluidCoolers))// &
', Entered Unit name = '//TRIM(FluidCoolerName))
ENDIF
IF (CheckEquipName(FluidCoolerNum)) THEN
IF (FluidCoolerName /= SimpleFluidCooler(FluidCoolerNum)%Name) THEN
CALL ShowFatalError('SimFluidCoolers: Invalid CompIndex passed = '// &
TRIM(TrimSigDigits(FluidCoolerNum))// &
', Unit name = '//TRIM(FluidCoolerName)//', stored Unit Name for that index = '// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name))
ENDIF
CheckEquipName(FluidCoolerNum)=.false.
ENDIF
ENDIF
CALL InitSimVars
!CALCULATE
TypeOfEquip: &
SELECT CASE (SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType_Num)
CASE (FluidCooler_SingleSpeed)
IF (InitLoopEquip) THEN
CALL InitFluidCooler(FluidCoolerNum, RunFlag)
IF (.NOT. PlantSizesOkayToFinalize) CALL SizeFluidCooler(FluidCoolerNum)
MinCap = 0.0d0
MaxCap = SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity
OptCap = SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity
RETURN
END IF
CALL InitFluidCooler(FluidCoolerNum, RunFlag)
CALL SingleSpeedFluidCooler(FluidCoolerNum)
CALL UpdateFluidCooler(FluidCoolerNum)
CALL ReportFluidCooler(RunFlag,FluidCoolerNum)
CASE (FluidCooler_TwoSpeed)
IF (InitLoopEquip) THEN
CALL InitFluidCooler(FluidCoolerNum, RunFlag)
IF (.NOT. PlantSizesOkayToFinalize) CALL SizeFluidCooler(FluidCoolerNum)
MinCap = 0.0d0 ! signifies non-load based model (i.e. forward
MaxCap = SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity
OptCap = SimpleFluidCooler(FluidCoolerNum)%FluidCoolerNominalCapacity
RETURN
END IF
CALL InitFluidCooler(FluidCoolerNum, RunFlag)
CALL TwoSpeedFluidCooler(FluidCoolerNum)
CALL UpdateFluidCooler(FluidCoolerNum)
CALL ReportFluidCooler(RunFlag,FluidCoolerNum)
CASE DEFAULT
CALL ShowFatalError('SimFluidCoolers: Invalid Fluid Cooler Type Requested = '//TRIM(FluidCoolerType))
END SELECT TypeOfEquip
RETURN
END SUBROUTINE SimFluidCoolers