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) | :: | PondGHENum | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
logical, | intent(in) | :: | RunFlag |
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 InitPondGroundHeatExchanger(PondGHENum,FirstHVACIteration,RunFlag)
! SUBROUTINE INFORMATION:
! AUTHOR Simon Rees
! DATE WRITTEN August 2002
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine Resets the elements of the data structure as necessary
! at the first HVAC iteration of each time step.
! METHODOLOGY EMPLOYED:
! One of the things done here is to update the record of the past pond
! temperature. This is needed in order to solve the diff. eqn. to find
! the temperature at the end of the next time step.
! Also set module variables to data structure for this pond. Set flow rate
! from node data and hypothetical design flow.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataGlobals, ONLY: BeginTimeStepFlag, PI,warmupflag
USE DataLoopNode, ONLY: Node
USE DataEnvironment, ONLY: GroundTemp_Deep, OutDryBulbTempAt
USE DataPlant, ONLY: TypeOf_GrndHtExchgPond, ScanPlantLoopsForObject
USE PlantUtilities, ONLY: SetComponentFlowRate, InitComponentNodes, RegisterPlantCompDesignFlow, &
RegulateCondenserCompFlowReqOp
USE FluidProperties, ONLY: GetDensityGlycol, GetSpecificHeatGlycol
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: PondGHENum ! component number
LOGICAL, INTENT(IN) :: FirstHVACIteration ! TRUE if 1st HVAC simulation of system timestep
! INTEGER, INTENT(IN) :: FlowLock ! flow initialization/condition flag !DSU
LOGICAL, INTENT(IN) :: RunFlag ! TRUE if equipment scheduled to operate
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: DesignVelocity=0.5d0 ! Hypothetical design max pipe velocity [m/s]
REAL(r64), PARAMETER :: PondHeight = 0.0d0 ! for now
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: DesignFlow ! Hypothetical design flow rate
LOGICAL, SAVE :: OneTimeFlag = .TRUE. ! flag for one time intializations
INTEGER :: PondNum ! loop counter
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyFlag
LOGICAL, SAVE :: MyOneTimeFlag = .TRUE.
INTEGER :: LoopNum
INTEGER :: LoopSideNum
REAL(r64) :: rho
REAL(r64) :: Cp
LOGICAL :: errFlag
!repeated warm up days tend to drive the initial pond temperature toward the drybulb temperature
!For each environment start the pond midway between drybulb and ground temp.
IF(OneTimeFlag .or. warmupflag)THEN
DO PondNum = 1, NumOfPondGHEs
! initialize pond temps to mean of drybulb and ground temps.
PondGHE%BulkTemperature = 0.5d0 * (OutDryBulbTempAt(PondHeight) + GroundTemp_Deep)
PondGHE%PastBulkTemperature = 0.5d0 * (OutDryBulbTempAt(PondHeight) + GroundTemp_Deep)
OneTimeFlag = .FALSE.
END DO
END IF
IF (MyOneTimeFlag) THEN
ALLOCATE(MyFlag(NumOfPondGHEs))
MyOneTimeFlag = .false.
MyFlag = .TRUE.
END IF
! Init more variables
IF (MyFlag(PondGHENum)) THEN
! Locate the hx on the plant loops for later usage
errFlag=.false.
CALL ScanPlantLoopsForObject(PondGHE(PondGHENum)%Name, &
TypeOf_GrndHtExchgPond, &
PondGHE(PondGHENum)%LoopNum, &
PondGHE(PondGHENum)%LoopSideNum, &
PondGHE(PondGHENum)%BranchNum, &
PondGHE(PondGHENum)%CompNum, &
errFlag=errFlag)
IF (errFlag) THEN
CALL ShowFatalError('InitPondGroundHeatExchanger: Program terminated due to previous condition(s).')
ENDIF
rho = GetDensityGlycol(PlantLoop(PondGHE(PondGHENum)%LoopNum)%fluidName, &
constant_zero,&
PlantLoop(PondGHE(PondGHENum)%LoopNum)%fluidIndex, &
'InitPondGroundHeatExchanger')
Cp = GetSpecificHeatGlycol(PlantLoop(PondGHE(PondGHENum)%LoopNum)%fluidName, &
constant_zero,&
PlantLoop(PondGHE(PondGHENum)%LoopNum)%fluidIndex, &
'InitPondGroundHeatExchanger')
PondGHE(PondGHENum)%DesignMassFlowRate = PI/4.0d0 * PondGHE(PondGHENum)%TubeInDiameter**2 * DesignVelocity * &
rho * PondGHE(PondGHENum)%NumCircuits
PondGHE(PondGHENum)%DesignCapacity = PondGHE(PondGHENum)%DesignMassFlowRate * Cp * 10.d0 !assume 10C delta T?
CALL InitComponentNodes(0.d0, PondGHE(PondGHENum)%DesignMassFlowRate, &
PondGHE(PondGHENum)%InletNodeNum, &
PondGHE(PondGHENum)%OutletNodeNum, &
PondGHE(PondGHENum)%LoopNum, &
PondGHE(PondGHENum)%LoopSideNum, &
PondGHE(PondGHENum)%BranchNum, &
PondGHE(PondGHENum)%CompNum)
CALL RegisterPlantCompDesignFlow(PondGHE(PondGHENum)%InletNodeNum, PondGHE(PondGHENum)%DesignMassFlowRate /rho)
MyFlag(PondGHENum)=.FALSE.
ENDIF
! check if we are in very first call for this zone time step
LoopNum = PondGHE(PondGHENum)%LoopNum
LoopSideNum = PondGHE(PondGHENum)%LoopSideNum
IF (BeginTimeStepFlag.AND.FirstHVACIteration.AND.PlantLoop(LoopNum)%Loopside(LoopSideNum)%FlowLock==1) THEN !DSU
! update past temperature
PondGHE(PondGHENum)%PastBulkTemperature = PondGHE(PondGHENum)%BulkTemperature
END IF
! initialize - module variables
InletNodeNum = PondGHE(PondGHENum)%InletNodeNum
OutletNodeNum = PondGHE(PondGHENum)%OutletNodeNum
PondArea = PondGHE(PondGHENum)%Area
PondDepth = PondGHE(PondGHENum)%Depth
InletTemp = Node(InletNodeNum)%Temp
OutletTemp = Node(OutletNodeNum)%Temp
TubeInDiameter = PondGHE(PondGHENum)%TubeInDiameter
TubeOutDiameter = PondGHE(PondGHENum)%TubeOutDiameter
TubeConductivity = PondGHE(PondGHENum)%TubeConductivity
GrndConductivity = PondGHE(PondGHENum)%GrndConductivity
NumCircuits = PondGHE(PondGHENum)%NumCircuits
CircLength = PondGHE(PondGHENum)%CircuitLength
! temperatures
PondTemp = PondGHE(PondGHENum)%BulkTemperature
PastPondTemp = PondGHE(PondGHENum)%PastBulkTemperature
DesignFlow = RegulateCondenserCompFlowReqOp(PondGHE(PondGHENum)%LoopNum,&
PondGHE(PondGHENum)%LoopSideNum,&
PondGHE(PondGHENum)%BranchNum,&
PondGHE(PondGHENum)%CompNum, &
PondGHE(PondGHENum)%DesignMassFlowRate)
CALL SetComponentFlowRate(DesignFlow, &
PondGHE(PondGHENum)%InletNodeNum,&
PondGHE(PondGHENum)%OutletNodeNum,&
PondGHE(PondGHENum)%LoopNum,&
PondGHE(PondGHENum)%LoopSideNum,&
PondGHE(PondGHENum)%BranchNum,&
PondGHE(PondGHENum)%CompNum)
! get the current flow rate - module variable
FlowRate = Node(InletNodeNum)%MassFlowRate
END SUBROUTINE InitPondGroundHeatExchanger