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 | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | InsideTemperature | |||
real(kind=r64), | intent(in) | :: | PondTemperature | |||
real(kind=r64), | intent(in) | :: | MassFlowRate | |||
integer, | intent(in) | :: | PondGHENum |
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.
FUNCTION CalcEffectiveness(InsideTemperature, PondTemperature,MassFlowRate,PondGHENum)
! FUNCTION INFORMATION:
! AUTHOR Simon Rees
! DATE WRITTEN August 2002
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates the "heat exchanger" effectiveness.
! This routine is adapted from that in the low temp radiant pond model.
! METHODOLOGY EMPLOYED:
! The heat transfer coefficient is calculated at the pipe and
! consists of inside and outside convection coefficients and conduction
! through the pipe. The other assumptions are that the tube inside
! surface temperature is equal to the "source location temperature"
! and that it is a CONSTANT throughout the pond. External convection is
! natural mode using Churchill and Chu correlation. Inside convection
! calcualted using the Dittus-Boelter equation.
! REFERENCES:
! Incropera, F.P. and D.P. DeWitt, 1996. Introduction to Heat Transfer,
! 3 rd Edition. John Wiley & Sons.
! Churchill, S.W. and H.H.S. Chu. 1975. Correlating Equations for
! Laminar and Turbulent Free Convection from a Horizontal Cylinder.
! International Journal of Heat and Mass Transfer, 18: 1049-1053.
! See also RadiantSystemLowTemp module.
! USE STATEMENTS:
USE DataGlobals, ONLY : PI, NumOfTimeStepInHour
USE General, ONLY : RoundSigDigits
USE FluidProperties, ONLY : GetSpecificHeatGlycol,GetConductivityGlycol, &
GetViscosityGlycol,GetDensityGlycol
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! FUNCTION ARGUMENT DEFINITIONS:
REAL(r64) :: CalcEffectiveness ! Function return variable
REAL(r64),INTENT(IN) :: InsideTemperature ! Temperature of fluid in pipe circuit, in C
REAL(r64),INTENT(IN) :: PondTemperature ! Temperature of pond water (i.e. outside the pipe), in C
REAL(r64),INTENT(IN) :: MassFlowRate ! Mass flow rate, in kg/s
INTEGER, INTENT(IN) :: PondGHENum ! Number of the Pond GHE
! FUNCTION PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: MaxLaminarRe = 2300.d0 ! Maximum Reynolds number for laminar flow
REAL(r64), PARAMETER :: GravConst = 9.81d0 ! gravitational constant - should be fixed!
CHARACTER(len=*), PARAMETER :: CalledFrom='PondGroundHeatExchanger:CalcEffectiveness'
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: NuseltNum ! Nuselt number (dimensionless)
REAL(r64) :: PrantlNum ! Prandtl number (dimensionless)
REAL(r64) :: ReynoldsNum ! Reynolds number (dimensionless)
REAL(r64) :: RayleighNum ! Rayleigh number (dimensionless)
REAL(r64) :: ThermDiff ! thermal diffusivity
REAL(r64) :: ExpansionCoef ! Expansion coefficient, in K^-1
REAL(r64) :: Viscosity ! Viscosity, in Ns/m2
REAL(r64) :: Density ! fluid density
REAL(r64) :: SpecificHeat ! Fluid specific heat
REAL(r64) :: Conductivity ! Fluid thermal conductivity
REAL(r64) :: WaterSpecHeat ! Specific heat of pond water
REAL(r64) :: NTU ! Number of transfer units, non-dimensional
REAL(r64) :: ConvCoefOut ! convection coefficient at outside of pipe
REAL(r64) :: ConvCoefIn ! convection coefficient at inside of pipe
REAL(r64) :: PipeResistance ! pipe wall thermal resistance
REAL(r64) :: TotalResistance ! total pipe thermal resistance - conduction and convection
! INTEGER, SAVE ::ErrCount=0
! INTEGER, SAVE ::ConsecutiveFrozen=0
! evaluate properties at pipe fluid temperature for given pipe fluid
SpecificHeat = GetSpecificHeatGlycol(PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidName,InsideTemperature, &
PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidIndex,CalledFrom)
Conductivity = GetConductivityGlycol(PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidName,InsideTemperature, &
PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidIndex,CalledFrom)
Viscosity = GetViscosityGlycol(PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidName,InsideTemperature, &
PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidIndex,CalledFrom)
Density = GetDensityGlycol(PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidName,InsideTemperature, &
PlantLoop(PondGHE(PondGHENum)%LoopNum)%FluidIndex,CalledFrom)
! Calculate the Reynold's number from RE=(4*Mdot)/(Pi*Mu*Diameter)
ReynoldsNum = 4.0d0 * MassFlowRate / ( PI * Viscosity * TubeInDiameter * NumCircuits)
PrantlNum = Viscosity*SpecificHeat/Conductivity
! Calculate the Nusselt number based on what flow regime one is in. h = (k)(Nu)/D
IF (ReynoldsNum >= MaxLaminarRe) THEN ! Turbulent flow --> use Dittus-Boelter equation
NuseltNum = 0.023d0*(ReynoldsNum**(0.8d0))*(PrantlNum**(0.3d0))
ELSE ! Laminar flow --> use constant surface temperature relation
NuseltNum = 3.66d0
END IF
! inside convection resistance, from Nu
ConvCoefIn = Conductivity * NuseltNum / TubeInDiameter
! now find properties of pond water - always assume pond fluid is water
WaterSpecHeat = GetSpecificHeatGlycol('WATER',MAX(PondTemperature,0.0d0), WaterIndex,CalledFrom)
Conductivity = GetConductivityGlycol('WATER',MAX(PondTemperature,0.0d0), WaterIndex,CalledFrom)
Viscosity = GetViscosityGlycol('WATER',MAX(PondTemperature,0.0d0), WaterIndex,CalledFrom)
Density = GetDensityGlycol('WATER',MAX(PondTemperature,0.0d0), WaterIndex,CalledFrom)
! derived properties for natural convection coefficient
! expansion coef (Beta) = -1/Rho. dRho/dT
! The following code includes some slight modifications from Simon's original code.
! It guarantees that the delta T is 10C and also avoids the problems associated with
! water hitting a maximum density at around 4C. (RKS)
ExpansionCoef = -(GetDensityGlycol('WATER',MAX(PondTemperature,10.0d0) + 5.0d0, WaterIndex,CalledFrom) - &
GetDensityGlycol('WATER',MAX(PondTemperature,10.0d0) - 5.0d0, WaterIndex,CalledFrom)) / &
(10.0d0*Density)
ThermDiff = Conductivity/(Density*WaterSpecHeat)
PrantlNum = Viscosity*WaterSpecHeat/Conductivity
RayleighNum = Density*GravConst*ExpansionCoef*ABS(InsideTemperature - PondTemperature) * &
TubeOutDiameter**3 / (Viscosity*ThermDiff)
! Calculate the Nusselt number for natural convection at outside of pipe
NuseltNum = (0.6d0 + (0.387d0*RayleighNum**(1.0d0/6.0d0)/((1.0d0+0.559d0/PrantlNum**(9.0d0/16.0d0))**(8.0d0/27.0d0))))**2
! outside convection resistance, from Nu
ConvCoefOut = Conductivity * NuseltNum / TubeOutDiameter
! conduction resistance of pipe
PipeResistance = TubeInDiameter/TubeConductivity * LOG(TubeOutDiameter/TubeInDiameter)
TotalResistance = PipeResistance + 1.0d0/ConvCoefIn + TubeInDiameter/(TubeOutDiameter*ConvCoefOut)
! Calculate the NTU parameter
! NTU = UA/[(Mdot*Cp)min] = A/[Rtot*(Mdot*Cp)min]
! where: Rtot = Ri,convection + Rconduction + Ro,conveciton
! A = Pi*D*TubeLength
IF(MassFlowRate == 0.0d0) Then
CalcEffectiveness = 1.0d0
Else
NTU = PI * TubeInDiameter * CircLength*NumCircuits / (TotalResistance * MassFlowRate * SpecificHeat)
! Calculate effectiveness - formula for static fluid
CalcEffectiveness = (1.d0-EXP(-NTU))
End If
! Check for frozen pond
IF (PondTemperature .LT. 0.0d0) THEN
PondGHE(PondGHENum)%ConsecutiveFrozen=PondGHE(PondGHENum)%ConsecutiveFrozen+1
IF (PondGHE(PondGHENum)%FrozenErrIndex == 0) THEN
CALL ShowWarningMessage('GroundHeatExchanger:Pond="'//trim(PondGHE(PondGHENum)%Name)// &
'", is frozen; Pond model not valid. Calculated Pond Temperature=['// &
trim(RoundSigDigits(PondTemperature,2))//'] C')
CALL ShowContinueErrorTimeStamp(' ')
ENDIF
CALL ShowRecurringWarningErrorAtEnd('GroundHeatExchanger:Pond="'//trim(PondGHE(PondGHENum)%Name)// &
'", is frozen',PondGHE(PondGHENum)%FrozenErrIndex, ReportMinOf=PondTemperature,ReportMinUnits='[C]', &
ReportMaxOf=PondTemperature,ReportMaxUnits='[C]')
IF (PondGHE(PondGHENum)%ConsecutiveFrozen >= NumOfTimeStepInHour*30) THEN
CALL ShowFatalError('GroundHeatExchanger:Pond="'//trim(PondGHE(PondGHENum)%Name)// &
'" has been frozen for 30 consecutive hours. Program terminates.')
ENDIF
ELSE
PondGHE(PondGHENum)%ConsecutiveFrozen=0
END IF
RETURN
END FUNCTION CalcEffectiveness