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 | :: | PipeType | ||||
integer, | intent(in) | :: | PipeHTNum | |||
logical, | intent(in) | :: | FirstHVACIteration |
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 InitPipesHeatTransfer(PipeType,PipeHTNum,FirstHVACIteration)
! SUBROUTINE INFORMATION:
! AUTHOR Simon Rees
! DATE WRITTEN July 2007
! MODIFIED L. Gu, 6/19/08, pipe wall heat capacity has metal layer only
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine Resets the elements of the data structure as necessary
! at the first step, and start of each call to simulated
! METHODOLOGY EMPLOYED:
! Check flags and update data structure
! REFERENCES:
! na
! USE STATEMENTS:
USE DataGlobals, ONLY : BeginSimFlag, BeginEnvrnFlag, PI, DayOfSim, HourOfDay,TimeStep, &
TimeStepZone, SecInHour, BeginTimeStepFlag
USE DataHVACGlobals, ONLY : SysTimeElapsed, TimeStepSys, ShortenTimeStepSys
USE DataEnvironment, ONLY : OutDryBulbTemp, GroundTemp, PubGroundTempSurface, PubGroundTempSurfFlag
USE DataLoopNode, ONLY : Node
USE DataHeatBalance, ONLY : TotConstructs, TotMaterials, Construct, Material
USE DataHeatBalFanSys, ONLY : MAT !average (mean) zone air temperature [C]
USE InputProcessor, ONLY : SameString
USE ScheduleManager, ONLY : GetCurrentScheduleValue
USE FluidProperties, ONLY : GetSpecificHeatGlycol,GetDensityGlycol
USE DataPlant, ONLY : PlantLoop, DemandSide, ScanPlantLoopsForObject
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: PipeType
INTEGER, INTENT(IN) :: PipeHTNum ! component number
LOGICAL, INTENT(IN) :: FirstHVACIteration ! component number
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: NumPipeSections = 20 ! Number of length nodes in Hanby model
INTEGER, PARAMETER :: NumberOfDepthNodes = 8 ! Number of nodes in the cartesian grid
INTEGER, PARAMETER :: MonthsInYear = 12 ! Number of months in the year
INTEGER, PARAMETER :: AvgDaysInMonth = 30 ! Average days in a month
INTEGER, PARAMETER :: DemandLoopSide = 1 ! Demand Loop side indicator
REAL(r64), PARAMETER :: LargeNumber = 9999.9d0 ! Large number (compared to temperature values)
REAL(r64), PARAMETER :: SecondsInHour = 3600.0d0 ! Number of seconds in hour
REAL(r64), PARAMETER :: HoursInDay = 24.0d0 ! Number of hours in day
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
LOGICAL,SAVE :: OneTimeInit = .TRUE. ! one time flag
REAL(r64) :: FirstTemperatures ! initial temperature of every node in pipe (set to inlet temp) [C]
INTEGER :: PipeNum ! number of pipes
INTEGER :: MonthIndex
INTEGER :: TimeIndex
INTEGER :: LengthIndex
INTEGER :: DepthIndex
INTEGER :: WidthIndex
REAL(r64) :: CurrentDepth
REAL(r64) :: CurTemp
REAL(r64) :: CurSimDay
INTEGER :: PlantLoopCtr
INTEGER :: LoopSideCtr
INTEGER :: BranchCtr
INTEGER :: CompCtr
LOGICAL :: PushArrays
LOGICAL :: errFlag
! Assign variable
CurSimDay = REAL(DayOfSim,r64)
! some useful module variables
InletNodeNum = PipeHT(PipeHTNum)%InletNodeNum
OutletNodeNum = PipeHT(PipeHTNum)%OutletNodeNum
MassFlowRate = Node(InletNodeNum)%MassFlowRate
InletTemp = Node(InletNodeNum)%Temp
! get some data only once
IF(OneTimeInit)THEN
errFlag=.false.
Do PipeNum =1,NumOfPipeHT
CALL ScanPlantLoopsForObject(PipeHT(PipeNum)%Name, &
PipeHT(PipeNum)%TypeOf, &
PipeHT(PipeNum)%LoopNum, &
PipeHT(PipeNum)%LoopSideNum, &
PipeHT(PipeNum)%BranchNum, &
PipeHT(PipeNum)%CompNum, &
errFlag=errFlag)
! 2010-03-15 ESL:
! The following code was in place because during the first implementation stage, bizarre MaxIters were found when
! heat transfer pipes were placed on demand sides
! Since then, a large number of plant and component upgrades were performed. As such, heat transfer pipes were
! re-tested on several locations of the demand side
! No problems were encountered placing the pipes on the demand side. This restriction is removed unless there are any
! problems encountered. If problems are encountered, it is expected that this restriction will still be avoided, and
! the proper fix implemented to allow the pipes to be placed on the demand side
!
! IF (PipeHT(PipeNum)%LoopSideNum == DemandSide) THEN
! CALL ShowSevereError('InitPipesHeatTransfer: Heat Transfer Pipe='//TRIM(PipeHT(PipeNum)%Name)//&
! ' was encountered on the demand side of loop: '//TRIM(PlantLoop(PipeHT(PipeNum)%LoopNum)%Name)//'.')
! CALL ShowContinueError('Due to simulation restrictions, heat transfer pipes are only allowed on supply sides.')
! CALL ShowFatalError('Preceding errors cause termination')
! END IF
IF (errFlag) CYCLE
!If there are any underground buried pipes, we must bring in data
IF(PipeHT(PipeNum)%EnvironmentPtr .EQ. GroundEnv)THEN
!If ground temp data was not brought in manually in GETINPUT,
! then we must get it from the surface ground temperatures
IF (PipeHT(PipeNum)%AvgAnnualManualInput .EQ. 0)THEN
IF (.NOT. PubGroundTempSurfFlag) THEN
CALL ShowFatalError('No Site:GroundTemperature:Shallow object found. This is required for a Pipe:Underground object.')
END IF
!Calculate Average Ground Temperature for all 12 months of the year:
PipeHT(PipeNum)%AvgGroundTemp = 0.0d0
Do MonthIndex = 1, MonthsInYear
PipeHT(PipeNum)%AvgGroundTemp = PipeHT(PipeNum)%AvgGroundTemp + PubGroundTempSurface(MonthIndex)
END Do
PipeHT(PipeNum)%AvgGroundTemp = PipeHT(PipeNum)%AvgGroundTemp / MonthsInYear
!Calculate Average Amplitude from Average:
PipeHT(PipeNum)%AvgGndTempAmp = 0.0d0
Do MonthIndex = 1, MonthsInYear
PipeHT(PipeNum)%AvgGndTempAmp = PipeHT(PipeNum)%AvgGndTempAmp + &
ABS(PubGroundTempSurface(MonthIndex) - PipeHT(PipeNum)%AvgGroundTemp)
END Do
PipeHT(PipeNum)%AvgGndTempAmp = PipeHT(PipeNum)%AvgGndTempAmp / MonthsInYear
!Also need to get the month of minimum surface temperature to set phase shift for Kusuda and Achenbach:
PipeHT(PipeNum)%MonthOfMinSurfTemp = 0
PipeHT(PipeNum)%MinSurfTemp = LargeNumber !Set high so that the first months temp will be lower and actually get updated
Do MonthIndex = 1, MonthsInYear
If (PubGroundTempSurface(MonthIndex) <= PipeHT(PipeNum)%MinSurfTemp) THEN
PipeHT(PipeNum)%MonthOfMinSurfTemp = MonthIndex
PipeHT(PipeNum)%MinSurfTemp = PubGroundTempSurface(MonthIndex)
END If
END Do
PipeHT(PipeNum)%PhaseShiftDays = PipeHT(PipeNum)%MonthOfMinSurfTemp * AvgDaysInMonth
ENDIF !End manual ground data input structure
ENDIF
END DO
IF (errFlag) THEN
CALL ShowFatalError('InitPipesHeatTransfer: Program terminated due to previous condition(s).')
ENDIF
! unset one-time flag
OneTimeInit = .FALSE.
END IF
! initialize temperatures by inlet node temp
IF((BeginSimFlag.AND. PipeHT(PipeHTNum)%BeginSimInit) .OR. (BeginEnvrnFlag .AND. PipeHT(PipeHTNum)%BeginSimEnvrn)) THEN
! For underground pipes, we need to re-init the cartesian array each environment
Do PipeNum =1,NumOfPipeHT
IF(PipeHT(PipeNum)%EnvironmentPtr.EQ.GroundEnv)THEN
Do TimeIndex = PreviousTimeIndex, TentativeTimeIndex
!Loop through all length, depth, and width of pipe to init soil temperature
Do LengthIndex = 1, PipeHT(PipeNum)%NumSections
Do DepthIndex = 1, PipeHT(PipeNum)%NumDepthNodes
Do WidthIndex = 1, PipeHT(PipeNum)%PipeNodeWidth
CurrentDepth = (DepthIndex - 1) * PipeHT(PipeNum)%dSregular
PipeHT(PipeNum)%T(TimeIndex, LengthIndex, DepthIndex, WidthIndex) = TBND(CurrentDepth, CurSimDay, PipeNum)
EndDo
EndDo
EndDo
EndDo
ENDIF
ENDDO
! We also need to re-init the Hanby arrays for all pipes, including buried
FirstTemperatures = 21.0d0 !Node(InletNodeNum)%Temp
PipeHT(PipeHTNum)%TentativeFluidTemp = FirstTemperatures
PipeHT(PipeHTNum)%FluidTemp = FirstTemperatures
PipeHT(PipeHTNum)%PreviousFluidTemp = FirstTemperatures
PipeHT(PipeHTNum)%TentativePipeTemp = FirstTemperatures
PipeHT(PipeHTNum)%PipeTemp = FirstTemperatures
PipeHT(PipeHTNum)%PreviousPipeTemp = FirstTemperatures
PipeHT(PipeHTNum)%PreviousSimTime = 0.0d0
DeltaTime = 0.0d0
OutletTemp = 0.0d0
EnvironmentTemp = 0.0d0
EnvHeatLossRate = 0.0d0
FluidHeatLossRate = 0.0d0
PipeHT(PipeHTNum)%BeginSimInit = .FALSE.
PipeHT(PipeHTNum)%BeginSimEnvrn = .FALSE.
END IF
IF (.NOT. BeginSimFlag) PipeHT(PipeHTNum)%BeginSimInit = .TRUE.
IF (.NOT. BeginEnvrnFlag) PipeHT(PipeHTNum)%BeginSimEnvrn = .TRUE.
! time step in seconds
DeltaTime = TimeStepSys*SecInHour
NumInnerTimeSteps = INT(DeltaTime / InnerDeltaTime)
! previous temps are updated if necessary at start of timestep rather than end
IF( (FirstHVACIteration .and. PipeHT(PipeHTNum)%FirstHVACupdateFlag) .or. &
(BeginEnvrnFlag .and. PipeHT(PipeHTNum)%BeginEnvrnupdateFlag) )THEN
!We need to update boundary conditions here, as well as updating the arrays
IF(PipeHT(PipeHTNum)%EnvironmentPtr.EQ.GroundEnv)THEN
! And then update Ground Boundary Conditions
Do TimeIndex = 1, TentativeTimeIndex
Do LengthIndex = 1, PipeHT(PipeHTNum)%NumSections
Do DepthIndex = 1, PipeHT(PipeHTNum)%NumDepthNodes
!Farfield boundary
CurrentDepth = (DepthIndex - 1) * PipeHT(PipeHTNum)%dSregular
CurTemp = TBND(CurrentDepth, CurSimDay, PipeHTNum)
PipeHT(PipeHTNum)%T(TimeIndex, LengthIndex, DepthIndex, 1) = CurTemp
EndDo
Do WidthIndex = 1, PipeHT(PipeHTNum)%PipeNodeWidth
!Bottom side of boundary
CurrentDepth = PipeHT(PipeHTNum)%DomainDepth
CurTemp = TBND(CurrentDepth, CurSimDay, PipeHTNum)
PipeHT(PipeHTNum)%T(TimeIndex, LengthIndex, PipeHT(PipeHTNum)%NumDepthNodes, WidthIndex) = CurTemp
EndDo
EndDo
EndDo
EndIf
! should next choose environment temperature according to coupled with air or ground
SELECT CASE (PipeHT(PipeHTNum)%EnvironmentPtr)
CASE(GroundEnv)
!EnvironmentTemp = GroundTemp
CASE(OutsideAirEnv)
EnvironmentTemp = OutDryBulbTemp
CASE(ZoneEnv)
EnvironmentTemp = MAT(PipeHT(PipeHTNum)%EnvrZonePtr)
CASE (ScheduleEnv)
EnvironmentTemp = GetCurrentScheduleValue(PipeHT(PipeHTNum)%EnvrSchedPtr)
CASE(None) !default to outside temp
EnvironmentTemp = OutDryBulbTemp
END SELECT
PipeHT(PipeHTNum)%BeginEnvrnupdateFlag = .false.
PipeHT(PipeHTNum)%FirstHVACupdateFlag = .false.
END IF
IF(.NOT. BeginEnvrnFlag) PipeHT(PipeHTNum)%BeginEnvrnupdateFlag = .true.
IF(.NOT. FirstHVACIteration) PipeHT(PipeHTNum)%FirstHVACupdateFlag = .true.
!Calculate the current sim time for this pipe (not necessarily structure variable, but it is ok for consistency)
PipeHT(PipeHTNum)%CurrentSimTime = (dayofSim-1)*24 + hourofday-1 + (timestep-1)*timestepZone + SysTimeElapsed
IF (ABS(PipeHT(PipeHTNum)%CurrentSimTime - PipeHT(PipeHTNum)%PreviousSimTime) > 1.0d-6) THEN
PushArrays = .TRUE.
PipeHT(PipeHTNum)%PreviousSimTime = PipeHT(PipeHTNum)%CurrentSimTime
ELSE
PushArrays = .FALSE. !Time hasn't passed, don't accept the tentative values yet!
END IF
IF (PushArrays) THEN
!If sim time has changed all values from previous runs should have been acceptable.
! Thus we will now shift the arrays from 2>1 and 3>2 so we can then begin
! to update 2 and 3 again.
IF (PipeHT(PipeHTNum)%EnvironmentPtr .EQ. GroundEnv) THEN
Do LengthIndex = 2, PipeHT(PipeHTNum)%NumSections
Do DepthIndex = 1, PipeHT(PipeHTNum)%NumDepthNodes
Do WidthIndex = 2, PipeHT(PipeHTNum)%PipeNodeWidth
!This will essentially 'accept' the tentative values that were calculated last iteration
! as the new officially 'current' values
PipeHT(PipeHTNum)%T(CurrentTimeIndex, LengthIndex, DepthIndex, WidthIndex) = &
PipeHT(PipeHTNum)%T(TentativeTimeIndex, LengthIndex, DepthIndex, WidthIndex)
EndDo
EndDo
EndDo
ENDIF
!Then update the Hanby near pipe model temperatures
PipeHT(PipeHTNum)%FluidTemp = PipeHT(PipeHTNum)%TentativeFluidTemp
PipeHT(PipeHTNum)%PipeTemp = PipeHT(PipeHTNum)%TentativePipeTemp
ELSE ! IF(.NOT. FirstHVACIteration)THEN
!If we don't have FirstHVAC, the last iteration values were not accepted, and we should
! not step through time. Thus we will revert our T(3,:,:,:) array back to T(2,:,:,:) to
! start over with the same values as last time.
Do LengthIndex = 2, PipeHT(PipeHTNum)%NumSections
Do DepthIndex = 1, PipeHT(PipeHTNum)%NumDepthNodes
Do WidthIndex = 2, PipeHT(PipeHTNum)%PipeNodeWidth
!This will essentially erase the past iterations and revert back to the correct values
PipeHT(PipeHTNum)%T(TentativeTimeIndex, LengthIndex, DepthIndex, WidthIndex) = &
PipeHT(PipeHTNum)%T(CurrentTimeIndex, LengthIndex, DepthIndex, WidthIndex)
EndDo
EndDo
EndDo
!Similarly for Hanby model arrays
PipeHT(PipeHTNum)%TentativeFluidTemp = PipeHT(PipeHTNum)%FluidTemp
PipeHT(PipeHTNum)%TentativePipeTemp = PipeHT(PipeHTNum)%PipeTemp
ENDIF
!This still catches even in winter design day
!Even though the loop eventually has no flow rate, it appears it initializes to a value, then converges to OFF
!Thus, this is called at the beginning of every time step once.
PipeHT(PipeHTNum)%FluidSpecHeat = GetSpecificHeatGlycol(PlantLoop(PipeHT(PipeHTNum)%LoopNum)%FluidName, &
InletTemp, &
PlantLoop(PipeHT(PipeHTNum)%LoopNum)%FluidIndex, &
'InitPipesHeatTransfer')
PipeHT(PipeHTNum)%FluidDensity = GetDensityGlycol(PlantLoop(PipeHT(PipeHTNum)%LoopNum)%FluidName, &
InletTemp, &
PlantLoop(PipeHT(PipeHTNum)%LoopNum)%FluidIndex,&
'InitPipesHeatTransfer')
! At this point, for all Pipe:Interior objects we should zero out the energy and rate arrays
PipeHTReport(PipeHTNum)%FluidHeatLossRate = 0.0d0
PipeHTReport(PipeHTNum)%FluidHeatLossEnergy = 0.0d0
PipeHTReport(PipeHTNum)%EnvironmentHeatLossRate = 0.0d0
PipeHTReport(PipeHTNum)%EnvHeatLossEnergy = 0.0d0
PipeHT(PipeHTNum)%ZoneHeatGainRate = 0.d0
FluidHeatLossRate = 0.0d0
EnvHeatLossRate = 0.0d0
OutletTemp = 0.0d0
IF(PipeHT(PipeHTNum)%FluidDensity .GT. 0.0d0) THEN
!The density will only be zero the first time through, which will be a warmup day, and not reported
VolumeFlowRate= MassFlowRate / PipeHT(PipeHTNum)%FluidDensity
ENDIF
RETURN
END SUBROUTINE InitPipesHeatTransfer