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) | :: | Delt | |||
integer, | intent(in) | :: | I | |||
integer, | intent(in) | :: | Lay | |||
integer, | intent(in) | :: | Surf | |||
real(kind=r64), | intent(in), | DIMENSION(:) | :: | T | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | TT | ||
real(kind=r64), | intent(in), | DIMENSION(:) | :: | Rhov | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | RhoT | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | RH | ||
real(kind=r64), | intent(in), | DIMENSION(:) | :: | TD | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | TDT | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | EnthOld | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | EnthNew | ||
real(kind=r64), | intent(inout), | DIMENSION(:) | :: | TDreport |
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 InteriorBCEqns(Delt,I,Lay,Surf,T,TT,Rhov,RhoT,RH,TD,TDT,EnthOld,EnthNew,TDReport)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Liesen
! DATE WRITTEN November, 2003
! MODIFIED B. Griffith, P. Tabares, May 2011, add first order fully implicit, bug fixes, cleanup
! November 2011 P. Tabares fixed problems with adiabatic walls/massless walls
! November 2011 P. Tabares fixed problems PCM stability problems
! RE-ENGINEERED C. O. Pedersen 2006
! PURPOSE OF THIS SUBROUTINE:
! Calculate the heat transfer at the node on the surfaces inside face (facing zone)
! METHODOLOGY EMPLOYED:
! <description>
! REFERENCES:
! na
! USE STATEMENTS:
USE DataHeatBalFanSys, ONLY: Mat, ZoneAirHumRat, QHTRadSysSurf, QHWBaseboardSurf, QSteamBaseboardSurf, QElecBaseboardSurf
USE DataSurfaces, ONLY: HeatTransferModel_CondFD
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: Delt ! Time Increment
INTEGER, INTENT(IN) :: I ! Node Index
INTEGER, INTENT(IN) :: Lay ! Layer Number for Construction
INTEGER, INTENT(IN) :: Surf ! Surface number
REAL(r64),DIMENSION(:), INTENT(In) :: T !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF (Old).
REAL(r64),DIMENSION(:), INTENT(InOut) :: TT !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF (New).
REAL(r64),DIMENSION(:), INTENT(In) :: Rhov !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF.
REAL(r64),DIMENSION(:), INTENT(InOut) :: RhoT !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF.
REAL(r64),DIMENSION(:), INTENT(In) :: TD !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF.
REAL(r64),DIMENSION(:), INTENT(InOut) :: TDT !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF.
REAL(r64),DIMENSION(:), INTENT(InOut) :: RH !INSIDE SURFACE TEMPERATURE OF EACH HEAT TRANSFER SURF.
REAL(r64),DIMENSION(:), INTENT(InOut) :: EnthOld ! Old Nodal enthalpy
REAL(r64),DIMENSION(:), INTENT(InOut) :: EnthNew ! New Nodal enthalpy
REAL(r64),DIMENSION(:), INTENT(InOut) :: TDreport ! Temperature value from previous HeatSurfaceHeatManager titeration's value
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: NetLWRadToSurfFD !Net interior long wavelength radiation to surface from other surfaces
REAL(r64) :: QRadSWInFD !Short wave radiation absorbed on inside of opaque surface
REAL(r64) :: QHtRadSysSurfFD ! Current radiant heat flux at a surface due to the presence of high temperature radiant heaters
Real(r64) :: QHWBaseboardSurfFD ! Current radiant heat flux at a surface due to the presence of hot water baseboard heaters
Real(r64) :: QSteamBaseboardSurfFD ! Current radiant heat flux at a surface due to the presence of steam baseboard heaters
Real(r64) :: QElecBaseboardSurfFD ! Current radiant heat flux at a surface due to the presence of electric baseboard heaters
REAL(r64) :: QRadThermInFD !Thermal radiation absorbed on inside surfaces
REAL(r64) :: Delx
REAL(r64), PARAMETER :: IterDampConst = 5.0d0 ! Damping constant for inside surface temperature iterations. Only used for massless (R-value only) Walls
INTEGER :: ConstrNum
INTEGER :: MatLay
INTEGER :: IndVarCol
INTEGER :: DepVarCol
REAL(r64) :: kto
REAL(r64) :: kt1
REAL(r64) :: kt
REAL(r64) :: Cp
REAL(r64) :: Cpo
REAL(r64) :: RhoS
REAL(r64) :: Tia
REAL(r64) :: Rhovi
REAL(r64) :: hmassi
REAL(r64) :: hconvi
REAL(r64) :: Rlayer
REAL(r64) :: SigmaRLoc
REAL(r64) :: SigmaCLoc
REAL(r64) :: QNetSurfInside
ConstrNum = Surface(surf)%Construction
SigmaRLoc = SigmaR(ConstrNum)
SigmaCLoc = SigmaC(ConstrNum)
!Set the internal conditions to local variables
NetLWRadToSurfFD = NetLWRadToSurf(surf)
QRadSWInFD = QRadSWInAbs(surf)
QHtRadSysSurfFD = QHtRadSysSurf(surf)
QHWBaseboardSurfFD = QHWBaseboardSurf(surf)
QSteamBaseboardSurfFD = QSteamBaseboardSurf(surf)
QElecBaseboardSurfFD = QElecBaseboardSurf(surf)
QRadThermInFD = QRadThermInAbs(Surf)
!Boundary Conditions from Simulation for Interior
hconvi = HConvInFD(surf)
hmassi = HMassConvInFD(surf)
Tia = Mat(Surface(Surf)%Zone)
rhovi = RhoVaporAirIn(surf)
!++++++++++++++++++++++++++++++++++++++++++++++++++++++
! Do all the nodes in the surface Else will switch to SigmaR,SigmaC
IF (Surface(Surf)%HeatTransferAlgorithm == HeatTransferModel_CondFD) THEN
MatLay = Construct(ConstrNum)%LayerPoint(Lay)
! Set Thermal Conductivity. Can be constant, simple linear temp dep or multiple linear segment temp function dep.
kto = Material(MatLay)%Conductivity ! 20C base conductivity
kt1 = MaterialFD(MatLay)%tk1 ! linear coefficient (normally zero)
kt = kto + kt1*((TDT(I)+TDT(i-1))/2.d0 - 20.d0)
IF( SUM(MaterialFD(MatLay)%TempCond(1:3,2)) >= 0.0d0) THEN ! Multiple Linear Segment Function
DepVarCol= 2 ! thermal conductivity
IndVarCol=1 !temperature
! Use average of surface and first node temp for determining k
kt = terpld(MaterialFD(MatLay)%numTempCond,MaterialFD(MatLay)%TempCond,(TDT(I)+TDT(I-1))/2.0d0 ,IndVarCol,DepVarCol)
ENDIF
RhoS = Material(MatLay)%Density
Cpo = Material(MatLay)%SpecHeat
Cp = Cpo ! Will be changed if PCM
Delx = ConstructFD(ConstrNum)%Delx(Lay)
!Calculate the Dry Heat Conduction Equation
Rlayer = Material(MatLay)%Resistance
If (Material(MatLay)%ROnly .or. Material(MatLay)%Group == 1 ) THEN ! R Layer or Air Layer
! Use algebraic equation for TDT based on R
IF (Surface(Surf)%ExtBoundCond > 0 .and. i==1) THEN !this is for an adiabatic partition
TDT(I)=(NetLWRadToSurfFD*Rlayer+QHtRadSysSurfFD*Rlayer + QHWBaseboardSurfFD*Rlayer + QSteamBaseboardSurfFD*Rlayer + &
QElecBaseboardSurfFD*Rlayer + QRadSWInFD*Rlayer + QRadThermInFD*Rlayer + &
TDT(I+1) + hconvi*Rlayer*Tia+TDreport(I)*IterDampConst*Rlayer)/(1.0d0 + hconvi*Rlayer+IterDampConst*Rlayer)
ELSE ! regular wall
TDT(I)=(NetLWRadToSurfFD*Rlayer+QHtRadSysSurfFD*Rlayer + QHWBaseboardSurfFD*Rlayer + QSteamBaseboardSurfFD*Rlayer + &
QElecBaseboardSurfFD*Rlayer + QRadSWInFD*Rlayer + QRadThermInFD*Rlayer + &
TDT(I-1) + hconvi*Rlayer*Tia+TDreport(I)*IterDampConst*Rlayer)/(1.0d0 + hconvi*Rlayer+IterDampConst*Rlayer)
ENDIF
IF ((TDT(I) > MaxSurfaceTempLimit) .OR. &
(TDT(I) < MinSurfaceTempLimit) ) THEN
TDT(I) = Max(MinSurfaceTempLimit,Min(MaxSurfaceTempLimit,TDT(I))) ! +++++ Limit Check
! CALL CheckFDSurfaceTempLimits(I,TDT(I))
ENDIF
ELSE ! Regular or PCM
IF( Sum(MaterialFD(MatLay)%TempEnth(1:3,2)) >= 0.0d0) THEN ! phase change material, Use TempEnth Data
DepVarCol= 2 ! enthalpy
IndVarCol=1 !temperature
EnthOld(I) =terpld(MaterialFD(MatLay)%numTempEnth,MaterialFD(MatLay)%TempEnth,TD(I),IndVarCol,DepVarCol)
EnthNew(I) =terpld(MaterialFD(MatLay)%numTempEnth,MaterialFD(MatLay)%TempEnth,TDT(I),IndVarCol,DepVarCol)
IF (ABS(EnthNew(I)-EnthOld(I)) <= smalldiff .or. ABS(TDT(I)-TD(I)) <= smalldiff) THEN
Cp = Cpo
ELSE
Cp = MAX(Cpo,(EnthNew(I) -EnthOld(I))/(TDT(I)-TD(I)))
END IF
ELSE ! Not phase change material
Cp= Cpo
END IF ! Phase change material check
IF (Surface(Surf)%ExtBoundCond > 0 .and. i==1) THEN !this is for an adiabatic or interzone partition
SELECT CASE (CondFDSchemeType)
CASE (CrankNicholsonSecondOrder)
! Adams-Moulton second order
TDT(I)=(2.d0*Delt*Delx*NetLWRadToSurfFD + 2.d0*Delt*Delx*QHtRadSysSurfFD + 2.d0*Delt*Delx*QHWBaseboardSurfFD + &
2.d0*Delt*Delx*QSteamBaseboardSurfFD + 2.d0*Delt*Delx*QElecBaseboardSurfFD + &
2.d0*Delt*Delx*QRadSWInFD + 2.d0*Delt*Delx*QRadThermInFD - &
Delt*Delx*hconvi*TD(I) - Delt*kt*TD(I) + Cp*Delx**2*RhoS*TD(I) + &
Delt*kt*TD(I+1) + Delt*kt*TDT(I+1) + 2.d0*Delt*Delx*hconvi*Tia)/ &
(Delt*Delx*hconvi + Delt*kt + Cp*Delx**2*RhoS)
CASE (FullyImplicitFirstOrder)
! Adams-Moulton First order
TDT(I)=(2.d0*Delt*Delx*NetLWRadToSurfFD + 2.d0*Delt*Delx*QHtRadSysSurfFD + 2.d0*Delt*Delx*QHWBaseboardSurfFD + &
2.d0*Delt*Delx*QSteamBaseboardSurfFD + 2.d0*Delt*Delx*QElecBaseboardSurfFD + &
2.d0*Delt*Delx*QRadSWInFD + 2.d0*Delt*Delx*QRadThermInFD + &
Cp*Delx**2*RhoS*TD(I) + 2.d0*Delt*kt*TDT(I+1) + 2.d0*Delt*Delx*hconvi*Tia)/ &
(2.d0*Delt*Delx*hconvi + 2.d0*Delt*kt + Cp*Delx**2*RhoS)
END SELECT
ELSE ! for regular or interzone walls
SELECT CASE (CondFDSchemeType)
CASE (CrankNicholsonSecondOrder)
TDT(I)=(2.d0*Delt*Delx*NetLWRadToSurfFD + 2.d0*Delt*Delx*QHtRadSysSurfFD + 2.d0*Delt*Delx*QHWBaseboardSurfFD + &
2.d0*Delt*Delx*QSteamBaseboardSurfFD + 2.d0*Delt*Delx*QElecBaseboardSurfFD + &
2.d0*Delt*Delx*QRadSWInFD + 2.d0*Delt*Delx*QRadThermInFD - &
Delt*Delx*hconvi*TD(I) - Delt*kt*TD(I) + Cp*Delx**2*RhoS*TD(I) + &
Delt*kt*TD(I-1) + Delt*kt*TDT(I-1) + 2.d0*Delt*Delx*hconvi*Tia)/ &
(Delt*Delx*hconvi + Delt*kt + Cp*Delx**2*RhoS)
CASE (FullyImplicitFirstOrder)
TDT(I)=(2.d0*Delt*Delx*NetLWRadToSurfFD + 2.d0*Delt*Delx*QHtRadSysSurfFD + 2.d0*Delt*Delx*QHWBaseboardSurfFD + &
2.d0*Delt*Delx*QSteamBaseboardSurfFD + 2.d0*Delt*Delx*QElecBaseboardSurfFD + &
2.d0*Delt*Delx*QRadSWInFD + 2.d0*Delt*Delx*QRadThermInFD + &
Cp*Delx**2*RhoS*TD(I) + 2.d0*Delt*kt*TDT(I-1) + 2.d0*Delt*Delx*hconvi*Tia)/ &
(2.d0*Delt*Delx*hconvi + 2.d0*Delt*kt + Cp*Delx**2*RhoS)
END SELECT
ENDIF
IF ((TDT(I) > MaxSurfaceTempLimit) .OR. &
(TDT(I) < MinSurfaceTempLimit) ) THEN
TDT(I) = Max(MinSurfaceTempLimit,Min(MaxSurfaceTempLimit,TDT(I))) ! +++++ Limit Check
! CALL CheckFDSurfaceTempLimits(I,TDT(I))
ENDIF
! TDT(I) = Max(MinSurfaceTempLimit,Min(MaxSurfaceTempLimit,TDT(I))) ! +++++ Limit Check
! Pass inside conduction Flux [W/m2] to DataHeatBalanceSurface array
! OpaqSurfInsFaceConductionFlux(Surf)= (TDT(I-1)-TDT(I))*kt/Delx
END IF ! Regular or R layer
END IF ! End of Regular node or SigmaR SigmaC option
QNetSurfInside= - (NetLWRadToSurfFD + QHtRadSysSurfFD + QRadSWInFD + QRadThermInFD + QHWBaseboardSurfFD + &
QSteamBaseboardSurfFD+QElecBaseboardSurfFD+hconvi*(-TDT(I) + Tia))
! note -- no change ref: CR8575
!feb2012 QNetSurfInside=NetLWRadToSurfFD + QHtRadSysSurfFD + QRadSWInFD + QRadThermInFD + QHWBaseboardSurfFD + &
!feb2012 QSteamBaseboardSurfFD+QElecBaseboardSurfFD+hconvi*(-TDT(I) + Tia)
! Pass inside conduction Flux [W/m2] to DataHeatBalanceSurface array
OpaqSurfInsFaceConductionFlux(Surf)= QNetSurfInside
! QFluxZoneToInSurf(Surf) = QNetSurfInside
OpaqSurfInsFaceConduction(Surf)=QNetSurfInside*Surface(Surf)%Area !for reporting as in CTF, PT
RETURN
END SUBROUTINE InteriorBCEqns