Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer | :: | SurfNum | ||||
real(kind=r64) | :: | AbsRadShade(2) |
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 StartingWindowTemps(SurfNum,AbsRadShade)
! SUBROUTINE INFORMATION:
! AUTHOR F. Winkelmann
! DATE WRITTEN January 2000
! MODIFIED March 2003, FW: add rough calc of increase above ambient of
! initial shade/blind temperature when shade/blind deployed
! after having been off.
! Jan 2004, FW: take into account whether storm window was added
! or removed in the current time step.
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Initializes face temperature distribution prior to iteration
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: SurfNum ! Surface number
REAL(r64) :: AbsRadShade(2) ! Short-wave radiation absorbed by shade/blind faces
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64),PARAMETER :: hrad = 5.3d0 ! Typical radiative conductance (W/m2-K)
REAL(r64),PARAMETER :: resgap = 0.21d0 ! Typical gap resistance (m2-K/W)
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: i ! Face counter
INTEGER :: ShadeFlag ! Shading flag
REAL(r64) :: rguess(11) ! Combined radiative/convective resistance (m2-K/W) of
! inside or outside air film, or gap
REAL(r64) :: restot ! Total window resistance including outside
! and inside air films (m2-K/W)
REAL(r64) :: temdiff ! Inside/outside air temperature difference (K)
REAL(r64) :: ressum ! Resistance sum (m2-K/W)
INTEGER :: StormWinFlagPrevDay ! Previous time step value (day) of storm window flag
INTEGER :: StormWinFlagThisDay ! Current time step value (day) of storm window flag
INTEGER :: nglfacePrevDay ! Previous time step value (dya) of number of glass faces (may differ
! current time step value, nglface, if storm window was
! added or removed during the current time step).
StormWinFlagPrevDay = SurfaceWindow(SurfNum)%StormWinFlagPrevDay
StormWinFlagThisDay = SurfaceWindow(SurfNum)%StormWinFlag
IF(BeginEnvrnFlag .OR. (StormWinFlagThisDay /= StormWinFlagPrevDay)) THEN
! Guess values of glass face temperatures based on a simple resistance-network solution
! that (1) ignores short- and long-wave radiation (from lights and zone equipment) absorbed
! by the glass faces, and (2) assumes zero glass resistance. Absorbed solar is also ignored
! since the tests on BeginEnvrnFlag and storm window transition can be true only at midnight.
! Interaction with shade or blind, if one of these is present, is ignored. See below for
! separate calculation of shade/blind temperature.
rguess(1) = 1.0d0/(hcout+hrad)
rguess(nglface+1) = 1.0d0/(hcin+hrad)
do i = 2,nglface,2
rguess(i) = 1.0d0/scon(i/2)
if(i<nglface) rguess(i+1) = resgap
end do
restot = 0.0d0
do i = 1,nglface+1
restot = restot + rguess(i)
enddo
temdiff = tin - tout
if(abs(temdiff)<0.5d0) temdiff = 2.0d0
ressum = 0.0d0
do i = 1,nglface
ressum = ressum + rguess(i)
thetas(i) = (ressum/restot)*temdiff + tout
end do
ELSE
! Use previous time step values
do i = 1,nglface
thetas(i) = SurfaceWindow(SurfNum)%ThetaFace(i)
end do
END IF
! Initialize face temperatures of shade or blind, if present
ShadeFlag = SurfaceWindow(SurfNum)%ShadingFlag
if(SurfaceWindow(SurfNum)%ExtIntShadePrevTS==IntShadeOn.OR. &
SurfaceWindow(SurfNum)%ExtIntShadePrevTS==IntBlindOn.OR. &
SurfaceWindow(SurfNum)%ExtIntShadePrevTS==ExtShadeOn.OR. &
SurfaceWindow(SurfNum)%ExtIntShadePrevTS==ExtBlindOn.OR. &
SurfaceWindow(SurfNum)%ExtIntShadePrevTS==BGShadeOn .OR. &
SurfaceWindow(SurfNum)%ExtIntShadePrevTS==BGBlindOn) then
! Shade or blind is on during the previous TS; use previous-TS values of shade/blind face temps.
! Note that if shade or blind is NOT on in the current TS the following two
! temperature values, although calculated here, are not used. The shade/blind face numbers
! during the previous time step depend on whether a storm window glass layer was added to
! or removed from the window during the current time step.
nglfacePrevDay = nglface
IF(StormWinFlagPrevDay == 0 .AND. StormWinFlagThisDay == 1) nglfacePrevDay = nglface - 2
IF(StormWinFlagPrevDay == 1 .AND. StormWinFlagThisDay == 0) nglfacePrevDay = nglface + 2
thetas(nglface+1) = SurfaceWindow(SurfNum)%ThetaFace(nglfacePrevDay+1)
thetas(nglface+2) = SurfaceWindow(SurfNum)%ThetaFace(nglfacePrevDay+2)
else
! No shade or blind previous time step; guess starting values of shade/blind
! taking into account short- and long-wave radiation (from solar, lights and zone equipment)
! absorbed by shade/blind faces. Face temps are assumed to be the same and
! equal to shade/blind temp. For interior shade/blind, air temp on either side is
! assumed to be the same and equal to tin; for exterior blind it is assumed to be
! equal to tout. For between-glass shade/blind it is assumed to be equal to the
! average temperature of the adjacent glass faces.
if(ShadeFlag == IntShadeOn .OR. ShadeFlag == IntBlindOn) then
thetas(nglface+1) = tin + (AbsRadShade(1)+AbsRadShade(2))/(2*(hcin+hrad))
thetas(nglface+2) = thetas(nglface+1)
end if
if(ShadeFlag == ExtShadeOn .OR. ShadeFlag == ExtBlindOn) then
thetas(nglface+1) = tout + (AbsRadShade(1)+AbsRadShade(2))/(2*(hcout+hrad))
thetas(nglface+2) = thetas(nglface+1)
end if
if(ShadeFlag == BGShadeOn .OR. ShadeFlag == BGBlindOn) then
! Between-glass shade/blind allowed only for double and triple glazing.
! The factor 16.0 below is based on a combined convective/radiative heat transfer
! coefficient on either side of the shade/blind of 8.0 W/m2-K -- about 1.4 Btu/h-ft2-F.
if(nglface==4) then ! double glazing
thetas(nglface+1) = 0.5d0*(thetas(2)+thetas(3)) + (AbsRadShade(1)+AbsRadShade(2))/16.0d0
thetas(nglface+2) = thetas(nglface+1)
else ! triple glazing
thetas(nglface+1) = 0.5d0*(thetas(4)+thetas(5)) + (AbsRadShade(1)+AbsRadShade(2))/16.0d0
thetas(nglface+2) = thetas(nglface+1)
end if
end if
end if
return
END SUBROUTINE StartingWindowTemps