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) | :: | ZoneNum |
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 SetSurfHBDataForTempDistModel(ZoneNum)
! SUBROUTINE INFORMATION:
! AUTHOR Brent Griffith
! DATE WRITTEN August 2005,Feb. 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! map data from air domain back to surface domain for each zone
! collects code couples to remote data structures
! METHODOLOGY EMPLOYED:
! sets values in Heat balance variables
!
! REFERENCES:
! na
! USE STATEMENTS:
USE DataEnvironment, ONLY : OutBaroPress
USE DataLoopNode, ONLY : Node
USE DataSurfaces, ONLY : Surface, AdjacentAirTemp, ZoneMeanAirTemp, SurfaceWindow, &
AirFlowWindow_Destination_ReturnAir
USE DataHeatBalance, ONLY : Zone, TempEffBulkAir, ZoneIntGain, RefrigCaseCredit
USE DataZoneEquipment, ONLY : ZoneEquipConfig
USE DataHeatBalFanSys, ONLY : MAT, ZT, TempZoneThermostatSetpoint, TempTstatAir, SysDepZoneLoads, &
ZoneLatentGain
USE InputProcessor, ONLY : FindItem
USE Psychrometrics, ONLY:PsyHFnTdbW, PsyCpAirFnWTdb, PsyRhoAirFnPbTdbW, PsyHgAirFnWTdb
USE InternalHeatGains, ONLY : SumAllReturnAirConvectionGains, SumAllReturnAirLatentGains
USE DataHVACGlobals, ONLY : RetTempMax, RetTempMin
USE DataGlobals, ONLY : ZoneSizingCalc
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ZoneNum ! index number for the specified zone
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: SurfFirst ! index number of the first surface in the zone
INTEGER :: SurfLast
REAL(r64) :: qretair ! Heat to return air from lights
REAL(r64) :: cpair ! Air heat capacity [J/kg-K]
REAL(r64) :: TempRetAir ! Return air temperature [C]
REAL(r64) :: TempZoneAir ! Zone air temperature [C]
INTEGER :: ReturnNode ! Node number of controlled zone's return air
INTEGER :: ZoneNode ! Node number of controlled zone
INTEGER :: SurfNum ! Surface number
REAL(r64) :: MassFlowRA ! Return air mass flow [kg/s]
REAL(r64) :: FlowThisTS ! Window gap air mass flow [kg/s]
REAL(r64) :: WinGapFlowtoRA ! Mass flow to return air from all airflow windows in zone [kg/s]
REAL(r64) :: WinGapFlowTtoRA ! Sum of mass flow times outlet temp for all airflow windows in zone [(kg/s)-C]
REAL(r64) :: WinGapTtoRA ! Temp of outlet flow mixture to return air from all airflow windows in zone [C]
REAL(r64) :: H2OHtOfVap ! Heat of vaporization of water (W/kg)
REAL(r64) :: RhoAir ! Density of air (Kg/m3)
REAL(r64) :: ZoneMult
REAL(r64) :: SumRetAirLatentGainRate
! FLOW:
SurfFirst = Zone(ZoneNum)%SurfaceFirst
SurfLast = Zone(ZoneNum)%SurfaceLast
! set air system leaving node conditions
! this is not so easy. THis task is normally done in CalcZoneLeavingConditions
! but efforts to do this update there were not succesful.
! Need to revisit how to best implement this. Ended up taking code from CalcZoneLeavingConditions
! ZoneNum is already equal to ActualZoneNum , changed block of source
IF (AirPatternZoneInfo(ZoneNum)%ZoneNodeID /= 0) THEN
! the zone system node should get the conditions leaving the zone (but before return air heat gains are added).
Node(AirPatternZoneInfo(ZoneNum)%ZoneNodeID)%Temp = AirPatternZoneInfo(ZoneNum)%Tleaving
ENDIF
IF( AirPatternZoneInfo(ZoneNum)%ReturnAirNodeID /= 0) THEN
!BEGIN BLOCK of code from CalcZoneLeavingConditions*********************************
ReturnNode = AirPatternZoneInfo(ZoneNum)%ReturnAirNodeID
ZoneNode = AirPatternZoneInfo(ZoneNum)%ZoneNodeID
ZoneMult = Zone(ZoneNum)%Multiplier * Zone(ZoneNum)%ListMultiplier
!RETURN AIR HEAT GAIN from the Lights statement; this heat gain is stored in
! Add sensible heat gain from refrigerated cases with under case returns
CALL SumAllReturnAirConvectionGains(ZoneNum, QRetAir)
CpAir = PsyCpAirFnWTdb(Node(ZoneNode)%HumRat, Node(ZoneNode)%Temp)
! Need to add the energy to the return air from lights and from airflow windows. Where the heat
! is added depends on if there is system flow or not. If there is system flow the heat is added
! to the Zone Return Node. If there is no system flow then the heat is added back to the zone in the
! Correct step through the SysDepZoneLoads variable.
MassFlowRA = Node(ReturnNode)%MassFlowRate / ZoneMult
TempZoneAir = AirPatternZoneInfo(ZoneNum)%Tleaving ! key difference from
TempRetAir = TempZoneAir
WinGapFlowtoRA = 0.0d0
WinGapTtoRA = 0.0d0
WinGapFlowTtoRA = 0.0d0
DO SurfNum = Zone(ZoneNum)%SurfaceFirst,Zone(ZoneNum)%SurfaceLast
IF(SurfaceWindow(SurfNum)%AirFlowThisTS > 0.0d0 .AND. &
SurfaceWindow(SurfNum)%AirflowDestination == AirFlowWindow_Destination_ReturnAir) THEN
FlowThisTS = PsyRhoAirFnPbTdbW(OutBaroPress,SurfaceWindow(SurfNum)%TAirFlowGapOutlet, Node(ZoneNode)%HumRat) * &
SurfaceWindow(SurfNum)%AirFlowThisTS * Surface(SurfNum)%Width
WinGapFlowtoRA = WinGapFlowtoRA + FlowThisTS
WinGapFlowTtoRA = WinGapFlowTtoRA + FlowThisTS * SurfaceWindow(SurfNum)%TAirFlowGapOutlet
END IF
END DO
IF(WinGapFlowtoRA > 0.0d0) WinGapTtoRA = WinGapFlowTtoRA / WinGapFlowtoRA
IF (.NOT. Zone(ZoneNum)%NoHeatToReturnAir) THEN
IF(MassFlowRA > 0.0d0) Then
IF(WinGapFlowtoRA > 0.0d0) THEN
! Add heat-to-return from window gap airflow
IF(MassFlowRA >= WinGapFlowtoRA) THEN
TempRetAir = (WinGapFlowTtoRA + (MassFlowRA-WinGapFlowtoRA)*TempZoneAir)/MassFlowRA
ELSE
! All of return air comes from flow through airflow windows
TempRetAir = WinGapTtoRA
! Put heat from window airflow that exceeds return air flow into zone air
SysDepZoneLoads(ZoneNum) = SysDepZoneLoads(ZoneNum) + &
(WinGapFlowToRA - MassFlowRA) * CpAir*(WinGapTtoRA - TempZoneAir)
END IF
END IF
! Add heat-to-return from lights
TempRetAir = TempRetAir + QRetAir/(MassFlowRA * CpAir)
IF (TempRetAir > RetTempMax) THEN
Node(ReturnNode)%Temp = RetTempMax
IF (.not. ZoneSizingCalc) THEN
SysDepZoneLoads(ZoneNum) = SysDepZoneLoads(ZoneNum) + CpAir*MassFlowRA*(TempRetAir-RetTempMax)
END IF
ELSE IF (TempRetAir < RetTempMin) THEN
Node(ReturnNode)%Temp = RetTempMin
IF (.not. ZoneSizingCalc) THEN
SysDepZoneLoads(ZoneNum) = SysDepZoneLoads(ZoneNum) + CpAir*MassFlowRA*(TempRetAir-RetTempMin)
END IF
ELSE
Node(ReturnNode)%Temp = TempRetAir
END IF
ELSE ! No return air flow
! Assign all heat-to-return from window gap airflow to zone air
IF(WinGapFlowToRA > 0.0d0) &
SysDepZoneLoads(ZoneNum) = SysDepZoneLoads(ZoneNum) + &
WinGapFlowToRA * CpAir * (WinGapTtoRA - TempZoneAir)
! Assign all heat-to-return from lights to zone air
IF(QRetAir > 0.0d0) &
SysDepZoneLoads(ZoneNum) = SysDepZoneLoads(ZoneNum) + QRetAir
Node(ReturnNode)%Temp = Node(ZoneNode)%Temp
END IF
ELSE
Node(ReturnNode)%Temp = Node(ZoneNode)%Temp
END IF
! Update the rest of the Return Air Node conditions, if the return air system exists!
Node(ReturnNode)%Press = Node(ZoneNode)%Press
H2OHtOfVap = PsyHgAirFnWTdb(Node(ZoneNode)%HumRat,Node(ReturnNode)%Temp)
RhoAir = PsyRhoAirFnPbTdbW(OutBaroPress,Node(ReturnNode)%Temp,Node(ZoneNode)%HumRat)
! Include impact of under case returns for refrigerated display cases when updateing return node
! humidity ratio
IF (.NOT. Zone(ZoneNum)%NoHeatToReturnAir) THEN
IF (MassFlowRA > 0) THEN
CALL SumAllReturnAirLatentGains(ZoneNum, SumRetAirLatentGainRate)
Node(ReturnNode)%HumRat = Node(ZoneNode)%HumRat + (SumRetAirLatentGainRate / &
(H2OHtOfVap * MassFlowRA))
ELSE
! If no mass flow rate exists, include the latent HVAC case credit with the latent Zone case credit
Node(ReturnNode)%HumRat = Node(ZoneNode)%HumRat
RefrigCaseCredit(ZoneNum)%LatCaseCreditToZone = RefrigCaseCredit(ZoneNum)%LatCaseCreditToZone + &
RefrigCaseCredit(ZoneNum)%LatCaseCreditToHVAC
! shouldn't the HVAC term be zeroed out then?
CALL SumAllReturnAirLatentGains(ZoneNum, SumRetAirLatentGainRate)
ZoneLatentGain(ZoneNum) = ZoneLatentGain(ZoneNum) + SumRetAirLatentGainRate
END IF
ELSE
Node(ReturnNode)%HumRat = Node(ZoneNode)%HumRat
RefrigCaseCredit(ZoneNum)%LatCaseCreditToZone = RefrigCaseCredit(ZoneNum)%LatCaseCreditToZone + &
RefrigCaseCredit(ZoneNum)%LatCaseCreditToHVAC
! shouldn't the HVAC term be zeroed out then?
CALL SumAllReturnAirLatentGains(ZoneNum, SumRetAirLatentGainRate)
ZoneLatentGain(ZoneNum) = ZoneLatentGain(ZoneNum) + SumRetAirLatentGainRate
END IF
Node(ReturnNode)%Enthalpy = PsyHFnTdbW(Node(ReturnNode)%Temp,Node(ReturnNode)%HumRat)
!END BLOCK of code from CalcZoneLeavingConditions*********************************
ENDIF
! set exhaust node leaving temp if present
If (Allocated(AirPatternZoneInfo(ZoneNum)%ExhaustAirNodeID)) THEN
! Do I= 1, size(AirPatternZoneInfo(ZoneNum)%ExhaustAirNodeID) (array assignment instead of do loop)
Node(AirPatternZoneInfo(ZoneNum)%ExhaustAirNodeID)%Temp = AirPatternZoneInfo(ZoneNum)%Texhaust
! ENDDO
ENDIF
! set thermostat reading for air system .
TempTstatAir(ZoneNum) = AirPatternZoneInfo(ZoneNum)%Tstat
! set results for all surface (note array assignments instead of looping)
TempEffBulkAir(SurfFirst:SurfLast) = AirPatternZoneInfo(ZoneNum)%surf%TadjacentAir
! set flag for reference air temperature mode
Surface(SurfFirst:SurfLast)%TAirRef = AdjacentAirTemp
RETURN
END SUBROUTINE SetSurfHBDataForTempDistModel