PlantPipingSystemsManager Module

module~~plantpipingsystemsmanager~~UsesGraph module~plantpipingsystemsmanager PlantPipingSystemsManager module~datainterfaces DataInterfaces module~datainterfaces->module~plantpipingsystemsmanager module~dataglobals DataGlobals module~dataglobals->module~plantpipingsystemsmanager module~dataplantpipingsystems DataPlantPipingSystems module~dataglobals->module~dataplantpipingsystems module~dataprecisionglobals DataPrecisionGlobals module~dataprecisionglobals->module~plantpipingsystemsmanager module~dataprecisionglobals->module~datainterfaces module~dataprecisionglobals->module~dataglobals module~dataprecisionglobals->module~dataplantpipingsystems module~dataplantpipingsystems->module~plantpipingsystemsmanager
Help

Used By

module~~plantpipingsystemsmanager~~UsedByGraph module~plantpipingsystemsmanager PlantPipingSystemsManager proc~simplantequip SimPlantEquip module~plantpipingsystemsmanager->proc~simplantequip
Help


Variables

TypeVisibility AttributesNameInitial
character(len=*), private, parameter:: ObjName_ug_GeneralDomain ='PipingSystem:Underground:Domain'
character(len=*), private, parameter:: objName_Circuit ='PipingSystem:Underground:PipeCircuit'
character(len=*), private, parameter:: objName_Segment ='PipingSystem:Underground:PipeSegment'
character(len=*), private, parameter:: objName_HorizTrench ='GroundHeatExchanger:HorizontalTrench'
integer, private, ALLOCATABLE, DIMENSION(:):: NeighborFieldCells
integer, private, ALLOCATABLE, DIMENSION(:):: NeighborBoundaryCells

Interfaces

private interface IssueSevereInputFieldError

  • private subroutine IssueSevereAlphaInputFieldError(RoutineName, ObjectName, InstanceName, FieldName, FieldEntry, Condition, ErrorsFound)

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: RoutineName
    character(len=*), intent(in) :: ObjectName
    character(len=*), intent(in) :: InstanceName
    character(len=*), intent(in) :: FieldName
    character(len=*), intent(in) :: FieldEntry
    character(len=*), intent(in) :: Condition
    logical, intent(inout) :: ErrorsFound
  • private subroutine IssueSevereRealInputFieldError(RoutineName, ObjectName, InstanceName, FieldName, FieldEntry, Condition, ErrorsFound)

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: RoutineName
    character(len=*), intent(in) :: ObjectName
    character(len=*), intent(in) :: InstanceName
    character(len=*), intent(in) :: FieldName
    real(kind=r64), intent(in) :: FieldEntry
    character(len=*), intent(in) :: Condition
    logical, intent(inout) :: ErrorsFound

private interface IsInRange

  • private function Integer_IsInRange(i, lower, upper) result(RetVal)

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: i
    integer, intent(in) :: lower
    integer, intent(in) :: upper

    Return Value logical

  • private function Real_IsInRange(r, lower, upper) result(RetVal)

    Arguments

    Type IntentOptional AttributesName
    real(kind=r64), intent(in) :: r
    real(kind=r64), intent(in) :: lower
    real(kind=r64), intent(in) :: upper

    Return Value logical


Functions

private function GetNumSegmentsForHorizontalTrenches(NumHorizontalTrenches) result(Total)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: NumHorizontalTrenches

Return Value integer

private function GetSurfaceCountForOSCM(OSCMIndex) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: OSCMIndex

Return Value integer

private function GetSurfaceIndecesForOSCM(OSCMIndex, SurfCount) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: OSCMIndex
integer, intent(in) :: SurfCount

Return Value integer, DIMENSION(1:SurfCount)

private function Integer_IsInRange(i, lower, upper) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: i
integer, intent(in) :: lower
integer, intent(in) :: upper

Return Value logical

private function Real_IsInRange(r, lower, upper) result(RetVal)

Arguments

Type IntentOptional AttributesName
real(kind=r64), intent(in) :: r
real(kind=r64), intent(in) :: lower
real(kind=r64), intent(in) :: upper

Return Value logical

private function Real_ConstrainTo(r, MinVal, MaxVal) result(RetVal)

Arguments

Type IntentOptional AttributesName
real(kind=r64), intent(in) :: r
real(kind=r64), intent(in) :: MinVal
real(kind=r64), intent(in) :: MaxVal

