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 | :: | ConstrNum | ||||
integer | :: | WinterSummerFlag | ||||
real(kind=r64) | :: | NominalConductance | ||||
real(kind=r64) | :: | SHGC | ||||
real(kind=r64) | :: | TSolNorm | ||||
real(kind=r64) | :: | TVisNorm | ||||
integer | :: | ErrFlag |
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 CalcNominalWindowCond (ConstrNum,WinterSummerFlag,NominalConductance,SHGC,TSolNorm,TVisNorm,ErrFlag)
! SUBROUTINE INFORMATION:
! AUTHOR F. Winkelmann
! DATE WRITTEN September 2000
! MODIFIED Oct 2000, FW: add solar heat gain coefficient
! June 2001, FW: account for blinds; change summer outside air
! temp from 35.0C to 31.7C to correspond to ASHRAE value
! Feb 2003, FW: add comments that this routine is not called for
! between-glass shade/blind constructions.
! May 2006, RR: account for screens
! Oct 2007, LKL: change temps to match Window 5 values
! Feb 2009, BG: Changes for CR7682 (SHGC)
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates nominal center-of-glass U-value and solar heat gain coefficient
! (SHGC) of a window construction for ASHRAE winter and summer conditions.
!
! Winter:
! Inside air temperature = 21.C (69.80F)
! Outside air temperature = -18C (-.4F)
! Windspeed = 5.5 m/s (12.3 mph)
! No solar radiation
! Replaced Winter:
! Inside air temperature = 21.1C (70F)
! Outside air temperature = -17.8C (0F)
! Windspeed = 6.71 m/s (15 mph)
! No solar radiation
!
! Summer:
! Inside air temperature = 24C (75.2F)
! Outside air temperature = 32C (89.6F)
! Windspeed = 2.8 m/s (6.2 mph)
! 783 W/m2 (248 Btu/h-ft2) incident beam solar radiation normal to glazing
! Replaced Summer:
! Inside air temperature = 24C (75.2F) ! BG changed again Feb. 2009 by 0.1 (per Window5 team)
! Outside air temperature = 31.7C (89F)
! Windspeed = 3.35 m/s (7.5 mph)
! 783 W/m2 (248 Btu/h-ft2) incident beam solar radiation normal to glazing
!
! The window's inside surround is assumed to be a black body at the inside air temp.
! The window's outside surround is assumed t be a black body at the outside air temp.
!
! Note that in this routine we use a value of 26 W/m2 for the outside convective
! air film conductance for 5.5 m/s (12.3 mph) wind speed.
! This is the value used in Window 5 and is also the value for which the center-of-glass
! conductances in the EnergyPlus window construction reference data set were calculated.
! However, in the time step loop we will have different values of outside film
! conductance depending on that time step's wind speed, wind direction, surface-to-air temp difference,
! etc.(see subroutine InitExteriorConvectionCoeff).
!
! This routine will return an error and exit for window constructions with between-glass shade or blind
! until a method is worked out to determine the nominal conductance and SHGC in this case.
!
! If an interior or exterior shade or blind is present in the construction,
! the conductance calculation does not include the effect of the shade or blind.
! This is because in this case the conductance depends on the natural convective
! air flow in the shade/glass, screen/glass or blind/glass channel, which in turn is highly dependent
! on window height and other parameters that are not part of the construction definition.
! Therefore, the reported conductance value will be too high for windows with a tightly fitting
! shade, screen or blind with a relatively high thermal resistance.
!
! For SHGC calculation, all solar absorbed by interior blind or shade is assumed
! to go into zone air. (This is not true in general; the fraction of this absorbed solar that
! is conducted back out is accounted for in the time-step glazing calculation.)
!
! For CR 7682, the SHGC calculations were changed to model the absorbed solar arriving at the middle of the layer
! rather than at the outer face of the layer. The resistances changed by one half the glazing layer, or 0.5/scon(n).
! (CR 7682 also changed WindowTempsForNominalCond to include absorbed solar, a bigger change)
!
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: POLYF, InterpBlind, InterpSlatAng, InterpProfSlatAng, BlindBeamBeamTrans
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: ConstrNum ! Construction number
INTEGER :: WinterSummerFlag ! 1=winter, 2=summer
REAL(r64) :: NominalConductance ! Nominal center-of-glass conductance, including air films
REAL(r64) :: SHGC ! Nominal center-of-glass solar heat gain coefficient for
! normal incidence beam solar radiation
REAL(r64) :: TSolNorm ! Overall beam solar transmittance at normal incidence
REAL(r64) :: TVisNorm ! Overall beam visible transmittance at normal incidence
INTEGER :: ErrFlag ! Error flag
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: TotLay ! Total number of layers in a construction
! (sum of solid layers and gap layers)
INTEGER :: TotGlassLay ! Total number of glass layers in a construction
INTEGER :: Lay ! Layer number
INTEGER :: LayPtr ! Material number for a layer
INTEGER :: IGlass ! glass layer number (1,2,3,...)
INTEGER :: IGap ! Gap layer number (1,2,...)
INTEGER :: IMix ! Gas component loop index for gap gas mixture
INTEGER :: ICoeff ! Gas property coefficient index
REAL(r64) :: BeamSolarInc ! Incident beam radiation at zero angle of incidence (W/m2)
REAL(r64) :: hOutRad,hInRad ! Radiative conductance of outside and inside airfilm [W/m2-K]
REAL(r64) :: rOut, rIn ! Combined radiative and conductive outside and inside film
! resistance [m2-K/W]
REAL(r64) :: hgap(5) ! Conductive gap conductance [W/m2-K]
REAL(r64) :: hGapTot(5) ! Combined radiative and conductive gap conductance [W/m2-K]
REAL(r64) :: Rbare ! Nominal center-of-glass resistance without air films [m2-K/W]
INTEGER :: ShadeFlag ! Shading flag
REAL(r64) :: ShadeRes ! Thermal resistance of shade
INTEGER :: MatOutside ! Material number of outside layer of construction
INTEGER :: MatInside ! Material number of inside layer of construction
INTEGER :: MatShade ! Material number of shade layer
REAL(r64) :: AbsBeamNorm(5) ! Beam absorptance at normal incidence for each glass layer
REAL(r64) :: AbsBeamShadeNorm ! Shade solar absorptance at normal incidence
INTEGER :: ConstrNum1 ! Construction counter
INTEGER :: ConstrNumBare ! Construction without shading device
INTEGER :: BlNum ! Blind number
INTEGER :: ScNum ! Screen number
LOGICAL :: VarSlats ! True if slats in blind are variable angle
REAL(r64) :: SlatAng ! Slat angle (rad)
INTEGER :: LayPtrSh ! Layer pointer of blind
REAL(r64) :: TBmBm,TBmBmVis ! Bare glass normal incidence beam-beam transmittance
REAL(r64) :: TBlBmBm ! Normal incidence blind beam-beam transmittance
REAL(r64) :: TScBmBm, TScBmBmVis ! Screen incident beam-beam transmittance
REAL(r64) :: TBmBmBl,TBmBmBlVis ! TBmBm * TBlBmBm, TBmBmVis * TBlBmBm
REAL(r64) :: RGlDiffBack,RGlDiffBackVis ! Bare glass back sol/vis reflectance
REAL(r64) :: RGlDiffFront,RGlDiffFrontVis ! Bare glass front sol/vis reflectance
REAL(r64) :: RhoBlFront,RhoBlFrontVis ! Blind normal front beam-diffuse sol/vis reflectance
REAL(r64) :: RhoBlBack,RhoBlBackVis ! Blind normal back beam-diffuse sol/vis reflectance
REAL(r64) :: RScBack,RScBackVis ! Screen back beam-diffuse sol/vis reflectance (same as front)
REAL(r64) :: AbsBlFront ! Blind normal front beam solar absorptance
REAL(r64) :: AbsBlBack ! Blind normal back beam solar absorptance
REAL(r64) :: RhoBlDiffFront,RhoBlDiffFrontVis ! Blind front diffuse-diffuse sol/vis reflectance
REAL(r64) :: AbsBlDiffFront ! Blind front diffuse solar absorptance
REAL(r64) :: AbsBlDiffBack ! Blind back diffuse solar absorptance
REAL(r64) :: RGlFront,RGlFrontVis ! Bare glass normal front beam sol/vis reflectance
REAL(r64) :: RhoBlDiffBack,RhoBlDiffBackVis ! Blind back diffuse-diffuse sol/vis reflectance
REAL(r64) :: RScDifBack,RScDifBackVis ! Screen back diffuse-diffuse sol/vis reflectance (doesn't change with sun angle)
REAL(r64) :: TBlBmDif,TBlBmDifVis ! Blind front normal beam-diffuse sol/vis transmittance
REAL(r64) :: TBlDifDif,TBlDifDifVis ! Blind front diffuse-diffuse sol/vis transmittance
REAL(r64) :: TScBmDif,TScBmDifVis ! Screen front beam-diffuse sol/vis transmittance
REAL(r64) :: TDif,TDifVis ! Bare glass diffuse sol/vis transmittance
REAL(r64) :: AGlDiffBack ! Back diffuse solar absorptance of a glass layer
ErrFlag = 0
TotLay = Construct(ConstrNum)%TotLayers
TotGlassLay = Construct(ConstrNum)%TotGlassLayers
ngllayer = TotGlassLay !Objexx:Uninit This routine needs to check/enforce 1<=ngllayer<=4
!EPTeam - believe that is done on input.
nglface = 2*ngllayer
tilt = 90.d0 ! Assume vertical window
IF(WinterSummerFlag == 1) THEN ! Winter
! LKL Oct 2007: According to Window5, Winter environmental conditions are:
tin = 294.15d0 ! Inside air temperature (69.8F, 21.C)
tout = 255.15d0 ! Outside air temperature (-.4F, -18C)
hcout = 26.d0 ! Outside convective film conductance for 5.5 m/s (12.3 mph) wind speed
! (the value used in Window 5)
! tin = 294.26 ! Inside air temperature (70F, 21.1C)
! tout = 255.35 ! Outside air temperature (0F, -17.8C)
! hcout = 25.47 ! Outside convective film conductance for 6.71 m/s (15 mph) wind speed
! ! (the value used in Window 4)
BeamSolarInc = 0.0d0
ELSE ! Summer
! LKL Oct 2007: According to Window5, Summer environmental conditions are:
!tin = 297.05d0 ! Inside air temperature (75.2F, 24C)
! BG Feb. 2009: According to Window5 Expert Christian Kohler, it is exactly 24C or 297.15
tin = 297.15d0
tout = 305.15d0 ! Outside air temperature (89.6F, 32C)
hcout = 15.d0 ! Outside convective film conductance for 2.8 m/s (6.2 mph) wind speed
! (the value used in Window 5)
! tin = 297.05 ! Inside air temperature (75F, 23.9C)
! !tout = 308.15 ! Outside air temperature (95F, 35.0C)
! ! Changed 6/20/01 by FCW to make consistent with Window 4 and 5.
! tout = 304.82 ! Outside air temperature (89F, 31.7C)
! hcout = 18.86 ! Outside convective film conductance for 3.35 m/s (7.5 mph) wind speed
! ! (average of Window 4 0 m/s and 6.71 m/s values)
BeamSolarInc = 783.0d0
END IF
! IR incident on inside of glazing (inside surround assumed to be
! a black body at inside air temperature)
rmir = sigma * tin**4
! IR incident on outside of glazing
! (outside surround is assumed to be a black body at outside air temperature)
outir = sigma * tout**4
! Determine whether construction has an exterior or interior shade or blind
ShadeFlag = NoShade
ShadeRes = 0.0d0
MatOutside = Construct(ConstrNum)%LayerPoint(1)
MatInside = Construct(ConstrNum)%LayerPoint(TotLay)
IF(Material(MatOutside)%Group == 2) THEN ! Exterior shade present
MatShade = MatOutside
ShadeFlag = ExtShadeOn
! Set glazing outside convection coefficient to Window 4 still-air value
hcout = 12.25d0
ELSE IF(Material(MatOutside)%Group == 7) THEN ! Exterior screen present
MatShade = MatOutside
ScNum = Material(MatShade)%ScreenDataPtr
! Orphaned constructs with exterior screen are ignored
IF(ScNum .GT. 0)ShadeFlag = ExtScreenOn
hcout = 12.25d0
ELSE IF(Material(MatOutside)%Group == 5) THEN ! Exterior blind present
MatShade = MatOutside
ShadeFlag = ExtBlindOn
BlNum = Material(MatShade)%BlindDataPtr
hcout = 12.25d0
ELSE IF(Material(MatInside)%Group == 2) THEN ! Interior shade present
MatShade = MatInside
ShadeFlag = IntShadeOn
ELSE IF(Material(MatInside)%Group == 5) THEN ! Interior blind present
MatShade = MatInside
BlNum = Material(MatShade)%BlindDataPtr
ShadeFlag = IntBlindOn
ELSE IF(TotGlassLay==2) THEN
IF(Material(Construct(ConstrNum)%LayerPoint(3))%Group == 2) ShadeFlag = BGShadeOn
IF(Material(Construct(ConstrNum)%LayerPoint(3))%Group == 5) ShadeFlag = BGBlindOn
ELSE IF(TotGlassLay==3) THEN
IF(Material(Construct(ConstrNum)%LayerPoint(5))%Group == 2) ShadeFlag = BGShadeOn
IF(Material(Construct(ConstrNum)%LayerPoint(5))%Group == 5) ShadeFlag = BGBlindOn
END IF
IF(ShadeFlag==BGShadeOn.OR.ShadeFlag==BGBlindOn) THEN
ErrFlag = 2
RETURN
END IF
TSolNorm = POLYF(1.0d0,Construct(ConstrNum)%TransSolBeamCoef(1:6))
TVisNorm = POLYF(1.0d0,Construct(ConstrNum)%TransVisBeamCoef(1:6))
AbsBeamShadeNorm = 0.0d0
IF(ShadeFlag == IntShadeOn .OR. ShadeFlag == ExtShadeOn) THEN ! Exterior or interior shade on
AbsBeamShadeNorm = POLYF(1.0d0,Construct(ConstrNum)%AbsBeamShadeCoef(1:6))
! Exterior blind or screen or interior blind on
ELSE IF(ShadeFlag == IntBlindOn .OR. ShadeFlag == ExtBlindOn .OR. ShadeFlag == ExtScreenOn) THEN
! Find unshaded construction that goes with this construction w/blind or screen
ConstrNumBare = 0
DO ConstrNum1 = 1, TotConstructs
IF(ConstrNum1 /= ConstrNum .AND. Construct(ConstrNum1)%TypeIsWindow .AND. &
Construct(ConstrNum1)%TotGlassLayers == Construct(ConstrNum1)%TotSolidLayers .AND. &
Construct(ConstrNum1)%TotGlassLayers == Construct(ConstrNum)%TotGlassLayers) THEN
! We have an unshaded window construction with the same number of glass layers as ConstrNum;
! see if the glass and gas layers match
ConstrNumBare = ConstrNum1
DO Lay = 1,Construct(ConstrNum1)%TotLayers
Layptr = Construct(ConstrNum1)%LayerPoint(Lay)
IF(ShadeFlag == IntBlindOn) THEN ! The shaded construction has an interior blind
LayPtrSh = Construct(ConstrNum)%LayerPoint(Lay)
ELSE ! The shaded construction has an exterior blind or screen
LayPtrSh = Construct(ConstrNum)%LayerPoint(Lay+1)
END IF
IF(LayPtrSh /= LayPtr) ConstrNumBare = 0
END DO
IF(ConstrNumBare /= 0) EXIT
END IF
END DO
IF(ConstrNumBare == 0) THEN
! No matching bare construction found for this construction with blind or screen
ErrFlag = 1
RETURN
END IF
TBmBm = POLYF(1.0d0,Construct(ConstrNumBare)%TransSolBeamCoef(1:6))
TBmBmVis = POLYF(1.0d0,Construct(ConstrNumBare)%TransVisBeamCoef(1:6))
IF(ShadeFlag == ExtScreenOn)THEN
! Don't need to call subroutine, use normal incident properties (SUBROUTINE CalcNominalWindowCond)
! Last call to CalcScreenTransmittance(ISurf) was done at direct normal angle (0,0) in CalcWindowScreenProperties
TScBmBm = SurfaceScreens(ScNum)%BmBmTrans
TScBmBmVis = SurfaceScreens(ScNum)%BmBmTransVis
TScBmDif = SurfaceScreens(ScNum)%BmDifTrans
TScBmDifVis = SurfaceScreens(ScNum)%BmDifTransVis
TDif = Construct(ConstrNumBare)%TransDiff
TDifVis = Construct(ConstrNumBare)%TransDiffVis
RScBack = SurfaceScreens(ScNum)%ReflectScreen
RScBackVis = SurfaceScreens(ScNum)%ReflectScreenVis
RScDifBack = SurfaceScreens(ScNum)%DifReflect
RScDifBackVis = SurfaceScreens(ScNum)%DifReflectVis
RGlFront = POLYF(1.0d0,Construct(ConstrNumBare)%ReflSolBeamFrontCoef(1:6))
RGlFrontVis = POLYF(1.0d0,Construct(ConstrNumBare)%ReflSolBeamFrontCoef(1:6))
RGlDiffFront = Construct(ConstrNumBare)%ReflectSolDiffFront
RGlDiffFrontVis = Construct(ConstrNumBare)%ReflectVisDiffFront
TSolNorm = TScBmBm * (TBmBm + TDif*RGlFront*RScBack/(1-RGlDiffFront*RScDifBack)) + &
TScBmDif*TDif/(1-RGlDiffFront*RScDifBack)
TVisNorm = TScBmBmVis * (TBmBmVis + TDifVis*RGlFrontVis*RScBackVis/(1-RGlDiffFrontVis*RScDifBackVis)) + &
TScBmDifVis*TDifVis/(1-RGlDiffFrontVis*RScDifBackVis)
ELSE
VarSlats = .FALSE.
IF(Blind(BlNum)%SlatAngleType == VariableSlats) VarSlats = .TRUE.
SlatAng = Blind(BlNum)%SlatAngle * DegToRadians
TBlBmBm = BlindBeamBeamTrans(0.0d0,SlatAng,Blind(BlNum)%SlatWidth,Blind(BlNum)%SlatSeparation, &
Blind(BlNum)%SlatThickness)
TBmBmBl = TBmBm * TBlBmBm
TBmBmBlVis = TBmBmVis * TBlBmBm
TBlBmDif = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolFrontBeamDiffTrans)
TBlBmDifVis = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%VisFrontBeamDiffTrans)
TDif = Construct(ConstrNumBare)%TransDiff
TDifVis = Construct(ConstrNumBare)%TransDiffVis
IF(ShadeFlag == IntBlindOn) THEN
RGlDiffBack = Construct(ConstrNumBare)%ReflectSolDiffBack
RGlDiffBackVis = Construct(ConstrNumBare)%ReflectVisDiffBack
RhoBlFront = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolFrontBeamDiffRefl)
RhoBlFrontVis = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%VisFrontBeamDiffRefl)
AbsBlFront = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolFrontBeamAbs)
RhoBlDiffFront = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%SolFrontDiffDiffRefl)
RhoBlDiffFrontVis = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%VisFrontDiffDiffRefl)
AbsBlDiffFront = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%SolFrontDiffAbs)
AbsBeamShadeNorm = TBmBm * (AbsBlFront + &
RhoBlFront*RGlDiffBAck*AbsBlDiffFront/(1.d0-RhoBlDiffFront*RGlDiffBack))
TBlDifDif = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%SolFrontDiffDiffTrans)
TBlDifDifVis = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%VisFrontDiffDiffTrans)
TSolNorm = TBmBm*( TBlBmBm + TBlBmDif + TBlDifDif*RhoBlFront*RGlDiffBack/(1.d0-RhoBlDiffFront*RGlDiffBack) )
! use of TBlBmBm here is correct, visible and IR transmittance are the same (reference deleted CR6925 on 3/20/2006)
TVisNorm = TBmBmVis*( TBlBmBm + TBlBmDifVis + TBlDifDifVis*RhoBlFrontVis*RGlDiffBackVis/ &
(1.d0-RhoBlDiffFrontVis*RGlDiffBackVis) )
END IF ! (IntBlind)
IF(ShadeFlag == ExtBlindOn) THEN
TBlBmBm = BlindBeamBeamTrans(0.0d0,SlatAng,Blind(BlNum)%SlatWidth,Blind(BlNum)%SlatSeparation, &
Blind(BlNum)%SlatThickness)
RGlFront = POLYF(1.0d0,Construct(ConstrNumBare)%ReflSolBeamFrontCoef(1:6))
RGlFrontVis = POLYF(1.0d0,Construct(ConstrNumBare)%ReflSolBeamFrontCoef(1:6))
AbsBlFront = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolFrontBeamAbs)
AbsBlBack = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolBackBeamAbs)
AbsBlDiffBack = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%SolBackDiffAbs)
RGlDiffFront = Construct(ConstrNumBare)%ReflectSolDiffFront
RGlDiffFrontVis = Construct(ConstrNumBare)%ReflectVisDiffFront
RhoBlDiffBack = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%SolBackDiffDiffRefl)
RhoBlDiffBackVis = InterpSlatAng(SlatAng,VarSlats,Blind(BlNum)%VisBackDiffDiffRefl)
RhoBlBack = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolBackBeamDiffRefl)
RhoBlBackVis = InterpProfSlatAng(0.0d0,SlatAng,VarSlats,Blind(BlNum)%SolBackBeamDiffRefl)
AbsBeamShadeNorm = AbsBlFront + AbsBlBack * RGlFront * TBlBmBm &
+ (AbsBlDiffBack*RGlDiffFront/(1.d0-RhoBlDiffBack*RGlDiffFront)) * &
(RGlFront*TBlBmBm*RhoBlBack + TBlBmDif)
RGlDiffFront = Construct(ConstrNumBare)%ReflectSolDiffFront
TSolNorm = TBlBmBm * (TBmBm + TDif*RGlFront*RhoBlBack/(1-RGlDiffFront*RhoBlDiffBack)) + &
TBlBmDif*TDif/(1.d0-RGlDiffFront*RhoBlDiffBack)
TVisNorm = TBlBmBm * (TBmBmVis + TDifVis*RGlFrontVis*RhoBlBackVis/(1-RGlDiffFrontVis*RhoBlDiffBackVis)) + &
TBlBmDifVis*TDifVis/(1.d0-RGlDiffFrontVis*RhoBlDiffBackVis)
END IF ! (ExtBlind)
END IF ! (Screen or Blind)
END IF ! (Shade, Blind, or Screen)
! Fill the layer properties needed for the thermal calculation.
! The layer and face numbering are as follows (for the triple glazing case):
! Glass layers are 1,2 and 3, where 1 is the outside (outside environment facing)
! layer and 3 is the inside (room-facing) layer;
! Faces (also called surfaces) are 1,2,3,4,5 and 6, where face 1 is the
! outside (front) face of glass layer 1, face 2 is the inside (back)
! face of glass layer 1, face 3 is the outer face of glass layer 2, face 4 is the
! inner face of glass layer 2, etc.
! Gap layers are 1 and 2, where gap layer 1 is between glass layers 1 and 2
! and gap layer 2 is between glass layers 2 and 3.
IGlass = 0
IGap = 0
DO Lay = 1,TotLay
LayPtr = Construct(ConstrNum)%LayerPoint(Lay)
IF(( Material(LayPtr)%Group == WindowGlass) .OR. (Material(LayPtr)%Group == WindowSimpleGlazing) ) THEN
IGlass = IGlass + 1
thick(IGlass) = Material(LayPtr)%Thickness
scon(IGlass) = Material(LayPtr)%Conductivity/Material(LayPtr)%Thickness
emis(2*IGlass-1) = Material(LayPtr)%AbsorpThermalFront
emis(2*IGlass) = Material(LayPtr)%AbsorpThermalBack
tir(2*IGlass-1) = Material(LayPtr)%TransThermal
tir(2*IGlass) = Material(LayPtr)%TransThermal
AbsBeamNorm(IGlass) = POLYF(1.0d0,Construct(ConstrNum)%AbsBeamCoef(IGlass,1:6))
IF(ShadeFlag == IntBlindOn) THEN ! Interior blind on
AbsBeamNorm(IGlass) = POLYF(1.0d0,Construct(ConstrNumBare)%AbsBeamCoef(IGlass,1:6))
AGlDiffBack = Construct(ConstrNumBare)%AbsDiffBack(IGlass)
AbsBeamNorm(IGlass) = AbsBeamNorm(IGlass) + TBmBm*AGlDiffBack*RhoBlFront/(1.d0-RhoBlFront*RGlDiffBack)
ELSE IF(ShadeFlag == ExtBlindOn) THEN ! Exterior blind on
AbsBeamNorm(IGlass) = POLYF(1.0d0,Construct(ConstrNumBare)%AbsBeamCoef(IGlass,1:6))
AbsBeamNorm(IGlass) = TBlBmBm*AbsBeamNorm(IGlass) + (TBlBmBm*RGlFront*RhoBlBack + TBlBmDif) * &
Construct(ConstrNumBare)%AbsDiff(IGlass)/(1.d0-RGlDiffFront*RhoBlDiffBack)
ELSE IF(ShadeFlag == ExtScreenOn) THEN ! Exterior screen on
AbsBeamNorm(IGlass) = POLYF(1.0d0,Construct(ConstrNumBare)%AbsBeamCoef(IGlass,1:6))
AbsBeamNorm(IGlass) = TScBmBm*AbsBeamNorm(IGlass) + (TScBmBm*RGlFront*RScBack + TScBmDif) * &
Construct(ConstrNumBare)%AbsDiff(IGlass)/(1.d0-RGlDiffFront*RScDifBack)
END IF
AbsRadGlassFace(2*IGlass-1) = 0.5d0*BeamSolarInc*AbsBeamNorm(IGlass)
AbsRadGlassFace(2*IGlass) = 0.5d0*BeamSolarInc*AbsBeamNorm(IGlass)
END IF
IF(Material(LayPtr)%Group == WindowGas .OR. Material(LayPtr)%Group == WindowGasMixture .OR. &
Material(LayPtr)%Group == ComplexWindowGap) THEN ! Gap layer
IGap = IGap + 1
!Simon: Need to re-reference gas data in casee of complex fenestration gap
IF(Material(LayPtr)%Group == ComplexWindowGap) THEN
LayPtr = Material(LayPtr)%GasPointer
END IF
gap(IGap) = Material(LayPtr)%Thickness
gnmix(IGap) = Material(LayPtr)%NumberOfGasesInMixture
DO IMix = 1,gnmix(IGap)
gwght(IGap,IMix) = Material(LayPtr)%GasWght(IMix)
gfract(IGap,IMix) = Material(LayPtr)%GasFract(IMix)
DO ICoeff = 1,3
gcon(IGap,IMix,ICoeff) = Material(LayPtr)%GasCon(IMix,ICoeff)
gvis(IGap,IMix,ICoeff) = Material(LayPtr)%GasVis(IMix,ICoeff)
gcp(IGap,IMix,ICoeff) = Material(LayPtr)%GasCp(IMix,ICoeff)
END DO
END DO
END IF
END DO
! Factors used in glass temperature solution
IF(ngllayer >= 2) THEN
A23P = -emis(3)/(1.0d0-(1.0d0-emis(2))*(1.0d0-emis(3)))
A32P = emis(2)/(1.0d0-(1.0d0-emis(2))*(1.0d0-emis(3)))
A23 = emis(2)*sigma*A23P
END IF
IF(ngllayer >= 3) THEN
A45P = -emis(5)/(1.0d0-(1.0d0-emis(4))*(1.0d0-emis(5)))
A54P = emis(4)/(1.0d0-(1.0d0-emis(4))*(1.0d0-emis(5)))
A45 = emis(4)*sigma*A45P
END IF
IF(ngllayer == 4) THEN
A67P = -emis(7)/(1.0d0-(1.0d0-emis(6))*(1.0d0-emis(7)))
A76P = emis(6)/(1.0d0-(1.0d0-emis(6))*(1.0d0-emis(7)))
A67 = emis(6)*sigma*A67P
END IF
thetas = 0.0d0
CALL WindowTempsForNominalCond(ConstrNum,hgap)
! Get center-of-glass conductance and solar heat gain coefficient
! including inside and outside air films
hOutRad = emis(1)*sigma*0.5d0*(tout+thetas(1))**3
rOut = 1.0d0/(hOutRad + hcout)
hInRad = emis(nglface)*sigma*0.5d0*(tin+thetas(nglface))**3
rIn = 1.0d0/(hInRad + hcin)
IF (.not. (ShadeFlag == IntShadeOn .OR. ShadeFlag == IntBlindOn)) AbsBeamShadeNorm=0.0d0
SELECT CASE(ngllayer)
CASE(1)
Rbare = 1.0D0/scon(1)
Rtot = rOut + Rbare + rIn
SHGC = AbsBeamNorm(1) * (rOut + (0.5d0/scon(1)))/Rtot ! BG changed for CR7682 (solar absorbed in middle of layer)
SHGC = SHGC + AbsBeamShadeNorm
SHGC = SHGC + TSolNorm
CASE(2)
hGapTot(1) = hgap(1) + ABS(A23)*0.5d0*(thetas(2)+thetas(3))**3
Rbare = 1.0D0/scon(1) + 1.0D0/hGapTot(1) + 1.0D0/scon(2)
Rtot = rOut + Rbare + rIn
SHGC = AbsBeamNorm(1)*(rOut + 0.5D0/scon(1))/Rtot &
+ AbsBeamNorm(2)*(rOut + 1.0D0/scon(1) + 1.0D0/hgapTot(1) + 0.5D0/scon(2) )/Rtot !CR7682
SHGC = SHGC + AbsBeamShadeNorm
SHGC = SHGC + TSolNorm
CASE(3)
hGapTot(1) = hgap(1) + ABS(A23)*0.5d0*(thetas(2)+thetas(3))**3
hGapTot(2) = hgap(2) + ABS(A45)*0.5d0*(thetas(4)+thetas(5))**3
Rbare = 1.0D0/scon(1) + 1.0D0/hGapTot(1) + 1.0D0/scon(2) + 1.0D0/hGapTot(2) + 1.0D0/scon(3)
Rtot = rOut + Rbare + rIn
SHGC = AbsBeamNorm(1)*(rOut + 0.5D0/scon(1))/Rtot &
+ AbsBeamNorm(2)*(rOut + 1.0D0/scon(1) + 1.0D0/hgapTot(1) + 0.5D0/scon(2) )/Rtot &
+ AbsBeamNorm(3)*(rOut + 1.0D0/scon(1) + 1.0D0/hgapTot(1) + 1.0D0/scon(2) + 1.0D0/hGapTot(2) + 0.5D0/scon(3) )/Rtot
SHGC = SHGC + AbsBeamShadeNorm
SHGC = SHGC + TSolNorm
CASE(4)
hGapTot(1) = hgap(1) + ABS(A23)*0.5d0*(thetas(2)+thetas(3))**3
hGapTot(2) = hgap(2) + ABS(A45)*0.5d0*(thetas(4)+thetas(5))**3
hGapTot(3) = hgap(3) + ABS(A67)*0.5d0*(thetas(6)+thetas(7))**3
Rbare = 1.0D0/scon(1) + 1.0D0/hGapTot(1) + 1.0D0/scon(2) + 1.0D0/hGapTot(2) + 1.0D0/scon(3) + &
1.0D0/hGapTot(3) + 1.0D0/scon(4)
Rtot = rOut + Rbare + rIn
SHGC = AbsBeamNorm(1)*(rOut + 0.5D0/scon(1))/Rtot &
+ AbsBeamNorm(2)*(rOut + 1.0D0/scon(1) + 1.0D0/hgapTot(1) + 0.5D0/scon(2) )/Rtot &
+ AbsBeamNorm(3)*(rOut + 1.0D0/scon(1) + 1.0D0/hgapTot(1) + 1.0D0/scon(2) + 1.0D0/hGapTot(2) + 0.5D0/scon(3) )/Rtot &
+ AbsBeamNorm(4)*(rOut + 1.0D0/scon(1) + 1.0D0/hgapTot(1) + 1.0D0/scon(2) + 1.0D0/hGapTot(2) + 1.0D0/scon(3) &
+ 1.0D0/hGapTot(3) + 0.5D0/scon(4) )/Rtot !CR7682
SHGC = SHGC + AbsBeamShadeNorm
SHGC = SHGC + TSolNorm
END SELECT
NominalConductance = 1.0D0/(rOut + Rbare + rIn) !Objexx:Uninit Rbare uninitialized if ngllayer>4
!EPTeam - again -- believe that is enforced in input
RETURN
END SUBROUTINE CalcNominalWindowCond