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) | :: | FluidCoolerNum |
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 UpdateFluidCooler(FluidCoolerNum)
! SUBROUTINE INFORMATION:
! AUTHOR: Chandan Sharma
! DATE WRITTEN: August 2008
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is for passing results to the outlet water node.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE DataEnvironment, ONLY: EnvironmentName, CurMnDy
! USE General, ONLY: TrimSigDigits
! USE FluidProperties, ONLY : GetDensityGlycol
! USE DataPlant, ONLY : PlantLoop
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: FluidCoolerNum
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: LowTempFmt="(' ',F6.2)"
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
CHARACTER(len=25) :: CharErrOut
CHARACTER(len=25) :: CharLowOutletTemp
INTEGER :: LoopNum
INTEGER :: LoopSideNum
REAL(r64) :: LoopMinTemp
! set node information
Node(WaterOutletNode)%Temp = OutletWaterTemp
LoopNum = SimpleFluidCooler(FluidCoolerNum)%LoopNum
LoopSideNum = SimpleFluidCooler(FluidCoolerNum)%LoopSideNum
IF(PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock.EQ.0 .OR. WarmupFlag)RETURN
!Check flow rate through fluid cooler and compare to design flow rate, show warning if greater than Design * Mulitplier
IF (Node(WaterOutletNode)%MassFlowRate .GT. SimpleFluidCooler(FluidCoolerNum)%DesWaterMassFlowRate * &
SimpleFluidCooler(FluidCoolerNum)%FluidCoolerMassFlowRateMultiplier) THEN
SimpleFluidCooler(FluidCoolerNum)%HighMassFlowErrorCount=SimpleFluidCooler(FluidCoolerNum)%HighMassFlowErrorCount+1
IF (SimpleFluidCooler(FluidCoolerNum)%HighMassFlowErrorCount < 2) THEN
CALL ShowWarningError (TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//'"')
CALL ShowContinueError (' Condenser Loop Mass Flow Rate is much greater than the fluid coolers design mass flow rate.')
CALL ShowContinueError (' Condenser Loop Mass Flow Rate = '//TrimSigDigits(Node(WaterOutletNode)%MassFlowRate,6))
CALL ShowContinueError (' Fluid Cooler Design Mass Flow Rate = '// &
TrimSigDigits(SimpleFluidCooler(FluidCoolerNum)%DesWaterMassFlowRate,6))
CALL ShowContinueErrorTimeStamp(' ')
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'" Condenser Loop Mass Flow Rate is much greater than the fluid coolers design mass flow rate error continues...' &
, SimpleFluidCooler(FluidCoolerNum)%HighMassFlowErrorIndex, Node(WaterOutletNode)%MassFlowRate, &
Node(WaterOutletNode)%MassFlowRate)
ENDIF
END IF
! Check if OutletWaterTemp is below the minimum condenser loop temp and warn user
LoopMinTemp = PlantLoop(LoopNum)%MinTemp
IF(OutletWaterTemp.LT.LoopMinTemp .AND. WaterMassFlowRate > 0.0d0) THEN
SimpleFluidCooler(FluidCoolerNum)%OutletWaterTempErrorCount = SimpleFluidCooler(FluidCoolerNum)%OutletWaterTempErrorCount &
+ 1
WRITE(CharLowOutletTemp,LowTempFmt) LoopMinTemp
WRITE(CharErrOut,LowTempFmt) OutletWaterTemp
CharErrOut=ADJUSTL(CharErrOut)
IF (SimpleFluidCooler(FluidCoolerNum)%OutletWaterTempErrorCount < 2) THEN
CALL ShowWarningError (TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//'"')
CALL ShowContinueError (' Fluid cooler water outlet temperature ('//TRIM(CharErrOut)//' C) is '// &
'below the specified minimum condenser loop temp of '//TRIM(ADJUSTL(CharLowOutletTemp))//' C')
CALL ShowContinueErrorTimeStamp(' ')
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'" Fluid cooler water outlet temperature is below the specified minimum condenser loop temp error continues...' &
, SimpleFluidCooler(FluidCoolerNum)%OutletWaterTempErrorIndex, OutletWaterTemp, OutletWaterTemp)
END IF
END IF
! Check if water mass flow rate is small (e.g. no flow) and warn user
IF(WaterMassFlowRate .GT. 0.0d0 .AND. WaterMassFlowRate .LE. MassFlowTolerance)THEN
SimpleFluidCooler(FluidCoolerNum)%SmallWaterMassFlowErrorCount = &
SimpleFluidCooler(FluidCoolerNum)%SmallWaterMassFlowErrorCount + 1
IF (SimpleFluidCooler(FluidCoolerNum)%SmallWaterMassFlowErrorCount < 2) THEN
CALL ShowWarningError (TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//'"')
CALL ShowContinueError (' Fluid cooler water mass flow rate near zero.')
CALL ShowContinueErrorTimeStamp(' ')
CALL ShowContinueError('Actual Mass flow = '//TRIM(TrimSigDigits(WaterMassFlowRate,2)))
ELSE
CALL ShowRecurringWarningErrorAtEnd(TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
'" Fluid cooler water mass flow rate near zero error continues...' &
, SimpleFluidCooler(FluidCoolerNum)%SmallWaterMassFlowErrorIndex, WaterMassFlowRate, WaterMassFlowRate)
ENDIF
END IF
! ! Check if water mass flow rate is lower than loop minimum and warn user
! IF(WaterMassFlowRate .LT. LoopMassFlowRateMinAvail)THEN
! SimpleFluidCooler(FluidCoolerNum)%WMFRLessThanMinAvailErrCount = &
! SimpleFluidCooler(FluidCoolerNum)%WMFRLessThanMinAvailErrCount + 1
! IF (SimpleFluidCooler(FluidCoolerNum)%WMFRLessThanMinAvailErrCount < 2) THEN
! CALL ShowWarningError (TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
! TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//'"')
! CALL ShowContinueError (' Fluid cooler water mass flow below loop minimum.')
! CALL ShowContinueErrorTimeStamp(' ')
! CALL ShowContinueError('Actual Mass flow = '//TRIM(TrimSigDigits(WaterMassFlowRate,2)))
! CALL ShowContinueError('Loop Minimum flow = '//TRIM(TrimSigDigits(LoopMassFlowRateMinAvail,2)))
! ELSE
! CALL ShowRecurringWarningErrorAtEnd(TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
! TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
! '" Fluid cooler water mass flow rate below loop minimum error continues...' &
! , SimpleFluidCooler(FluidCoolerNum)%WMFRLessThanMinAvailErrIndex, WaterMassFlowRate, WaterMassFlowRate)
! ENDIF
! END IF
!
! ! Check if water mass flow rate is greater than loop maximum and warn user
! IF(WaterMassFlowRate .GT. LoopMassFlowRateMaxAvail)THEN
! SimpleFluidCooler(FluidCoolerNum)%WMFRGreaterThanMaxAvailErrCount = &
! SimpleFluidCooler(FluidCoolerNum)%WMFRGreaterThanMaxAvailErrCount + 1
! IF (SimpleFluidCooler(FluidCoolerNum)%WMFRGreaterThanMaxAvailErrCount < 2) THEN
! CALL ShowWarningError (TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
! TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//'"')
! CALL ShowContinueError (' Fluid cooler water mass flow above loop maximum.')
! CALL ShowContinueErrorTimeStamp(' ')
! CALL ShowContinueError('Actual Mass flow = '//TRIM(TrimSigDigits(WaterMassFlowRate,2)))
! CALL ShowContinueError('Loop Maximum flow = '//TRIM(TrimSigDigits(LoopMassFlowRateMaxAvail,2)))
! ELSE
! CALL ShowRecurringWarningErrorAtEnd(TRIM(SimpleFluidCooler(FluidCoolerNum)%FluidCoolerType)//' "'// &
! TRIM(SimpleFluidCooler(FluidCoolerNum)%Name)//&
! '" Fluid cooler water mass flow rate above loop maximum error continues...' &
! , SimpleFluidCooler(FluidCoolerNum)%WMFRGreaterThanMaxAvailErrIndex, WaterMassFlowRate, WaterMassFlowRate)
! ENDIF
! END IF
RETURN
END SUBROUTINE UpdateFluidCooler