Return Value real(kind=r64)

private function CellType_IsFieldCell(CellType) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: CellType

Return Value logical

private function MeshPartitionArray_Contains(meshes, value) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(MeshPartition), intent(in), ALLOCATABLE, DIMENSION(:):: meshes
real(kind=r64), intent(in) :: value

Return Value logical

private function RadialCellInfo_XY_CrossSectArea(r) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(RadialCellInformation), intent(in) :: r

Return Value real(kind=r64)

private function DomainRectangle_Contains(Rect, p) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(DomainRectangle), intent(in) :: Rect
type(Point), intent(in) :: p

Return Value logical

private function MeshPartition_CompareByDimension(x, y) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(MeshPartition), intent(in) :: x
type(MeshPartition), intent(in) :: y

Return Value integer

private function BaseThermalPropertySet_Diffusivity(p) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(BaseThermalPropertySet), intent(in) :: p

Return Value real(kind=r64)

private function RectangleF_Contains(rect, p) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(RectangleF), intent(in) :: rect
type(PointF), intent(in) :: p

Return Value logical

private function RadialSizing_Thickness(r) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(RadialSizing), intent(in) :: r

Return Value real(kind=r64)

private function IsConverged_CurrentToPrevIteration(DomainNum) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

Return Value logical

private function IsConverged_PipeCurrentToPrevIteration(CircuitNum, CellToCheck, MaxDivAmount) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: CircuitNum
type(CartesianCell), intent(in) :: CellToCheck
real(kind=r64), intent(inout) :: MaxDivAmount

Return Value logical

private function CheckForOutOfRangeTemps(DomainNum) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

Return Value logical

