Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer | :: | MaterNum |
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 SetupSimpleWindowGlazingSystem(MaterNum)
! SUBROUTINE INFORMATION:
! AUTHOR B. Griffith
! DATE WRITTEN January 2009
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Convert simple window performance indices into all the properties needed to
! describe a single, equivalent glass layer
! METHODOLOGY EMPLOYED:
! The simple window indices are converted to a single materal layer using a "block model"
!
! REFERENCES:
! draft paper by Arasteh, Kohler, and Griffith
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: MaterNum
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: Riw = 0.0D0 ! thermal resistance of interior film coefficient under winter conditions (m2-K/W)
REAL(r64) :: Row = 0.0D0 ! theraml resistance of exterior film coefficient under winter conditions (m2-K/W)
REAL(r64) :: Rlw = 0.0D0 ! thermal resistance of block model layer (m2-K/W)
REAL(r64) :: Ris = 0.0D0 ! thermal resistance of interior film coefficient under summer conditions (m2-K/W)
REAL(r64) :: Ros = 0.0D0 ! theraml resistance of exterior film coefficient under summer conditions (m2-K/W)
REAL(r64) :: InflowFraction = 0.0d0 ! inward flowing fraction for SHGC, intermediate value non dimensional
REAL(r64) :: SolarAbsorb = 0.0d0 ! solar aborptance
LOGICAL :: ErrorsFound = .false.
REAL(r64) :: TsolLowSide = 0.0d0 ! intermediate solar transmission for interpolating
REAL(r64) :: TsolHiSide = 0.0d0 ! intermediate solar transmission for interpolating
REAL(r64) :: DeltaSHGCandTsol = 0.0d0 ! intermediate difference
REAL(r64) :: RLowSide = 0.0d0
REAL(r64) :: RHiSide = 0.0d0
! first fill out defaults
Material(MaterNum)%GlassSpectralDataPtr = 0
Material(MaterNum)%SolarDiffusing = .FALSE.
Material(MaterNum)%Roughness = VerySmooth
Material(MaterNum)%TransThermal = 0.0d0
Material(MaterNum)%AbsorpThermalBack = 0.84d0
Material(MaterNum)%AbsorpThermalFront = 0.84d0
Material(MaterNum)%AbsorpThermal = Material(MaterNum)%AbsorpThermalBack
! step 1. Determine U-factor without film coefficients
! Simple window model has its own correlation for film coefficients (m2-K/W) under Winter conditions as function of U-factor
IF ( Material(MaterNum)%SimpleWindowUfactor < 5.85d0 ) THEN
Riw = 1.0d0 / ( 0.359073d0 * Log( Material(MaterNum)%SimpleWindowUfactor ) + 6.949915d0)
Else
Riw = 1.0d0 / (1.788041d0 * Material(MaterNum)%SimpleWindowUfactor - 2.886625d0 )
Endif
Row = 1.0d0 / (0.025342d0 * Material(MaterNum)%SimpleWindowUfactor + 29.163853d0 )
! determine 1/U without film coefficients
Rlw = (1.0d0/Material(MaterNum)%SimpleWindowUfactor) - Riw - Row
IF (Rlw <= 0.0d0) THEN ! U factor of film coefficients is better than user input.
Rlw = MAX(Rlw, 0.001d0)
CALL ShowWarningError('WindowMaterial:SimpleGlazingSystem: ' //Trim(Material(MaterNum)%Name)// &
' has U-factor higher than that provided by surface film resistances, Check value of U-factor')
ENDIF
! Step 2. determine layer thickness.
IF ( (1.0d0 / Rlw) > 7.0d0 ) THEN
Material(MaterNum)%Thickness = 0.002d0
ELSE
Material(MaterNum)%Thickness = 0.05914d0 - (0.00714d0 / Rlw )
ENDIF
! Step 3. determine effective conductivity
Material(MaterNum)%Conductivity = Material(MaterNum)%Thickness / Rlw
IF (Material(MaterNum)%Conductivity > 0.0d0) THEN
NominalR(MaterNum) = Rlw
Material(MaterNum)%Resistance = Rlw
ELSE
ErrorsFound = .true.
CALL ShowSevereError('WindowMaterial:SimpleGlazingSystem: ' //Trim(Material(MaterNum)%Name)// &
' has Conductivity <= 0.0, must be >0.0, Check value of U-factor')
END IF
!step 4. determine solar transmission (revised to 10-1-2009 version from LBNL.)
IF (Material(MaterNum)%SimpleWindowUfactor > 4.5d0) THEN
IF (Material(MaterNum)%SimpleWindowSHGC < 0.7206d0 ) THEN
Material(MaterNum)%Trans = 0.939998d0 * Material(MaterNum)%SimpleWindowSHGC**2 &
+ 0.20332d0 * Material(MaterNum)%SimpleWindowSHGC
ELSE ! >= 0.7206
Material(MaterNum)%Trans = 1.30415d0 * Material(MaterNum)%SimpleWindowSHGC - 0.30515d0
ENDIF
ELSEIF (Material(MaterNum)%SimpleWindowUfactor < 3.4d0) THEN
IF (Material(MaterNum)%SimpleWindowSHGC <= 0.15d0) THEN
Material(MaterNum)%Trans = 0.41040d0 * Material(MaterNum)%SimpleWindowSHGC
ELSE ! > 0.15
Material(MaterNum)%Trans = 0.085775d0*(Material(MaterNum)%SimpleWindowSHGC**2) &
+ 0.963954d0*Material(MaterNum)%SimpleWindowSHGC - 0.084958d0
ENDIF
ELSE ! interpolate. 3.4 <= Ufactor <= 4.5
IF (Material(MaterNum)%SimpleWindowSHGC < 0.7206d0 ) THEN
TsolHiSide = 0.939998d0 * Material(MaterNum)%SimpleWindowSHGC**2 &
+ 0.20332d0 * Material(MaterNum)%SimpleWindowSHGC
ELSE ! >= 0.7206
TsolHiSide = 1.30415d0 * Material(MaterNum)%SimpleWindowSHGC - 0.30515d0
ENDIF
IF (Material(MaterNum)%SimpleWindowSHGC <= 0.15d0) THEN
TsolLowSide = 0.41040d0 * Material(MaterNum)%SimpleWindowSHGC
ELSE ! > 0.15
TsolLowSide = 0.085775d0*(Material(MaterNum)%SimpleWindowSHGC**2) &
+ 0.963954d0*Material(MaterNum)%SimpleWindowSHGC - 0.084958d0
ENDIF
Material(MaterNum)%Trans = ((Material(MaterNum)%SimpleWindowUfactor - 3.4d0) &
/ (4.5d0 - 3.4d0) ) &
* (TsolHiSide - TsolLowSide) + TsolLowSide
ENDIF
If (Material(MaterNum)%Trans < 0.0d0) Material(MaterNum)%Trans = 0.0d0
!step 5. determine solar reflectances
DeltaSHGCandTsol = Material(MaterNum)%SimpleWindowSHGC - Material(MaterNum)%Trans
IF (Material(MaterNum)%SimpleWindowUfactor > 4.5d0) THEN
Ris = 1.0d0 / (29.436546d0*DeltaSHGCandTsol**3.0d0 - 21.943415d0*DeltaSHGCandTsol**2 &
+ 9.945872d0*DeltaSHGCandTsol + 7.426151d0 )
Ros = 1.0d0 / (2.225824d0*DeltaSHGCandTsol + 20.577080d0 )
ELSEIF (Material(MaterNum)%SimpleWindowUfactor < 3.4d0) THEN
Ris = 1.0d0 / (199.8208128d0*DeltaSHGCandTsol**3.0d0 - 90.639733d0*DeltaSHGCandTsol**2 &
+ 19.737055d0*DeltaSHGCandTsol + 6.766575d0 )
Ros = 1.0d0 / (5.763355d0*DeltaSHGCandTsol + 20.541528d0 )
ELSE ! interpolate. 3.4 <= Ufactor <= 4.5
!inside first
RLowSide = 1.0d0 / (199.8208128d0*DeltaSHGCandTsol**3.0d0 - 90.639733d0*DeltaSHGCandTsol**2 &
+ 19.737055d0*DeltaSHGCandTsol + 6.766575d0 )
RHiSide = 1.0d0 / (29.436546d0*DeltaSHGCandTsol**3 - 21.943415d0*DeltaSHGCandTsol**2 &
+ 9.945872d0*DeltaSHGCandTsol + 7.426151d0 )
Ris = ((Material(MaterNum)%SimpleWindowUfactor - 3.4d0) &
/ (4.5d0 - 3.4d0) ) &
* (RLowSide - RHiSide) + RLowSide
! then outside
RLowSide = 1.0d0 / (5.763355d0*DeltaSHGCandTsol + 20.541528d0 )
RHiSide = 1.0d0 / (2.225824d0*DeltaSHGCandTsol + 20.577080d0 )
Ros = ((Material(MaterNum)%SimpleWindowUfactor - 3.4d0) &
/ (4.5d0 - 3.4d0) ) &
* (RLowSide - RHiSide) + RLowSide
ENDIF
InflowFraction = (Ros + 0.5d0*Rlw)/(Ros + Rlw + Ris)
SolarAbsorb = (Material(MaterNum)%SimpleWindowSHGC - Material(MaterNum)%Trans) / InflowFraction
Material(MaterNum)%ReflectSolBeamBack = 1.0d0 - Material(MaterNum)%Trans - SolarAbsorb
Material(MaterNum)%ReflectSolBeamFront = Material(MaterNum)%ReflectSolBeamBack
!step 6. determine visible properties.
IF (Material(MaterNum)%SimpleWindowVTinputByUser) THEN
Material(MaterNum)%TransVis = Material(MaterNum)%SimpleWindowVisTran
Material(MaterNum)%ReflectVisBeamBack = - 0.7409d0 * Material(MaterNum)%TransVis**3 &
+ 1.6531d0 * Material(MaterNum)%TransVis**2 &
- 1.2299d0 * Material(MaterNum)%TransVis + 0.4545d0
IF (Material(MaterNum)%TransVis + Material(MaterNum)%ReflectVisBeamBack >= 1.0d0) THEN
Material(MaterNum)%ReflectVisBeamBack = 0.999d0 - Material(MaterNum)%TransVis
ENDIF
Material(MaterNum)%ReflectVisBeamFront = - 0.0622d0 * Material(MaterNum)%TransVis**3 &
+ 0.4277d0 * Material(MaterNum)%TransVis**2 &
- 0.4169d0 * Material(MaterNum)%TransVis + 0.2399d0
IF (Material(MaterNum)%TransVis + Material(MaterNum)%ReflectVisBeamFront >= 1.0d0) THEN
Material(MaterNum)%ReflectVisBeamFront = 0.999d0 - Material(MaterNum)%TransVis
ENDIF
ELSE
Material(MaterNum)%TransVis = Material(MaterNum)%Trans
Material(MaterNum)%ReflectVisBeamBack = Material(MaterNum)%ReflectSolBeamBack
Material(MaterNum)%ReflectVisBeamFront = Material(MaterNum)%ReflectSolBeamFront
ENDIF
!step 7. The dependence on incident angle is in subroutine TransAndReflAtPhi
!step 8. Hemispherical terms are averaged using standard method
IF (ErrorsFound) THEN
CALL ShowFatalError('Program halted because of input problem(s) in WindowMaterial:SimpleGlazingSystem')
ENDIF
RETURN
END SUBROUTINE SetupSimpleWindowGlazingSystem