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(2) | |||
real(kind=r64), | intent(out) | :: | hcv(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 BetweenGlassShadeNaturalFlow(SurfNum,iter,VGap,TGapNew,hcv)
! SUBROUTINE INFORMATION:
! AUTHOR F. Winkelmann
! DATE WRITTEN December 2002
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Called by SolveForWindowTemperatures for windows that have a
! between-glass shade or blind in place.
! Solves for gas flow in the two gaps on either side of shade/blind.
! Finds average temperature of gas in the two gaps, and the coefficient
! for convective heat transfer from glass to gap gas and shade/blind to gap gas
! for the two gaps. The two gaps are assumed to have the same depth so that the
! gas velocity due to natural convection is the same in the two gaps.
!
! The Between-glass shade/blind is between the two glass layers of double glazing
! or between the two inner glass layers of triple glazing. The quadruple glazing
! case is not considered.
! 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 ! Gas velocity in gaps (m/s)
REAL(r64), INTENT (INOUT) :: TGapNew(2) ! Current-iteration average gas temp in gaps (K)
REAL(r64), INTENT (OUT) :: hcv(2) ! Convection coefficient from gap glass or shade to gap gas (W/m2-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
! In the following, "gaps" refer to the gaps on either side of the shade/blind
REAL(r64) :: TGlassFace(2) ! Temperature of glass surfaces facing gaps (K)
REAL(r64) :: TShadeFace(2) ! Temperature of shade surfaces facing gaps (K)
REAL(r64) :: hGapStill(2) ! Still-air conduction/convection coeffs for the gaps (W/m2-K)
REAL(r64) :: TGapOld(2) ! Previous-iteration average gas temp in gaps (K)
REAL(r64) :: GapHeight ! Vertical length of glass-shade/blind gap (m)
REAL(r64) :: GapDepth ! Distance from shade/blind to glass; assumed same for both gaps (m)
REAL(r64) :: RhoGas(2) ! Density of gap gas at a temperature of TGapOld (kg/m3)
REAL(r64) :: RhoTRef ! Density of gap gas at reference temp = KelvinConvK (kg/m3)
REAL(r64) :: ViscGas(2) ! Viscosity of gap gas at a temperature of TGapOld (kg/m3)
REAL(r64) :: RhoGasZero ! Gas density at KelvinConvK
REAL(r64) :: ViscGasZero ! Gas viscosity at KelvinConvK (not used)
REAL(r64) :: AGap ! Cross sectional area of gaps (m2); for vertical window, this
! is in horizontal plane normal to window.
REAL(r64) :: ATopGap, ABotGap ! Area of the top and bottom openings of shade/blind (m2)
REAL(r64) :: ALeftGap, ARightGap ! Area of the left and right openings of shade/blind (m2)
REAL(r64) :: AHolesGap ! Area of the holes in the shade/blind (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(2) ! Characteristic height of the gap gas temperature profile (m)
REAL(r64) :: EpsChar(2) ! EXP(-GapHeight/GapHeightChar(IGap))
REAL(r64) :: TAve(2) ! Average of TGlass and TShade for the gaps (K)
REAL(r64) :: con ! Gap gas conductivity and derivative
REAL(r64) :: gr ! Gap gas Grashof number
REAL(r64) :: pr ! Gap gas Prandtl number
REAL(r64) :: nu ! Gap gas Nusselt number
INTEGER :: ShadeFlag ! Shading flag
INTEGER :: BlNum ! Blind number
INTEGER :: IGap ! Gap counter; 1 = gap on outer side of shade/blind, 2 = gap on inner side.
INTEGER :: IGapInc ! Gap increment (0 or 1)
ConstrNumSh = Surface(SurfNum)%ShadedConstruction
ShadeFlag = SurfaceWindow(SurfNum)%ShadingFlag
nglassfaces = 2*Construct(ConstrNumSh)%TotGlassLayers
IF(Construct(ConstrNumSh)%TotGlassLayers == 2) THEN ! Double glazing
MatNumSh = Construct(ConstrNumSh)%LayerPoint(3)
IGapInc = 0
DO IGap = 1,2
TGlassFace(IGap) = thetas(IGap+1)
TShadeFace(IGap) = thetas(IGap+4)
END DO
ELSE ! Triple glazing
MatNumSh = Construct(ConstrNumSh)%LayerPoint(5)
IGapInc = 1
DO IGap = 1,2
TGlassFace(IGap) = thetas(IGap+3)
TShadeFace(IGap) = thetas(IGap+6)
END DO
END IF
DO IGap = 1,2
TAve(IGap) = 0.5d0*(TGlassFace(IGap) + TShadeFace(IGap))
IF(iter == 0) THEN
TGapOld(IGap) = TAve(IGap)
ELSE
TGapOld(IGap) = TGapNew(IGap)
END IF
! Conductance of gaps on either side of shade/blind assuming gaps are sealed
CALL WindowGasConductance(TGlassFace(IGap),TShadeFace(IGap),IGap+IGapInc,con,pr,gr)
CALL NusseltNumber(SurfNum,TGlassFace(IGap),TShadeFace(IGap),IGap+IGapInc,gr,pr,nu)
hGapStill(IGap) = con/gap(IGap+IGapInc)*nu
END DO
! 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
DO IGap = 1,2
hcv(IGap) = 2.d0*hGapStill(IGap)
TGapNew(IGap) = TAve(IGap)
END DO
RETURN
END IF
GapHeight = Surface(SurfNum)%Height
GapDepth = gap(1+IGapInc)
AGap = GapDepth * Surface(SurfNum)%Width
IF(ShadeFlag == BGShadeOn) THEN
! Shade on
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
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
DO IGap = 1,2
CALL WindowGasPropertiesAtTemp(TGapOld(IGap),IGap+IGapInc,RhoGas(IGap),ViscGas(IGap))
END DO
BVGap = 12.d0*(ViscGas(1)+ViscGas(2))*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)
AEqInlet = ABotGap + ATopLRH
AEqOutlet = ATopGap + ABotLRH
! 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*(RhoGas(1)+RhoGas(2))*(1.d0+Zinlet+Zoutlet)
CALL WindowGasPropertiesAtTemp(TKelvin,1+IGapInc,RhoGasZero,ViscGasZero)
RhoTRef = RhoGasZero*TKelvin
CVGap = RhoTRef*9.81d0*GapHeight*Surface(SurfNum)%SinTilt* &
(TGapOld(1)-TGapOld(2))/(TGapOld(1)*TGapOld(2))
! Solution of quadratic equation in VGap
VGap = (SQRT(BVGap**2 + ABS(4*AVGap*CVGap)) - BVGap)/(2*AVGap)
DO IGap = 1,2
hcv(IGap) = 2.d0*hGapStill(IGap) + 4.d0*VGap
GapHeightChar(IGap) = RhoGas(IGap) * 1008.d0 * GapDepth * VGap/(2.d0*hcv(IGap))
! The following avoids divide by zero and exponential underflow
IF(GapHeightChar(IGap) == 0.0d0) THEN
EpsChar(IGap) = 0.0d0
ELSE IF((GapHeight/GapHeightChar(IGap)) > 15.d0) THEN
EpsChar(IGap) = 0.0d0
ELSE
EpsChar(IGap) = EXP(-GapHeight/GapHeightChar(IGap))
END IF
END DO
TGapNew(1) = TAve(1) - (TAve(1)-TAve(2))*(GapHeightChar(1)/GapHeight) * &
(1-EpsChar(1))*(1-EpsChar(2))/(1-EpsChar(1)*EpsChar(2))
TGapNew(2) = TAve(2) - (TAve(2)-TAve(1))*(GapHeightChar(2)/GapHeight) * &
(1-EpsChar(1))*(1-EpsChar(2))/(1-EpsChar(1)*EpsChar(2))
RETURN
END SUBROUTINE BetweenGlassShadeNaturalFlow