private function Width(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function Height(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function Depth(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function XNormalArea(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function YNormalArea(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function ZNormalArea(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function Volume(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value real(kind=r64)

private function XYRectangle(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value type(RectangleF)

private function XZRectangle(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value type(RectangleF)

private function YZRectangle(c) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c

Return Value type(RectangleF)

private function NormalArea(c, Direction) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(in) :: c
integer, intent(in) :: Direction

Return Value real(kind=r64)

private function NeighborInformationArray_Value(dict, Direction) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(DirectionNeighbor_Dictionary), intent(in), ALLOCATABLE, DIMENSION(:):: dict
integer, intent(in) :: Direction

Return Value type(NeighborInformation)

private function CreatePartitionRegionList(DomainNum, ThesePartitionCenters, PartitionsExist, DirExtentMax, PartitionsUbound) result(ThesePartitionRegions)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(MeshPartition), intent(in), ALLOCATABLE, DIMENSION(:):: ThesePartitionCenters
logical, intent(in) :: PartitionsExist
real(kind=r64), intent(in) :: DirExtentMax
integer, intent(in) :: PartitionsUbound

Return Value type(GridRegion), DIMENSION(0:PartitionsUBound)

private function CreateRegionListCount(ThesePartitionRegions, DirExtentMax, PartitionsExist) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(GridRegion), intent(in), ALLOCATABLE, DIMENSION(:):: ThesePartitionRegions
real(kind=r64), intent(in) :: DirExtentMax
logical, intent(in) :: PartitionsExist

Return Value integer

private function CreateRegionList(DomainNum, ThesePartitionRegions, DirExtentMax, DirDirection, RetValUBound, PartitionsExist, BasementWallXIndex, BasementFloorYIndex) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(GridRegion), intent(in), ALLOCATABLE, DIMENSION(:):: ThesePartitionRegions
real(kind=r64), intent(in) :: DirExtentMax
integer, intent(in) :: DirDirection
integer, intent(in) :: RetValUBound
logical, intent(in) :: PartitionsExist
integer, intent(inout), optional :: BasementWallXIndex
integer, intent(inout), optional :: BasementFloorYIndex

Return Value type(GridRegion), DIMENSION(0:RetValUbound)

private function CreateBoundaryListCount(RegionList, dirDirection) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(GridRegion), intent(in), ALLOCATABLE, DIMENSION(:):: RegionList
integer, intent(in) :: dirDirection

Return Value integer

private function CreateBoundaryList(RegionList, DirExtentMax, DirDirection, RetValLbound, RetValUbound) result(RetVal)

Arguments

Type IntentOptional AttributesName
type(GridRegion), intent(in), ALLOCATABLE, DIMENSION(:):: RegionList
real(kind=r64), intent(in) :: DirExtentMax
integer, intent(in) :: DirDirection
integer, intent(in) :: RetValLbound
integer, intent(in) :: RetValUbound

Return Value real(kind=r64) (RetValLbound:RetValUbound)

private function GetCellWidthsCount(DomainNum, dir) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: dir

Return Value integer

private function EvaluateFieldCellTemperature(DomainNum, ThisCell) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: ThisCell

Return Value real(kind=r64)

private function EvaluateGroundSurfaceTemperature(DomainNum, cell) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell

Return Value real(kind=r64)

private function EvaluateAdiabaticSurfaceTemperature(DomainNum, cell) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell

Return Value real(kind=r64)

private function EvaluateBasementCellTemperature(DomainNum, cell) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell

Return Value real(kind=r64)

private function GetBasementWallHeatFlux(DomainNum) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

Return Value real(kind=r64)

private function GetBasementFloorHeatFlux(DomainNum) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

Return Value real(kind=r64)

private function GetAverageTempByType(DomainNum, CellType) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CellType

Return Value real(kind=r64)

private function EvaluateFarfieldBoundaryTemperature(DomainNum, cell) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell

Return Value real(kind=r64)

private function GetFarfieldTemp(DomainNum, cell) result(RetVal)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell

Return Value real(kind=r64)


Subroutines

public subroutine SimPipingSystemCircuit(EquipName, EqNum, FirstHVACIteration, InitLoopEquip)

Arguments

Type IntentOptional AttributesName
character(len=*), intent(in) :: EquipName
integer, intent(inout) :: EqNum
logical, intent(in) :: FirstHVACIteration
logical, intent(in) :: InitLoopEquip

private subroutine GetPipingSystemsInput()

Arguments

None

private subroutine ReadGeneralDomainInputs(IndexStart, NumGeneralizedDomains, ErrorsFound)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: IndexStart
integer, intent(in) :: NumGeneralizedDomains
logical, intent(inout) :: ErrorsFound

private subroutine ReadPipeCircuitInputs(NumPipeCircuits, ErrorsFound)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: NumPipeCircuits
logical, intent(inout) :: ErrorsFound

private subroutine ReadPipeSegmentInputs(NumPipeSegmentsInInput, ErrorsFound)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: NumPipeSegmentsInInput
logical, intent(inout) :: ErrorsFound

private subroutine ReadHorizontalTrenchInputs(StartingDomainNumForHorizontal, StartingCircuitNumForHorizontal, StartingSegmentNumForHorizontal, NumHorizontalTrenchesInInput, ErrorsFound)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: StartingDomainNumForHorizontal
integer, intent(in) :: StartingCircuitNumForHorizontal
integer, intent(in) :: StartingSegmentNumForHorizontal
integer, intent(in) :: NumHorizontalTrenchesInInput
logical, intent(inout) :: ErrorsFound

private subroutine SetupAllOutputVariables(TotalNumSegments, TotalNumCircuits)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: TotalNumSegments
integer, intent(in) :: TotalNumCircuits

private subroutine InitPipingSystems(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine UpdatePipingSystems(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine IssueSevereAlphaInputFieldError(RoutineName, ObjectName, InstanceName, FieldName, FieldEntry, Condition, ErrorsFound)

Arguments

Type IntentOptional AttributesName
character(len=*), intent(in) :: RoutineName
character(len=*), intent(in) :: ObjectName
character(len=*), intent(in) :: InstanceName
character(len=*), intent(in) :: FieldName
character(len=*), intent(in) :: FieldEntry
character(len=*), intent(in) :: Condition
logical, intent(inout) :: ErrorsFound

private subroutine IssueSevereRealInputFieldError(RoutineName, ObjectName, InstanceName, FieldName, FieldEntry, Condition, ErrorsFound)

Arguments

Type IntentOptional AttributesName
character(len=*), intent(in) :: RoutineName
character(len=*), intent(in) :: ObjectName
character(len=*), intent(in) :: InstanceName
character(len=*), intent(in) :: FieldName
real(kind=r64), intent(in) :: FieldEntry
character(len=*), intent(in) :: Condition
logical, intent(inout) :: ErrorsFound

private subroutine MeshPartition_SelectionSort(X)

Arguments

Type IntentOptional AttributesName
type(MeshPartition), intent(inout), ALLOCATABLE, DIMENSION(:):: X

private subroutine PipeSegmentInfo_InitPipeCells(s, x, y)

Arguments

Type IntentOptional AttributesName
type(PipeSegmentInfo), intent(inout) :: s
integer, intent(in) :: x
integer, intent(in) :: y

private subroutine PipeCircuitInfo_InitInOutCells(c, in, out)

Arguments

Type IntentOptional AttributesName
type(PipeCircuitInfo), intent(inout) :: c
type(CartesianCell), intent(in) :: in
type(CartesianCell), intent(in) :: out

private subroutine ShiftTemperaturesForNewTimeStep(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine ShiftTemperaturesForNewIteration(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine ShiftPipeTemperaturesForNewIteration(ThisPipeCell)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(inout) :: ThisPipeCell

private subroutine CartesianPipeCellInformation_ctor(c, GridCellWidth, PipeSizes, NumRadialNodes, CellDepth, InsulationThickness, RadialGridExtent, SimHasInsulation)

Arguments

Type IntentOptional AttributesName
type(CartesianPipeCellInformation), intent(inout) :: c
real(kind=r64), intent(in) :: GridCellWidth
type(RadialSizing), intent(in) :: PipeSizes
integer, intent(in) :: NumRadialNodes
real(kind=r64), intent(in) :: CellDepth
real(kind=r64), intent(in) :: InsulationThickness
real(kind=r64), intent(in) :: RadialGridExtent
logical, intent(in) :: SimHasInsulation

private subroutine RadialCellInformation_ctor(c, m_RadialCentroid, m_MinRadius, m_MaxRadius)

Arguments

Type IntentOptional AttributesName
type(RadialCellInformation), intent(inout) :: c
real(kind=r64), intent(in) :: m_RadialCentroid
real(kind=r64), intent(in) :: m_MinRadius
real(kind=r64), intent(in) :: m_MaxRadius

private subroutine FluidCellInformation_ctor(c, m_PipeInnerRadius, m_CellDepth)

Arguments

Type IntentOptional AttributesName
type(FluidCellInformation), intent(inout) :: c
real(kind=r64), intent(in) :: m_PipeInnerRadius
real(kind=r64), intent(in) :: m_CellDepth

private subroutine DevelopMesh(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine CreatePartitionCenterList(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine CreateCellArray(DomainNum, XBoundaryPoints, YBoundaryPoints, ZBoundaryPoints, MaxBasementXNodeIndex, MinBasementYNodeIndex)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
real(kind=r64), intent(in), ALLOCATABLE, DIMENSION(:):: XBoundaryPoints
real(kind=r64), intent(in), ALLOCATABLE, DIMENSION(:):: YBoundaryPoints
real(kind=r64), intent(in), ALLOCATABLE, DIMENSION(:):: ZBoundaryPoints
integer, intent(in) :: MaxBasementXNodeIndex
integer, intent(in) :: MinBasementYNodeIndex

private subroutine SetupCellNeighbors(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine AddNeighborInformation(DomainNum, X, Y, Z, Direction, ThisCentroidToNeighborCentroid, ThisCentroidToNeighborWall, ThisWallToNeighborCentroid)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: X
integer, intent(in) :: Y
integer, intent(in) :: Z
integer, intent(in) :: Direction
real(kind=r64), intent(in) :: ThisCentroidToNeighborCentroid
real(kind=r64), intent(in) :: ThisCentroidToNeighborWall
real(kind=r64), intent(in) :: ThisWallToNeighborCentroid

private subroutine SetupPipeCircuitInOutCells(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine GetCellWidths(DomainNum, g)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(GridRegion) :: g

private subroutine PerformIterationLoop(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine PerformTemperatureFieldUpdate(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine UpdateBasementSurfaceTemperatures(DomainNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum

private subroutine EvaluateFarfieldCharacteristics(DomainNum, cell, direction, neighbortemp, resistance)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell
integer, intent(in) :: direction
real(kind=r64), intent(out) :: neighbortemp
real(kind=r64), intent(out) :: resistance

private subroutine PreparePipeCircuitSimulation(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine PerformPipeCircuitSimulation(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine PerformPipeCellSimulation(DomainNum, CircuitNum, ThisCell, FlowRate, EnteringTemp)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum
type(CartesianCell), intent(inout) :: ThisCell
real(kind=r64), intent(in) :: FlowRate
real(kind=r64), intent(in) :: EnteringTemp

private subroutine SimulateRadialToCartesianInterface(DomainNum, ThisCell)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(inout) :: ThisCell

private subroutine SimulateOuterMostRadialSoilSlice(DomainNum, CircuitNum, ThisCell)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum
type(CartesianCell), intent(inout) :: ThisCell

private subroutine SimulateAllInteriorRadialSoilSlices(ThisCell)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(inout) :: ThisCell

private subroutine SimulateInnerMostRadialSoilSlice(DomainNum, CircuitNum, ThisCell)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum
type(CartesianCell), intent(inout) :: ThisCell

private subroutine SimulateRadialInsulationCell(ThisCell)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(inout) :: ThisCell

private subroutine SimulateRadialPipeCell(DomainNum, CircuitNum, ThisCell, ConvectionCoefficient)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum
type(CartesianCell), intent(inout) :: ThisCell
real(kind=r64), intent(in) :: ConvectionCoefficient

private subroutine SimulateFluidCell(ThisCell, FlowRate, ConvectionCoefficient, EnteringFluidTemp)

Arguments

Type IntentOptional AttributesName
type(CartesianCell), intent(inout) :: ThisCell
real(kind=r64), intent(in) :: FlowRate
real(kind=r64), intent(in) :: ConvectionCoefficient
real(kind=r64), intent(in) :: EnteringFluidTemp

private subroutine DoOneTimeInitializations(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine DoStartOfTimeStepInitializations(DomainNum, CircuitNum)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: CircuitNum

private subroutine DoEndOfIterationOperations(DomainNum, Finished)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
logical, intent(inout) :: Finished

private subroutine EvaluateSoilRhoCp(DomainNum, CellTemp, rhoCp, InitOnly)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
real(kind=r64), intent(in), optional :: CellTemp
real(kind=r64), intent(out), optional :: rhoCp
logical, intent(in), optional :: InitOnly

private subroutine SetAdditionalNeighborData(DomainNum, X, Y, Z, Direction, Resistance, NeighborCell)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
integer, intent(in) :: X
integer, intent(in) :: Y
integer, intent(in) :: Z
integer, intent(in) :: Direction
real(kind=r64), intent(in) :: Resistance
type(CartesianCell), intent(in) :: NeighborCell

private subroutine EvaluateNeighborCharacteristics(DomainNum, ThisCell, CurDirection, NeighborTemp, Resistance, NeighborX, NeighborY, NeighborZ)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: ThisCell
integer, intent(in) :: CurDirection
real(kind=r64), intent(out) :: NeighborTemp
real(kind=r64), intent(out) :: Resistance
integer, intent(out), optional :: NeighborX
integer, intent(out), optional :: NeighborY
integer, intent(out), optional :: NeighborZ

private subroutine EvaluateCellNeighborDirections(DomainNum, cell)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: DomainNum
type(CartesianCell), intent(in) :: cell


AirflowNetworkBalanceManager AirflowNetworkSolver BaseboardElectric BaseboardRadiator Boilers BoilerSteam BranchInputManager BranchNodeConnections ChillerAbsorption ChillerElectricEIR ChillerExhaustAbsorption ChillerGasAbsorption ChillerIndirectAbsorption ChillerReformulatedEIR CondenserLoopTowers ConductionTransferFunctionCalc ConvectionCoefficients CoolTower CostEstimateManager CrossVentMgr CTElectricGenerator CurveManager DataAirflowNetwork DataAirLoop DataAirSystems DataBranchAirLoopPlant DataBranchNodeConnections DataBSDFWindow DataComplexFenestration DataContaminantBalance DataConvergParams DataConversions DataCostEstimate DataDaylighting DataDaylightingDevices DataDefineEquip DataDElight DataEnvironment DataErrorTracking DataGenerators DataGlobalConstants DataGlobals DataHeatBalance DataHeatBalFanSys DataHeatBalSurface DataHVACControllers DataHVACGlobals DataInterfaces DataIPShortCuts DataLoopNode DataMoistureBalance DataMoistureBalanceEMPD DataOutputs DataPhotovoltaics DataPlant DataPlantPipingSystems DataPrecisionGlobals DataReportingFlags DataRoomAirModel DataRootFinder DataRuntimeLanguage DataShadowingCombinations DataSizing DataStringGlobals DataSurfaceColors DataSurfaceLists DataSurfaces DataSystemVariables DataTimings DataUCSDSharedData DataVectorTypes DataViewFactorInformation DataWater DataWindowEquivalentLayer DataZoneControls DataZoneEnergyDemands DataZoneEquipment DaylightingDevices DaylightingManager DELIGHTMANAGERF DELIGHTMANAGERF DemandManager DesiccantDehumidifiers DirectAirManager DisplacementVentMgr DualDuct DXCoils DXFEarClipping EarthTube EconomicLifeCycleCost EconomicTariff EcoRoofManager ElectricBaseboardRadiator EMSManager EvaporativeCoolers EvaporativeFluidCoolers ExteriorEnergyUse ExternalInterface FanCoilUnits Fans FaultsManager FluidCoolers FluidProperties FuelCellElectricGenerator Furnaces General GeneratorDynamicsManager GeneratorFuelSupply GlobalNames GroundHeatExchangers HeatBalanceAirManager HeatBalanceHAMTManager HeatBalanceIntRadExchange HeatBalanceManager HeatBalanceMovableInsulation HeatBalanceSurfaceManager HeatBalFiniteDiffManager HeatingCoils HeatPumpWaterToWaterCOOLING HeatPumpWaterToWaterHEATING HeatPumpWaterToWaterSimple HeatRecovery HighTempRadiantSystem Humidifiers HVACControllers HVACCooledBeam HVACDuct HVACDXHeatPumpSystem HVACDXSystem HVACHXAssistedCoolingCoil HVACInterfaceManager HVACManager HVACMultiSpeedHeatPump HVACSingleDuctInduc HVACStandAloneERV HVACUnitaryBypassVAV HVACUnitarySystem HVACVariableRefrigerantFlow HWBaseboardRadiator ICEngineElectricGenerator IceThermalStorage InputProcessor InternalHeatGains ISO_C_FUNCTION_BINDING ISO_C_FUNCTION_BINDING LowTempRadiantSystem ManageElectricPower MatrixDataManager MicroCHPElectricGenerator MicroturbineElectricGenerator MixedAir MixerComponent MoistureBalanceEMPDManager MundtSimMgr NodeInputManager NonZoneEquipmentManager OutAirNodeManager OutdoorAirUnit OutputProcessor OutputReportPredefined OutputReportTabular OutsideEnergySources PackagedTerminalHeatPump PackagedThermalStorageCoil Photovoltaics PhotovoltaicThermalCollectors PipeHeatTransfer Pipes PlantCentralGSHP PlantChillers PlantComponentTemperatureSources PlantCondLoopOperation PlantHeatExchangerFluidToFluid PlantLoadProfile PlantLoopEquip PlantLoopSolver PlantManager PlantPipingSystemsManager PlantPressureSystem PlantUtilities PlantValves PollutionModule PondGroundHeatExchanger PoweredInductionUnits Psychrometrics Pumps PurchasedAirManager RefrigeratedCase ReportSizingManager ReturnAirPathManager RoomAirModelManager RoomAirModelUserTempPattern RootFinder RuntimeLanguageProcessor ScheduleManager SetPointManager SimAirServingZones SimulationManager SingleDuct SizingManager SolarCollectors SolarReflectionManager SolarShading SortAndStringUtilities SplitterComponent SQLiteProcedures SQLiteProcedures StandardRatings SteamBaseboardRadiator SteamCoils SurfaceGeometry SurfaceGroundHeatExchanger SystemAvailabilityManager SystemReports TARCOGArgs TARCOGCommon TARCOGDeflection TARCOGGasses90 TARCOGGassesParams TARCOGMain TARCOGOutput TARCOGParams TarcogShading ThermalChimney ThermalComfort ThermalEN673Calc ThermalISO15099Calc TranspiredCollector UFADManager UnitHeater UnitVentilator UserDefinedComponents VariableSpeedCoils vectors VentilatedSlab WaterCoils WaterManager WaterThermalTanks WatertoAirHeatPump WatertoAirHeatPumpSimple WaterUse WeatherManager WindowAC WindowComplexManager WindowEquivalentLayer WindowManager WindTurbine ZoneAirLoopEquipmentManager ZoneContaminantPredictorCorrector ZoneDehumidifier ZoneEquipmentManager ZonePlenum ZoneTempPredictorCorrector