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) | :: | CompNum | |||
real(kind=r64), | intent(in) | :: | SupSideMdot | |||
real(kind=r64), | intent(in) | :: | DmdSideMdot |
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 CalcFluidHeatExchanger(CompNum, SupSideMdot, DmdSideMdot)
! SUBROUTINE INFORMATION:
! AUTHOR B.Griffith, derived from CalcEconHeatExchanger by Sankaranarayanan K P aug. 2007
! DATE WRITTEN November 2012
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Evalutate heat exchanger model and calculate leaving temperatures
! METHODOLOGY EMPLOYED:
! apply heat transfer model depending on type of HX used
! REFERENCES:
! na
! USE STATEMENTS:
USE FluidProperties, ONLY: GetSpecificHeatGlycol
USE DataLoopNode, ONLY: Node
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: CompNum
REAL(r64), INTENT(IN) :: SupSideMdot ! mass flow rate of fluid entering from supply side loop
REAL(r64), INTENT(IN) :: DmdSideMdot ! mass flow rate of fluid entering from demand side loop
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: CmaxMixedCminUnmixed = 40
INTEGER, PARAMETER :: CmaxUnMixedCminMixed = 41
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: SupSideLoopInletTemp
REAL(r64) :: DmdSideLoopInletTemp
REAL(r64) :: SupSideLoopInletCp ! specific heat of fluid entering from supply side loop at inlet temp
REAL(r64) :: DmdSideLoopInletCp ! specific heat of fluid entering from demand side loop at inlet temp
REAL(r64) :: SupSideCapRate ! product of specific heat and mass flow for supply side loop at inlet temp
REAL(r64) :: DmdSideCapRate ! product of specific heat and mass flow for demand side loop at inlet temp
REAL(r64) :: MinCapRate ! minimum capacity flow rate
REAL(r64) :: MaxCapRate ! maximum capacity flow rate
REAL(r64) :: NTU ! number of transfer units for heat exchanger performance model
REAL(r64) :: CapRatio
REAL(r64) :: ExpCheckValue1
REAL(r64) :: ExpCheckValue2
REAL(r64) :: Effectiveness
REAL(r64) :: HeatTransferRate
REAL(r64) :: MdotDmdSide
REAL(r64) :: LeavingTempMinFlow
REAL(r64) :: LeavingTempFullFlow
INTEGER :: CrossFlowEquation
SupSideLoopInletTemp = Node(FluidHX(CompNum)%SupplySideLoop%InletNodeNum)%Temp
DmdSideLoopInletTemp = Node(FluidHX(CompNum)%DemandSideLoop%InletNodeNum)%Temp
SupSideLoopInletCp = GetSpecificHeatGlycol(PlantLoop(FluidHX(CompNum)%SupplySideLoop%LoopNum)%FluidName, &
SupSideLoopInletTemp , &
PlantLoop(FluidHX(CompNum)%SupplySideLoop%LoopNum)%FluidIndex, &
'CalcFluidHeatExchanger')
DmdSideLoopInletCp = GetSpecificHeatGlycol(PlantLoop(FluidHX(CompNum)%DemandSideLoop%LoopNum)%FluidName, &
DmdSideLoopInletTemp , &
PlantLoop(FluidHX(CompNum)%DemandSideLoop%LoopNum)%FluidIndex, &
'CalcFluidHeatExchanger')
SupSideCapRate = SupSideMdot * SupSideLoopInletCp
DmdSideCapRate = DmdSideMdot * DmdSideLoopInletCp
MinCapRate = MIN(SupSideCapRate, DmdSideCapRate)
MaxCapRate = MAX(SupSideCapRate, DmdSideCapRate)
IF (MinCapRate > 0.d0) THEN
SELECT CASE (FluidHX(CompNum)%HeatExchangeModelType)
CASE (CrossFlowBothUnMixed)
NTU = FluidHX(CompNum)%UA/MinCapRate
CapRatio = MinCapRate/MaxCapRate
EXPCheckValue1 = NTU**0.22d0/CapRatio
EXPCheckValue2 = -CapRatio*NTU**0.78d0
IF ((EXPCheckValue1 > EXP_UpperLimit) .OR. (EXPCheckValue2 > EXP_UpperLimit)) THEN
IF (-NTU >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ELSE
Effectiveness = 1.d0 - EXP((NTU**0.22d0/CapRatio) * &
(EXP(-CapRatio*NTU**0.78d0) - 1.0d0))
Effectiveness = MIN(1.d0,Effectiveness)
ENDIF
CASE (CrossFlowBothMixed)
NTU = FluidHX(CompNum)%UA/MinCapRate
CapRatio = MinCapRate/MaxCapRate
EXPCheckValue1 = -CapRatio*NTU
EXPCheckValue2 = -NTU
IF (EXPCheckValue1 < EXP_LowerLimit) THEN
IF (EXPCheckValue2 >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ELSEIF ( (EXP(-NTU) == 1.d0) .or. (NTU == 0.d0) .OR. (EXP(-CapRatio*NTU) == 1.d0) ) THEN ! don't div by zero
Effectiveness = 0.d0
ELSE
Effectiveness = 1.d0/( (1.d0/(1.d0-EXP(-NTU))) + (CapRatio/(1.d0 - EXP(-CapRatio*NTU) ) ) - ( 1.d0/ NTU) )
Effectiveness = MIN(1.0d0,Effectiveness)
ENDIF
CASE (CrossFlowSupplyLoopMixedDemandLoopUnMixed, CrossFlowSupplyLoopUnMixedDemandLoopMixed)
IF (SupSideCapRate == MaxCapRate .AND. FluidHX(CompNum)%HeatExchangeModelType &
== CrossFlowSupplyLoopMixedDemandLoopUnMixed) THEN
CrossFlowEquation = CmaxMixedCminUnmixed
ELSEIF (SupSideCapRate == MinCapRate .AND. FluidHX(CompNum)%HeatExchangeModelType &
== CrossFlowSupplyLoopMixedDemandLoopUnMixed) THEN
CrossFlowEquation = CmaxUnMixedCminMixed
ELSEIF (DmdSideCapRate == MaxCapRate .AND. FluidHX(CompNum)%HeatExchangeModelType &
== CrossFlowSupplyLoopUnMixedDemandLoopMixed) THEN
CrossFlowEquation = CmaxMixedCminUnmixed
ELSEIF (DmdSideCapRate == MinCapRate .AND. FluidHX(CompNum)%HeatExchangeModelType &
== CrossFlowSupplyLoopUnMixedDemandLoopMixed) THEN
CrossFlowEquation = CmaxUnMixedCminMixed
ELSE
CrossFlowEquation = CmaxMixedCminUnmixed
ENDIF
NTU = FluidHX(CompNum)%UA/MinCapRate
CapRatio = MinCapRate/MaxCapRate
IF (CrossFlowEquation == CmaxMixedCminUnmixed) THEN
ExpCheckValue1 = -NTU
IF (CapRatio == 0.d0) THEN ! protect div by zero
IF (ExpCheckValue1 >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ElSEIF (ExpCheckValue1 < EXP_LowerLimit ) THEN
Effectiveness = 0.632d0/CapRatio
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = (1.d0/CapRatio) * (1.d0 - EXP(CapRatio*EXP(-NTU)- 1.d0 ) )
Effectiveness = MIN(1.d0,Effectiveness)
ENDIF
ELSEIF (CrossFlowEquation == CmaxUnMixedCminMixed) THEN
ExpCheckValue1 = -CapRatio*NTU
IF (CapRatio == 0.d0) THEN
IF (-NTU >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ELSE
EXPCheckValue2 = -(1.0d0/CapRatio)*(1.0d0 - EXP(-CapRatio*NTU) )
IF (EXPCheckValue2 < EXP_LowerLimit) THEN
Effectiveness = 1.d0
ELSE
Effectiveness = 1.0d0 - EXP(-(1.0d0/CapRatio)*(1.0d0 - EXP(-CapRatio*NTU) ) )
Effectiveness = MIN(1.d0,Effectiveness)
ENDIF
ENDIF
ENDIF
CASE (CounterFlow)
NTU = FluidHX(CompNum)%UA/MinCapRate
CapRatio = MinCapRate/MaxCapRate
EXPCheckValue1 = -NTU*(1.d0-CapRatio)
IF (EXPCheckValue1 > EXP_UpperLimit) THEN
IF (-NTU >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ELSEIF (CapRatio*EXP(-NTU*(1.d0-CapRatio)) == 1.0d0) THEN
IF (-NTU >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ELSE
Effectiveness = (1.d0-EXP(-NTU*(1.d0-CapRatio)))/(1.d0-CapRatio*EXP(-NTU*(1.d0-CapRatio)))
Effectiveness = MIN(1.0d0,Effectiveness)
ENDIF
CASE (ParallelFlow)
NTU = FluidHX(CompNum)%UA/MinCapRate
CapRatio = MinCapRate/MaxCapRate
EXPCheckValue1 = -NTU*(1.d0+CapRatio)
IF (EXPCheckValue1 > EXP_UpperLimit) THEN
IF (-NTU >= EXP_LowerLimit) THEN
Effectiveness = 1.d0-EXP(-NTU)
Effectiveness = MIN(1.d0,Effectiveness)
ELSE
Effectiveness = 1.d0
ENDIF
ELSE
Effectiveness = (1.d0-EXP(-NTU*(1.d0+CapRatio)))/(1.d0+CapRatio)
Effectiveness = MIN(1.d0,Effectiveness)
ENDIF
CASE (Ideal)
Effectiveness = 1.d0
END SELECT
ELSE ! no capacity
Effectiveness = 0.d0
ENDIF
HeatTransferRate = Effectiveness * MinCapRate * ( SupSideLoopInletTemp - DmdSideLoopInletTemp) ! + means supply side is cooled
IF (SupSideMdot > 0.d0 ) THEN
FluidHX(CompNum)%SupplySideLoop%OutletTemp = SupSideLoopInletTemp - HeatTransferRate/ (SupSideLoopInletCp * SupSideMdot)
ELSE
FluidHX(CompNum)%SupplySideLoop%OutletTemp = SupSideLoopInletTemp
ENDIF
IF (DmdSideMdot > 0.d0) THEN
FluidHX(CompNum)%DemandSideLoop%OutletTemp = DmdSideLoopInletTemp + HeatTransferRate/ (DmdSideLoopInletCp * DmdSideMdot)
ELSE
FluidHX(CompNum)%DemandSideLoop%OutletTemp = DmdSideLoopInletTemp
ENDIF
FluidHX(CompNum)%Effectiveness = Effectiveness
FluidHX(CompNum)%HeatTransferRate = HeatTransferRate
FluidHX(CompNum)%SupplySideLoop%InletTemp = SupSideLoopInletTemp
FluidHX(CompNum)%SupplySideLoop%InletMassFlowRate = SupSideMdot
FluidHX(CompNum)%DemandSideLoop%InletTemp = DmdSideLoopInletTemp
FluidHX(CompNum)%DemandSideLoop%InletMassFlowRate = DmdSideMdot
RETURN
END SUBROUTINE CalcFluidHeatExchanger