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) | :: | PipeHTNum |
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.
REAL(r64) FUNCTION OutsidePipeHeatTransCoef(PipeHTNum)
! FUNCTION INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN July 2007
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates the convection heat transfer
! coefficient for a cylinder in cross flow.
! REFERENCES:
! Fundamentals of Heat and Mass Transfer: Incropera and DeWitt, 4th ed.
! p. 369-370 (Eq. 7:55b)
! USE STATEMENTS:
USE DataHeatBalFanSys, ONLY : MAT !average (mean) zone air temperature [C]
USE DataLoopNode, ONLY : Node
USE ScheduleManager, ONLY : GetCurrentScheduleValue
USE DataEnvironment, ONLY : WindSpeed
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: PipeHTNum ! Index number of surface under consideration
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: Pr = 0.7d0 ! Prandl number for air (assume constant)
REAL(r64), PARAMETER :: CondAir = 0.025d0 ! thermal conductivity of air (assume constant) [W/m.K]
REAL(r64), PARAMETER :: RoomAirVel = 0.381d0 !room air velocity of 75 ft./min [m/s]
REAL(r64), PARAMETER :: NaturalConvNusselt = 0.36d0
!Nusselt for natural convection for horizontal cylinder
!from: Correlations for Convective Heat Transfer
! Dr. Bernhard Spang
! Chemical Engineers' Resource Page: http://www.cheresources.com/convection.pdf
INTEGER, PARAMETER :: NumOfParamDivisions = 5 ! intervals in property correlation
INTEGER, PARAMETER :: NumOfPropDivisions = 12 ! intervals in property correlation
REAL(r64), PARAMETER, DIMENSION(NumOfParamDivisions) :: CCoef = & ! correlation coefficient
(/0.989d0,0.911d0,0.683d0,0.193d0,0.027d0/)
REAL(r64), PARAMETER, DIMENSION(NumOfParamDivisions) :: mExp = & ! exponent
(/0.33d0,0.385d0,0.466d0,0.618d0,0.805d0/)
REAL(r64), PARAMETER, DIMENSION(NumOfParamDivisions) :: LowerBound = & ! upper bound of correlation range
(/0.4d0,4.d0,40.d0,4000.d0,40000.d0/)
REAL(r64), PARAMETER, DIMENSION(NumOfParamDivisions) :: UpperBound = & ! lower bound of correlation range
(/4.d0,40.d0,4000.d0,40000.d0,400000.d0/)
REAL(r64), PARAMETER, DIMENSION(NumOfPropDivisions) :: Temperature = & ! temperature [C]
(/-73.d0,-23.d0,-10.d0,0.d0,10.d0,20.d0,27.d0,30.d0,40.d0,50.d0,76.85d0,126.85d0/)
REAL(r64), PARAMETER, DIMENSION(NumOfPropDivisions) :: DynVisc = & ! dynamic viscosity [m^2/s]
(/75.52d-7,11.37d-6,12.44d-6,13.3d-6,14.18d-6,15.08d-6,15.75d-6,16d-6,16.95d-6,17.91d-6,20.92d-6,26.41d-6/)
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: Index
REAL(r64) :: NuD
REAL(r64) :: ReD
REAL(r64) :: Coef
REAL(r64) :: rExp
REAL(r64) :: AirVisc
REAL(r64) :: AirVel
REAL(r64) :: AirTemp
REAL(r64) :: MidTemp
REAL(r64) :: PipeOD
LOGICAL :: ViscositySet
LOGICAL :: CoefSet
!Set environmental variables
SELECT CASE (PipeHT(PipeHTNum)%TypeOf)
CASE (TypeOf_PipeInterior)
SELECT CASE (PipeHT(PipeHTNum)%EnvironmentPtr)
CASE (ScheduleEnv)
AirTemp = GetCurrentScheduleValue(PipeHT(PipeHTNum)%EnvrSchedPtr)
AirVel = GetCurrentScheduleValue(PipeHT(PipeHTNum)%EnvrVelSchedPtr)
CASE (ZoneEnv)
AirTemp = MAT(PipeHT(PipeHTNum)%EnvrZonePtr)
AirVel = RoomAirVel
END SELECT
CASE (TypeOf_PipeExterior)
SELECT CASE (PipeHT(PipeHTNum)%EnvironmentPtr)
CASE (OutsideAirEnv)
AirTemp = Node(PipeHT(PipeHTNum)%EnvrAirNodeNum)%Temp
AirVel = WindSpeed
END SELECT
END SELECT
PipeOD = PipeHT(PipeHTNum)%InsulationOD
ViscositySet = .FALSE.
DO index = 1, NumOfPropDivisions
IF(AirTemp <= Temperature(index))THEN
AirVisc = DynVisc(index)
ViscositySet = .TRUE.
EXIT
ENDIF
ENDDO
IF (.NOT. ViscositySet)THEN
AirVisc = DynVisc(NumOfPropDivisions)
IF(AirTemp > Temperature(NumOfPropDivisions))THEN
CALL ShowWarningError('Heat Transfer Pipe = '//TRIM(PipeHT(PipeHTNum)%Name)// &
'Viscosity out of range, air temperature too high, setting to upper limit.')
ENDIF
ENDIF
! Calculate the Reynold's number
CoefSet = .FALSE.
IF (AirVisc > 0.0d0)THEN
ReD = AirVel* PipeOD / (AirVisc)
ENDIF
DO index = 1,NumOfParamDivisions
IF(ReD <= Upperbound(index))THEN
Coef = CCoef(index)
rExp = mExp(index)
CoefSet = .TRUE.
EXIT
ENDIF
ENDDO
IF (.NOT. CoefSet)THEN
Coef = CCoef(NumOfParamDivisions)
rExp = mExp(NumOfParamDivisions)
IF(ReD > Upperbound(NumOfParamDivisions))THEN
CALL ShowWarningError('Heat Transfer Pipe = '//TRIM(PipeHT(PipeHTNum)%Name)// &
'Reynolds Number out of range, setting coefficients to upper limit.')
ENDIF
ENDIF
! Calculate the Nusselt number
NuD = Coef*(ReD**(rExp))*(Pr**(1.d0/3.d0))
! If the wind speed is too small, we need to use natural convection behavior:
NuD = MAX(NuD,NaturalConvNusselt)
! h = (k)(Nu)/D
OutsidePipeHeatTransCoef = CondAir * NuD / PipeOD
RETURN
END FUNCTION OutsidePipeHeatTransCoef