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) | :: | GlheNum | |||
real(kind=r64), | intent(out) | :: | ResistanceBhole |
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 BoreholeResistance(GlheNum,ResistanceBhole)
! SUBROUTINE INFORMATION:
! AUTHOR Cenk Yavuzturk
! DATE WRITTEN 1998
! MODIFIED August, 2000
! RE-ENGINEERED Dan Fisher
! PURPOSE OF THIS SUBROUTINE:
! Calculates the resistance of a vertical borehole
! with a U-tube inserted into it.
!
! METHODOLOGY EMPLOYED:
!
! REFERENCE: Thermal Analysis of Heat Extraction
! Boreholes. Per Eskilson, Dept. of
! Mathematical Physics, University of
! Lund, Sweden, June 1987.
!
! USE STATEMENTS: na
USE FluidProperties, ONLY: GetSpecificHeatGlycol, GetDensityGlycol, GetViscosityGlycol, &
GetConductivityGlycol
USE DataPlant, ONLY: PlantLoop
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: GlheNum
REAL(r64), INTENT(OUT) :: ResistanceBhole
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: NumBholes !number of boreholes
REAL(r64) :: BholeLength
REAL(r64) :: BholeRadius
REAL(r64) :: K_Ground
REAL(r64) :: Cp_Ground
REAL(r64) :: Cp_Fluid
REAL(r64) :: Tground
REAL(r64) :: K_Grout
REAL(r64) :: K_Fluid
REAL(r64) :: K_Pipe
REAL(r64) :: FluidDensity
REAL(r64) :: FluidViscosity
REAL(r64) :: PipeOuterDia
REAL(r64) :: PipeInnerDia
REAL(r64) :: DistUtube
REAL(r64) :: ThickPipe
REAL(r64) :: BholeMdot
REAL(r64) :: PipeOuterRad
REAL(r64) :: PipeInnerRad
REAL(r64) :: NusseltNum
REAL(r64) :: ReynoldsNum
REAL(r64) :: PrandlNum
REAL(r64) :: hci
REAL(r64) :: Rcond
REAL(r64) :: Rconv
REAL(r64) :: Rgrout
REAL(r64) :: B0, B1 !grout resistance curve fit coefficients
REAL(r64) :: MaxDistance
REAL(r64) :: DistanceRatio
!assign local variables
NumBholes = VerticalGlhe(GlheNum)%NumBoreholes
BholeLength = VerticalGlhe(GlheNum)%BoreholeLength
BholeRadius = VerticalGlhe(GlheNum)%BoreholeRadius
K_Ground = VerticalGlhe(GlheNum)%KGround
Cp_Ground = VerticalGlhe(GlheNum)%CpRhoGround
Cp_Fluid = GetSpecificHeatGlycol(PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidName, &
GlheInletTemp, &
PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidIndex, &
'CalcVerticalGroundHeatExchanger')
Tground = VerticalGlhe(GlheNum)%TempGround
K_Grout = VerticalGlhe(GlheNum)%KGrout
K_Pipe = VerticalGlhe(GlheNum)%KPipe
K_Fluid = GetConductivityGlycol(PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidName, &
GlheInletTemp, &
PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidIndex, &
'CalcVerticalGroundHeatExchanger')
FluidDensity = GetDensityGlycol(PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidName, &
GlheInletTemp, &
PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidIndex, &
'CalcVerticalGroundHeatExchanger')
FluidViscosity = GetViscosityGlycol(PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidName, &
GlheInletTemp, &
PlantLoop(VerticalGlhe(GlheNum)%LoopNum)%FluidIndex, &
'CalcVerticalGroundHeatExchanger')
PipeOuterDia = VerticalGlhe(GlheNum)%PipeOutDia
DistUtube = VerticalGlhe(GlheNum)%UtubeDist
ThickPipe = VerticalGlhe(GlheNum)%PipeThick
!calculate mass flow rate
BholeMdot = GlheMassFlowRate/NumBholes !VerticalGlhe(GlheNum)%DesignFlow*FluidDensity /NumBholes
PipeOuterRad = PipeOuterDia / 2.0d0
PipeInnerRad = PipeOuterRad-ThickPipe
PipeInnerDia = 2.0d0 * PipeInnerRad
!Re=Rho*V*D/Mu
ReynoldsNum = FluidDensity*PipeInnerDia*(BholeMdot/FluidDensity/(PI*PipeInnerRad**2))/FluidViscosity
PrandlNum=(Cp_Fluid*FluidViscosity)/(K_Fluid)
! Convection Resistance
NusseltNum = 0.023d0 * (ReynoldsNum**0.8d0) * (PrandlNum**0.35d0)
hci = NusseltNum * K_Fluid / PipeInnerDia
IF(BholeMdot == 0.0d0)THEN
RCONV=0.0d0
ELSE
RCONV = 1.0d0 / (2.0d0*PI*PipeInnerDia*hci)
ENDIF
! Conduction Resistance
RCOND = LOG(PipeOuterRad/PipeInnerRad) / (2.0d0*PI*K_Pipe)/2.d0 ! pipe in parallel so /2
! Resistance Due to the grout.
MaxDistance=2.d0*BholeRadius-(2.d0*PipeOuterDia)
DistanceRatio=DistUtube/MaxDistance
IF(DistanceRatio >= 0.0d0 .AND. DistanceRatio <= 0.25d0) THEN
B0=14.450872d0
B1=-0.8176d0
ELSE IF(DistanceRatio > 0.25d0 .AND. DistanceRatio < 0.5d0) THEN
B0=20.100377d0
B1=-0.94467d0
ELSE IF(DistanceRatio >= 0.5d0.and.DistanceRatio <= 0.75d0) THEN
B0=17.44268d0
B1=-0.605154d0
ELSE
B0=21.90587d0
B1=-0.3796d0
END IF
RGROUT=1.d0/(K_Grout*(B0*(BholeRadius/PipeOuterRad)**B1))
ResistanceBhole = RCOND+RCONV+RGROUT
RETURN
END SUBROUTINE BoreholeResistance