Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | SurfNum | |||
integer, | intent(in) | :: | iter | |||
real(kind=r64), | intent(out) | :: | VGap | |||
real(kind=r64), | intent(inout) | :: | TGapNew | |||
real(kind=r64), | intent(out) | :: | TGapOutlet | |||
real(kind=r64), | intent(out) | :: | hcv | |||
real(kind=r64), | intent(out) | :: | QConvGap |
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 ExtOrIntShadeNaturalFlow(SurfNum,iter,VGap,TGapNew,TGapOutlet,hcv,QConvGap)
! SUBROUTINE INFORMATION:
! AUTHOR F. Winkelmann
! DATE WRITTEN December 2000
! MODIFIED June 2001: add window blinds
! May 2006 (RR): add exterior window screens
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Called by SolveForWindowTemperatures for windows that have an interior
! or exterior blind or shade in place.
! Solves for air flow in gap between glass and shade/blind.
! Finds temperature of gap air and coefficient for convective heat transfer
! from glass to gap air and shade/blind to gap air.
! METHODOLOGY EMPLOYED:
! Based on ISO/DIS 15099, "Thermal Performance of Windows, Doors and Shading Devices --
! Detailed Calculations," 1/12/2000, Chapter 7, "Shading Devices."
! REFERENCES:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: SurfNum ! Surface number
INTEGER, INTENT (IN) :: iter ! Iteration number for glass heat balance calculation
REAL(r64), INTENT (OUT) :: VGap ! Air velocity in glass-shade/blind gap (m/s)
REAL(r64), INTENT (INOUT) :: TGapNew ! Current-iteration average air temp in glass-shade/blind gap (K)
REAL(r64), INTENT (OUT) :: TGapOutlet ! Temperature of air leaving glass-shade/blind gap at top for upward
REAL(r64), INTENT (OUT) :: hcv ! Convection coefficient from gap glass or shade to gap air (W/m2-K)
REAL(r64), INTENT (OUT) :: QConvGap ! Convective heat gain from glass-shade/blind gap for interior shade (W)
! air flow or bottom for downward air flow (K)
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ConstrNumSh ! Shaded construction number
INTEGER :: MatNumSh ! Material number of shade/blind layer
INTEGER :: nglassfaces ! Number of glass faces in contruction
REAL(r64) :: TGapInlet ! Temperature of air entering glass-shade/blind gap at bottom for upward
! air flow or top for downward air flow (K)
REAL(r64) :: TGlassFace ! Temperature of glass surface facing glass-shade/blind gap (K)
REAL(r64) :: TShadeFace ! Temperature of shade surface facing glass-shade/blind gap (K)
REAL(r64) :: hGapStill ! Still-air glass-shade/blind gap conduction/convection coeff (W/m2-K)
REAL(r64) :: TGapOld ! Previous-iteration average air temp in glass-shade/blind gap (K)
REAL(r64) :: GapHeight ! Vertical length of glass-shade/blind gap (m)
REAL(r64) :: GapDepth ! Distance from shade to glass (m)
REAL(r64) :: RhoAir ! Density of glass-shade/blind gap air at a temperature of TGapOld (kg/m3)
REAL(r64) :: RhoTRef ! Density of glass-shade/blind air at reference temp = KelvinConv (kg/m3)
REAL(r64) :: ViscAir ! Viscosity of glass-shade/blind gap air at a temperature of TGapOld (kg/m3)
REAL(r64) :: AGap ! Cross sectional area of glass-shade/blind gap (m2); for vertical window, this
! is in horizontal plane normal to window.
REAL(r64) :: ATopGap, ABotGap ! Area of the top and bottom openings (m2)
REAL(r64) :: ALeftGap, ARightGap ! Area of the left and right openings (m2)
REAL(r64) :: AHolesGap ! Area of the holes in the shade (assumed homogeneously
! distributed) (m2)
REAL(r64) :: ATopLRH,ABotLRH ! Intermediate variables
REAL(r64) :: AEqInlet, AEqOutlet ! Equivalent inlet and outlet opening areas (m2)
REAL(r64) :: Zinlet, Zoutlet ! Inlet and outlet pressure loss factors
REAL(r64) :: AVGap ! Coeff. of VGap**2 term in pressure balance equation
REAL(r64) :: BVGap ! Coeff. of VGap term in pressure balance equation
REAL(r64) :: CVGap ! VGap-independent term in pressure balance equation
REAL(r64) :: GapHeightChar ! Characteristic height of the gap air temperature profile (m)
REAL(r64) :: TAve ! Average of TGlass and TShade (K)
!REAL(r64) :: AirProps(8) ! Air properties
INTEGER :: TotGaps ! Glass/glass gaps + glass-shade/blind gap
REAL(r64) :: con ! Gap conductivity and derivative
REAL(r64) :: gr ! glass-shade/blind gap Grashof number
REAL(r64) :: pr ! glass-shade/blind gap Prandtl number
REAL(r64) :: nu ! glass-shade/blind gap Nusselt number
INTEGER :: ShadeFlag ! Shading flag
INTEGER :: BlNum ! Blind number
! Air properties
! Dens dDens/dT Con dCon/dT Vis dVis/dT Prandtl dPrandtl/dT
!DATA AirProps / 1.29, -0.4e-2, 2.41e-2, 7.6e-5, 1.73e-5, 1.0e-7, 0.72, 1.8e-3 /
ConstrNumSh = SurfaceWindow(SurfNum)%ShadedConstruction
IF(SurfaceWindow(SurfNum)%StormWinFlag==1) ConstrNumSh = Surface(SurfNum)%StormWinShadedConstruction
ShadeFlag = SurfaceWindow(SurfNum)%ShadingFlag
nglassfaces = 2*Construct(ConstrNumSh)%TotGlassLayers
TotGaps = Construct(ConstrNumSh)%TotGlassLayers
IF(ShadeFlag == IntShadeOn .OR. ShadeFlag == IntBlindOn) THEN ! Interior shade or blind
MatNumSh = Construct(ConstrNumSh)%LayerPoint(nglassfaces)
TGapInlet = tin
TGlassFace = thetas(nglassfaces)
TShadeFace = thetas(nglassfaces+1)
ELSE ! Exterior shade, screen or blind
MatNumSh = Construct(ConstrNumsh)%LayerPoint(1)
TGapInlet = tout
TGlassFace = thetas(1)
TShadeFace = thetas(nglassfaces+2)
END IF
TAve = 0.5d0*(TGlassFace + TShadeFace)
IF(iter == 0) THEN
TGapOld = 0.5d0*(TAve + TGapInlet)
ELSE
TGapOld = TGapNew
END IF
! Conductance of gap between glass and shade assuming gap is sealed
CALL WindowGasConductance(TGlassFace,TShadeFace,TotGaps,con,pr,gr)
CALL NusseltNumber(SurfNum,TGlassFace,TShadeFace,TotGaps,gr,pr,nu)
hGapStill = con/gap(TotGaps)*nu
! For near-horizontal windows (i.e., no more than 5 deg from horizontal) assume
! there is no air flow thru gap
IF(ABS(Surface(SurfNum)%SinTilt) < 0.0872d0) THEN
VGap = 0.0d0
hcv = 2.d0*hGapStill
QConvGap = 0.0d0
TGapNew = TAve
TGapOutlet = TAve
RETURN
END IF
GapHeight = Surface(SurfNum)%Height
IF(ShadeFlag == IntShadeOn .OR. ShadeFlag == ExtShadeOn .OR. ShadeFlag == ExtScreenOn) THEN
! Shade or Screen on
GapDepth = Material(MatNumSh)%WinShadeToGlassDist
AGap = GapDepth * Surface(SurfNum)%Width
ATopGap = Material(MatNumSh)%WinShadeTopOpeningMult * AGap
ABotGap = Material(MatNumSh)%WinShadeBottomOpeningMult * AGap
ALeftGap = Material(MatNumSh)%WinShadeLeftOpeningMult * GapHeight * GapDepth
ARightGap = Material(MatNumSh)%WinShadeRightOpeningMult * GapHeight * GapDepth
AHolesGap = Material(MatNumSh)%WinShadeAirFlowPermeability * GapHeight * Surface(SurfNum)%Width
ELSE
! Blind on
BlNum = SurfaceWindow(SurfNum)%BlindNumber
GapDepth = Blind(BlNum)%BlindToGlassDist
AGap = GapDepth * Surface(SurfNum)%Width
ATopGap = Blind(BlNum)%BlindTopOpeningMult * AGap
ABotGap = Blind(BlNum)%BlindBottomOpeningMult * AGap
ALeftGap = Blind(BlNum)%BlindLeftOpeningMult * GapHeight * GapDepth
ARightGap = Blind(BlNum)%BlindRightOpeningMult * GapHeight * GapDepth
AHolesGap = SurfaceWindow(SurfNum)%BlindAirFlowPermeability * GapHeight * Surface(SurfNum)%Width
END IF
RhoAir = AirProps(1) + AirProps(2)*(TGapOld-TKelvin)
ViscAir = AirProps(5) + AirProps(6)*(TGapOld-TKelvin)
! The factor 12 in the next line is based on the solution of steady laminar flow between fixed
! parallel plates given in Sec. 6.9.1 of Fundamentals of Fluid Mechanics, Munson/Young/Okishi, Third Edition
! Update, John Wiley & Sons, 1998; ISO 15099 has 8 for this factor, which is for flow through a tube.
BVGap = 12.d0*ViscAir*GapHeight/(GapDepth**2)
! Adding 0.000001 and 0.000002 in the following gives ATopLRH = ABotLRH =
! 0.25*(ALeftGap + ARightGap + AHolesGap) when ABotGap = ATopGap = 0.0 (shade/blind sealed at
! bottom and top but possibly open at left side, right side and/or in-shade/blind)
ATopLRH = 0.5d0*((ATopGap+0.000001d0)/(ABotGap+ATopGap+0.000002d0))*(ALeftGap + ARightGap + AHolesGap)
ABotLRH = 0.5d0*((ABotGap+0.000001d0)/(ABotGap+ATopGap+0.000002d0))*(ALeftGap + ARightGap + AHolesGap)
IF(TGapOld > TGapInlet) THEN
AEqInlet = ABotGap + ATopLRH
AEqOutlet = ATopGap + ABotLRH
ELSE
AEqOutlet = ABotGap + ATopLRH
AEqInlet = ATopGap + ABotLRH
END IF
! Adding 0.000001 in the following gives very large value of Zinlet for AEqInlet = 0 and
! very large value of Zoutlet for AEqInlet = 0; this gives VGap close to zero, as required
! when there is no inlet and/or outlet for air. This then reduces to the
! case of a completely sealed shade, in which hcv = 2*hGapStill and QConvGap = 0.
Zinlet = (AGap/(0.6d0*AEqInlet+0.000001d0)-1.d0)**2
Zoutlet = (AGap/(0.6d0*AEqOutlet+0.000001d0)-1.d0)**2
AVGap = 0.5d0*RhoAir*(1+Zinlet+Zoutlet)
RhoTRef = AirProps(1)*TKelvin
CVGap = RhoTRef*9.81d0*GapHeight*Surface(SurfNum)%SinTilt* &
(TGapOld-TGapInlet)/(TGapOld*TGapInlet)
! Solution of quadratic equation in VGap
VGap = (SQRT(BVGap**2 + ABS(4.d0*AVGap*CVGap)) - BVGap)/(2.d0*AVGap)
hcv = 2.d0*hGapStill + 4.d0*VGap
GapHeightChar = RhoAir * 1008.d0 * GapDepth * VGap/(2.d0*hcv)
! The following avoids divide by zero and exponential underflow
IF(GapHeightChar == 0.0d0) THEN
TGapOutlet = TAve
ELSE IF((GapHeight/GapHeightChar) > 15.d0) THEN
TGapOutlet = TAve
ELSE
TGapOutlet = TAve - (TAve-TGapInlet)*EXP(-GapHeight/GapHeightChar)
END IF
TGapNew = TAve - (GapHeightChar/GapHeight) * (TGapOutlet-TGapInlet)
! Convective heat flow from gap to room air for interior shade or blind
IF(ShadeFlag == IntShadeOn .OR. ShadeFlag == IntBlindOn) THEN
RhoAir = AirProps(1) + AirProps(2)*(TGapNew-TKelvin)
QConvGap = RhoAir * AGap * VGap * 1008.d0 * (TGapOutlet - TGapInlet)
! Exclude convection to gap due to divider, if present; divider convection handled
! separately in CalcWinFrameAndDividerTemps
QConvGap = QConvGap * 0.5d0 * (1.d0 + Surface(SurfNum)%Area/(Surface(SurfNum)%Area+SurfaceWindow(SurfNum)%DividerArea))
END IF
RETURN
END SUBROUTINE ExtOrIntShadeNaturalFlow