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, | intent(in) | :: | ConstrNum | |||
logical, | intent(inout) | :: | ErrorsFound |
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 CheckAndSetConstructionProperties(ConstrNum,ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Linda Lawrie
! DATE WRITTEN December 2006
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This routine checks some properties of entered constructions; sets some properties; and sets
! an error flag for certain error conditions.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE DataInterfaces, ONLY: ShowWarningError,ShowSevereError,ShowContinueError
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ConstrNum ! Construction number to be set/checked
LOGICAL, INTENT(INOUT) :: ErrorsFound ! error flag that is set when certain errors have occurred
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: InsideLayer ! Inside Layer of Construct; for window construct, layer no. of inside glass
INTEGER :: MaterNum ! Counters to keep track of the material number for a layer
INTEGER :: OutsideMaterNum ! Material "number" of the Outside layer
INTEGER :: InsideMaterNum ! Material "number" of the Inside layer
INTEGER :: Layer ! loop index for each of the construction layers
INTEGER :: TotLayers ! Number of layers in a construction
INTEGER :: TotGlassLayers ! Number of glass layers in a construction
INTEGER :: TotShadeLayers ! Number of shade layers in a construction
INTEGER :: TotGasLayers ! Number of gas layers in a construction
LOGICAL :: WrongMaterialsMix ! True if window construction has a layer that is not glass, gas or shade
LOGICAL :: WrongWindowLayering ! True if error in layering of a window construction
INTEGER :: MaterNumNext ! Next material number in the layer sequence
INTEGER :: IGas ! Index for gases in a mixture of gases in a window gap
INTEGER :: LayNumSh ! Number of shade/blind layer in a construction
INTEGER :: MatSh ! Material number of a shade/blind layer
INTEGER :: MatGapL ! Material number of the gas layer to the left (outer side) of a shade/blind layer
INTEGER :: MatGapR ! Material number of the gas layer to the right (innner side) of a shade/blind layer
INTEGER :: BlNum ! Blind number
LOGICAL :: ValidBGShadeBlindConst ! True if a valid window construction with between-glass shade/blind
INTEGER :: GlassLayNum ! Glass layer number
TotLayers = Construct(ConstrNum)%TotLayers
InsideLayer = TotLayers
IF (Construct(ConstrNum)%LayerPoint(InsideLayer) <= 0) RETURN ! Error condition
IF (TotLayers == 0) RETURN ! error condition, hopefully caught elsewhere
! window screen is not allowed on inside layer
Construct(ConstrNum)%DayltPropPtr = 0
InsideMaterNum=Construct(ConstrNum)%LayerPoint(InsideLayer)
IF (InsideMaterNum /= 0) THEN
Construct(ConstrNum)%InsideAbsorpVis = Material(InsideMaterNum)%AbsorpVisible
Construct(ConstrNum)%InsideAbsorpSolar = Material(InsideMaterNum)%AbsorpSolar
! Following line applies only to opaque surfaces; it is recalculated later for windows.
Construct(ConstrNum)%ReflectVisDiffBack = 1.0d0 - Material(InsideMaterNum)%AbsorpVisible
END IF
OutsideMaterNum=Construct(ConstrNum)%LayerPoint(1)
IF (OutsideMaterNum /= 0) THEN
Construct(ConstrNum)%OutsideAbsorpVis = Material(OutsideMaterNum)%AbsorpVisible
Construct(ConstrNum)%OutsideAbsorpSolar = Material(OutsideMaterNum)%AbsorpSolar
END IF
Construct(ConstrNum)%TotSolidLayers = 0
Construct(ConstrNum)%TotGlassLayers = 0
Construct(ConstrNum)%AbsDiffShade = 0.0d0
! Check if any layer is glass, gas, shade, screen or blind; if so it is considered a window construction for
! purposes of error checking.
Construct(ConstrNum)%TypeIsWindow = .false.
DO Layer = 1,TotLayers
MaterNum = Construct(ConstrNum)%LayerPoint(Layer)
IF (MaterNum == 0) CYCLE ! error -- has been caught will stop program later
IF(Material(MaterNum)%Group == WindowGlass .OR. Material(MaterNum)%Group == WindowGas &
.OR. Material(MaterNum)%Group == WindowGasMixture &
.OR. Material(MaterNum)%Group == Shade .OR. Material(MaterNum)%Group == WindowBlind &
.OR. Material(MaterNum)%Group == Screen .OR. Material(MaterNum)%Group == WindowSimpleGlazing &
.OR. Material(MaterNum)%Group == ComplexWindowShade .OR. Material(MaterNum)%Group == ComplexWindowGap &
.OR. Material(MaterNum)%Group == GlassEquivalentLayer .OR. Material(MaterNum)%Group == ShadeEquivalentLayer &
.OR. Material(MaterNum)%Group == DrapeEquivalentLayer .OR. Material(MaterNum)%Group == ScreenEquivalentLayer &
.OR. Material(MaterNum)%Group == BlindEquivalentLayer .OR. Material(MaterNum)%Group == GapEquivalentLayer) &
Construct(ConstrNum)%TypeIsWindow = .true.
END DO
IF (InsideMaterNum == 0) RETURN
IF (OutsideMaterNum == 0) RETURN
IF(Construct(ConstrNum)%TypeIsWindow) THEN
Construct(ConstrNum)%NumCTFTerms = 0
Construct(ConstrNum)%NumHistories = 0
WrongMaterialsMix = .false.
WrongWindowLayering = .false.
DO Layer = 1,TotLayers
MaterNum = Construct(ConstrNum)%LayerPoint(Layer)
IF (MaterNum == 0) CYCLE ! error -- has been caught will stop program later
IF(Material(MaterNum)%Group /= WindowGlass .AND. Material(MaterNum)%Group /= WindowGas &
.AND. Material(MaterNum)%Group /= WindowGasMixture &
.AND. Material(MaterNum)%Group /= Shade .AND. Material(MaterNum)%Group /= WindowBlind &
.AND. Material(MaterNum)%Group /= Screen .AND. Material(MaterNum)%Group /= WindowSimpleGlazing &
.AND. Material(MaterNum)%Group /= ComplexWindowShade .AND. Material(MaterNum)%Group /= ComplexWindowGap &
.AND. Material(MaterNum)%Group /= GlassEquivalentLayer .AND. Material(MaterNum)%Group /= GapEquivalentLayer &
.AND. Material(MaterNum)%Group /= ShadeEquivalentLayer .AND. Material(MaterNum)%Group /= DrapeEquivalentLayer &
.AND. Material(MaterNum)%Group /= ScreenEquivalentLayer .AND. Material(MaterNum)%Group /= BlindEquivalentLayer) &
WrongMaterialsMix = .true.
END DO
IF(WrongMaterialsMix) THEN !Illegal material for a window construction
CALL ShowSevereError('Error: Window construction='//TRIM(Construct(ConstrNum)%Name)// &
' has materials other than glass, gas, shade, screen, blind, complex shading, complex gap, or simple system.')
ErrorsFound = .true.
! Do not check number of layers for BSDF type of window since that can be handled
ELSE IF((TotLayers > 8).and.(.not.Construct(ConstrNum)%WindowTypeBSDF) &
.and.(.not.Construct(ConstrNum)%WindowTypeEQL) ) THEN !Too many layers for a window construction
CALL ShowSevereError('CheckAndSetConstructionProperties: Window construction='//TRIM(Construct(ConstrNum)%Name)// &
' has too many layers (max of 8 allowed -- 4 glass + 3 gap + 1 shading device).')
ErrorsFound = .true.
ELSE IF (TotLayers == 1) THEN
IF(Material(Construct(ConstrNum)%LayerPoint(1))%Group == Shade &
.OR. Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowGas &
.OR. Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowGasMixture &
.OR. Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowBlind &
.OR. Material(Construct(ConstrNum)%LayerPoint(1))%Group == Screen &
.OR. Material(Construct(ConstrNum)%LayerPoint(1))%Group == ComplexWindowShade &
.OR. Material(Construct(ConstrNum)%LayerPoint(1))%Group == ComplexWindowGap) THEN
CALL ShowSevereError('CheckAndSetConstructionProperties: The single-layer window construction='// &
TRIM(Construct(ConstrNum)%Name)// &
' has a gas, complex gap, shade, complex shade, screen or blind material; '// &
'it should be glass of simple glazing system.')
ErrorsFound = .true.
END IF
END IF
! Find total glass layers, total shade/blind layers and total gas layers in a window construction
TotGlassLayers = 0
TotShadeLayers = 0 ! Includes shades, blinds, and screens
TotGasLayers = 0
DO Layer = 1,TotLayers
MaterNum = Construct(ConstrNum)%LayerPoint(Layer)
IF (MaterNum == 0) CYCLE ! error -- has been caught will stop program later
IF(Material(MaterNum)%Group == WindowGlass) TotGlassLayers = TotGlassLayers + 1
IF(Material(MaterNum)%Group == WindowSimpleGlazing) TotGlassLayers = TotGlassLayers + 1
IF(Material(MaterNum)%Group == Shade .OR. Material(MaterNum)%Group == WindowBlind .OR. &
Material(MaterNum)%Group == Screen .OR. Material(MaterNum)%Group == ComplexWindowShade) &
TotShadeLayers = TotShadeLayers + 1
IF(Material(MaterNum)%Group == WindowGas .OR. Material(MaterNum)%Group == WindowGasMixture .OR. &
Material(MaterNum)%Group == ComplexWindowGap) &
TotGasLayers = TotGasLayers + 1
IF(Layer < TotLayers) THEN
MaterNumNext = Construct(ConstrNum)%LayerPoint(Layer+1)
! Adjacent layers of same type not allowed
IF (MaterNumNext == 0) CYCLE
IF(Material(MaterNum)%Group == Material(MaterNumNext)%Group) WrongWindowLayering = .true.
END IF
END DO
! It is not necessary to check rest of BSDF window structure since that is performed inside TARCOG90 routine.
! That routine also allow structures which are not allowed in rest of this routine
if (Construct(ConstrNum)%WindowTypeBSDF) then
Construct(ConstrNum)%TotGlassLayers = TotGlassLayers
Construct(ConstrNum)%TotSolidLayers = TotGlassLayers + TotShadeLayers
Construct(ConstrNum)%InsideAbsorpThermal = Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%AbsorpThermalBack
Construct(ConstrNum)%OutsideAbsorpThermal = Material(Construct(ConstrNum)%LayerPoint(1))%AbsorpThermalFront
return
end if
IF (Construct(ConstrNum)%WindowTypeEQL) Then
Construct(ConstrNum)%InsideAbsorpThermal = Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%AbsorpThermalBack
Construct(ConstrNum)%OutsideAbsorpThermal = Material(Construct(ConstrNum)%LayerPoint(1))%AbsorpThermalFront
Return
ENDIF
IF(Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowGas .or. &
Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowGasMixture .or. &
Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Group == WindowGas .or. &
Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Group == WindowGasMixture) &
WrongWindowLayering = .true. ! Gas cannot be first or last layer
IF(TotShadeLayers > 1) WrongWindowLayering = .true. !At most one shade, screen or blind allowed
! If there is a diffusing glass layer no shade, screen or blind is allowed
DO Layer = 1,TotLayers
MaterNum = Construct(ConstrNum)%LayerPoint(Layer)
IF (MaterNum == 0) CYCLE ! error -- has been caught will stop program later
IF(Material(MaterNum)%SolarDiffusing .AND. TotShadeLayers > 0) THEN
ErrorsFound = .true.
CALL ShowSevereError('CheckAndSetConstructionProperties: Window construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError( &
'has diffusing glass='//TRIM(Material(MaterNum)%Name)//' and a shade, screen or blind layer.')
EXIT
END IF
END DO
! If there is a diffusing glass layer it must be the innermost layer
IF(TotGlassLayers > 1) THEN
GlassLayNum = 0
DO Layer = 1,TotLayers
MaterNum = Construct(ConstrNum)%LayerPoint(Layer)
IF (MaterNum == 0) CYCLE ! error -- has been caught will stop program later
IF(Material(MaterNum)%Group == WindowGlass) THEN
GlassLayNum = GlassLayNum + 1
IF(GlassLayNum < TotGlassLayers .AND. Material(MaterNum)%SolarDiffusing) THEN
ErrorsFound = .true.
CALL ShowSevereError('CheckAndSetConstructionProperties: Window construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError( &
'has diffusing glass='//TRIM(Material(MaterNum)%Name)//' that is not the innermost glass layer.')
END IF
END IF
END DO
END IF
! interior window screen is not allowed. Check for invalid between-glass screen is checked below.
IF(TotShadeLayers == 1 .AND. Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Group == Screen .and. &
TotLayers /= 1) THEN
WrongWindowLayering = .true.
END IF
! Consistency checks for a construction with a between-glass shade or blind
IF(TotShadeLayers == 1 .AND. Material(Construct(ConstrNum)%LayerPoint(1))%Group /= Shade .AND. &
Material(Construct(ConstrNum)%LayerPoint(1))%Group /= WindowBlind .AND. &
Material(Construct(ConstrNum)%LayerPoint(1))%Group /= Screen .AND. &
Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Group /= Shade .AND. &
Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Group /= WindowBlind .AND. &
Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Group /= ComplexWindowShade .AND. &
.NOT.WrongWindowLayering) THEN
! This is a construction with a between-glass shade or blind
IF(TotGlassLayers == 4) THEN
! Quadruple pane not allowed.
WrongWindowLayering = .true.
ELSE IF(TotGlassLayers == 2 .OR. TotGlassLayers == 3) THEN
ValidBGShadeBlindConst = .FALSE.
IF(TotGlassLayers == 2) THEN
IF(TotLayers /= 5) THEN
WrongWindowLayering = .TRUE.
ELSE
IF(Material(Construct(ConstrNum)%LayerPoint(1))%Group==WindowGlass .AND. &
(Material(Construct(ConstrNum)%LayerPoint(2))%Group==WindowGas .OR. &
Material(Construct(ConstrNum)%LayerPoint(2))%Group==WindowGasMixture) .AND. &
((Material(Construct(ConstrNum)%LayerPoint(3))%Group==Shade .OR. &
Material(Construct(ConstrNum)%LayerPoint(3))%Group==WindowBlind) .AND. &
.NOT. Material(Construct(ConstrNum)%LayerPoint(3))%Group==Screen) .AND. &
(Material(Construct(ConstrNum)%LayerPoint(4))%Group==WindowGas .OR. &
Material(Construct(ConstrNum)%LayerPoint(4))%Group==WindowGasMixture) .AND. &
Material(Construct(ConstrNum)%LayerPoint(5))%Group==WindowGlass) &
ValidBGShadeBlindConst = .TRUE.
END IF
ELSE ! TotGlassLayers = 3
IF(TotLayers /= 7) THEN
WrongWindowLayering = .TRUE.
ELSE
IF (Material(Construct(ConstrNum)%LayerPoint(1))%Group==WindowGlass .AND. &
(Material(Construct(ConstrNum)%LayerPoint(2))%Group==WindowGas .OR. &
Material(Construct(ConstrNum)%LayerPoint(2))%Group==WindowGasMixture) .AND. &
Material(Construct(ConstrNum)%LayerPoint(3))%Group==WindowGlass .AND. &
(Material(Construct(ConstrNum)%LayerPoint(4))%Group==WindowGas .OR. &
Material(Construct(ConstrNum)%LayerPoint(4))%Group==WindowGasMixture) .AND. &
((Material(Construct(ConstrNum)%LayerPoint(5))%Group==Shade .OR. &
Material(Construct(ConstrNum)%LayerPoint(5))%Group==WindowBlind) .AND. &
.NOT. Material(Construct(ConstrNum)%LayerPoint(5))%Group==Screen) .AND. &
(Material(Construct(ConstrNum)%LayerPoint(6))%Group==WindowGas .OR. &
Material(Construct(ConstrNum)%LayerPoint(6))%Group==WindowGasMixture) .AND. &
Material(Construct(ConstrNum)%LayerPoint(7))%Group==WindowGlass) &
ValidBGShadeBlindConst = .TRUE.
END IF
END IF ! End of check if TotGlassLayers = 2 or 3
IF(.NOT.ValidBGShadeBlindConst) WrongWindowLayering = .TRUE.
IF(.NOT.WrongWindowLayering) THEN
LayNumSh = 2*TotGlassLayers - 1
MatSh = Construct(ConstrNum)%LayerPoint(LayNumSh)
! For double pane, shade/blind must be layer #3.
! For triple pane, it must be layer #5 (i.e., between two inner panes).
IF(Material(MatSh)%Group /= Shade .AND. Material(MatSh)%Group /= WindowBlind) WrongWindowLayering = .true.
IF(TotLayers /= 2*TotGlassLayers + 1) WrongWindowLayering = .true.
! TH 8/26/2010 commented out, CR 8206
! All glass layers must be SpectralAverage
! IF(.not.WrongWindowLayering) THEN
! IF(TotGlassLayers == 2) THEN ! Double pane
! IF(Material(Construct(ConstrNum)%LayerPoint(1))%GlassSpectralDataPtr > 0 .OR. &
! Material(Construct(ConstrNum)%LayerPoint(5))%GlassSpectralDataPtr > 0) THEN
! CALL ShowSevereError('CheckAndSetConstructionProperties: For window construction '// &
! TRIM(Construct(ConstrNum)%Name))
! CALL ShowContinueError('Glass layers cannot use SpectralData -- must be SpectralAverage.')
! WrongWindowLayering = .true.
! ENDIF
! ELSE ! Triple pane
! IF(Material(Construct(ConstrNum)%LayerPoint(1))%GlassSpectralDataPtr > 0 .OR. &
! Material(Construct(ConstrNum)%LayerPoint(3))%GlassSpectralDataPtr > 0 .OR. &
! Material(Construct(ConstrNum)%LayerPoint(7))%GlassSpectralDataPtr > 0) THEN
! CALL ShowSevereError('CheckAndSetConstructionProperties: For window construction '// &
! TRIM(Construct(ConstrNum)%Name))
! CALL ShowContinueError('Glass layers cannot use SpectralData -- must be SpectralAverage.')
! WrongWindowLayering = .true.
! ENDIF
! END IF
! END IF
IF(.NOT.WrongWindowLayering) THEN
! Gas on either side of a between-glass shade/blind must be the same
MatGapL = Construct(ConstrNum)%LayerPoint(LayNumSh-1)
MatGapR = Construct(ConstrNum)%LayerPoint(LayNumSh+1)
DO IGas = 1,5
IF((Material(MatGapL)%GasType(IGas) /= Material(MatGapR)%GasType(IGas)) .OR. &
(Material(MatGapL)%GasFract(IGas) /= Material(MatGapR)%GasFract(IGas))) WrongWindowLayering = .true.
END DO
! Gap width on either side of a between-glass shade/blind must be the same
IF(ABS(Material(MatGapL)%Thickness - Material(MatGapR)%Thickness) > 0.0005d0) WrongWindowLayering = .true.
IF(Material(MatSh)%Group == WindowBlind) THEN
BlNum = Material(MatSh)%BlindDataPtr
IF(BlNum > 0) THEN
IF((Material(MatGapL)%Thickness + Material(MatGapR)%Thickness) < Blind(BlNum)%SlatWidth) THEN
ErrorsFound = .true.
CALL ShowSevereError('CheckAndSetConstructionProperties: For window construction '// &
TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('the slat width of the between-glass blind is greater than')
CALL ShowContinueError('the sum of the widths of the gas layers adjacent to the blind.')
END IF
END IF ! End of check if BlNum > 0
END IF ! End of check if material is window blind
END IF ! End of check if WrongWindowLayering
END IF ! End of check if WrongWindowLayering
END IF ! End of check on total glass layers
END IF ! End of check if construction has between-glass shade/blind
! Check Simple Windows,
IF (Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowSimpleGlazing) THEN
IF (TotLayers > 1) THEN
! check that none of the other layers are glazing or gas
DO Layer = 1,TotLayers
MaterNum = Construct(ConstrNum)%LayerPoint(Layer)
IF (MaterNum == 0) CYCLE ! error -- has been caught will stop program later
IF(Material(MaterNum)%Group == WindowGlass) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError('CheckAndSetConstructionProperties: Error in window construction '// &
TRIM(Construct(ConstrNum)%Name)// '--')
CALL ShowContinueError('For simple window constructions, no other glazing layers are allowed.')
END IF
IF(Material(MaterNum)%Group == WindowGas) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError('CheckAndSetConstructionProperties: Error in window construction '// &
TRIM(Construct(ConstrNum)%Name)// '--')
CALL ShowContinueError('For simple window constructions, no other gas layers are allowed.')
END IF
END DO
ENDIF
ENDIF
IF(WrongWindowLayering) THEN
CALL ShowSevereError('CheckAndSetConstructionProperties: Error in window construction '// &
TRIM(Construct(ConstrNum)%Name)// '--')
CALL ShowContinueError(' For multi-layer window constructions the following rules apply:')
CALL ShowContinueError(' --The first and last layer must be a solid layer (glass or shade/screen/blind),')
CALL ShowContinueError(' --Adjacent glass layers must be separated by one and only one gas layer,')
CALL ShowContinueError(' --Adjacent layers must not be of the same type,')
CALL ShowContinueError(' --Only one shade/screen/blind layer is allowed,')
CALL ShowContinueError(' --An exterior shade/screen/blind must be the first layer,')
CALL ShowContinueError(' --An interior shade/blind must be the last layer,')
CALL ShowContinueError(' --An interior screen is not allowed,')
CALL ShowContinueError(' --For an exterior shade/screen/blind or interior shade/blind, there should not be a gas layer')
CALL ShowContinueError(' ----between the shade/screen/blind and adjacent glass,')
CALL ShowContinueError(' --A between-glass screen is not allowed,')
CALL ShowContinueError(' --A between-glass shade/blind is allowed only for double and triple glazing,')
CALL ShowContinueError(' --A between-glass shade/blind must have adjacent gas layers of the same type and width,')
! CALL ShowContinueError(' --For between-glass shade/blind all glazing layers must be input using SpectralAverage data,')
CALL ShowContinueError(' --For triple glazing the between-glass shade/blind must be between the two inner glass layers,')
CALL ShowContinueError(' --The slat width of a between-glass blind must be less than the sum of the widths')
CALL ShowContinueError(' ----of the gas layers adjacent to the blind.')
ErrorsFound = .true.
END IF
Construct(ConstrNum)%TotGlassLayers = TotGlassLayers
Construct(ConstrNum)%TotSolidLayers = TotGlassLayers + TotShadeLayers
! In following, InsideLayer is layer number of inside glass and InsideAbsorpThermal applies
! only to inside glass; it is corrected later in InitGlassOpticalCalculations
! if construction has inside shade or blind.
IF (Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%Group == Shade .OR. &
Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%Group == WindowBlind) THEN
InsideLayer=InsideLayer-1
ENDIF
IF (InsideLayer > 0) THEN
InsideMaterNum=Construct(ConstrNum)%LayerPoint(InsideLayer)
Construct(ConstrNum)%InsideAbsorpThermal = &
Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%AbsorpThermalBack
ENDIF
IF (InsideMaterNum /= 0) THEN
Construct(ConstrNum)%InsideAbsorpVis = Material(InsideMaterNum)%AbsorpVisible
Construct(ConstrNum)%InsideAbsorpSolar = Material(InsideMaterNum)%AbsorpSolar
ENDIF
IF((Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowGlass) .OR. & !Glass
(Material(Construct(ConstrNum)%LayerPoint(1))%Group == WindowSimpleGlazing) ) THEN
Construct(ConstrNum)%OutsideAbsorpThermal = &
Material(Construct(ConstrNum)%LayerPoint(1))%AbsorpThermalFront
ELSE !Exterior shade, blind or screen
Construct(ConstrNum)%OutsideAbsorpThermal = &
Material(Construct(ConstrNum)%LayerPoint(1))%AbsorpThermal
END IF
ELSE !Opaque surface
Construct(ConstrNum)%InsideAbsorpThermal = &
Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%AbsorpThermal
Construct(ConstrNum)%OutsideAbsorpThermal = &
Material(Construct(ConstrNum)%LayerPoint(1))%AbsorpThermal
END IF
Construct(ConstrNum)%OutsideRoughness=Material(Construct(ConstrNum)%LayerPoint(1))%Roughness
IF (Material(Construct(ConstrNum)%LayerPoint(1))%Group == Air) THEN
CALL ShowSevereError('CheckAndSetConstructionProperties: Outside Layer is Air for construction '// &
TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError(' Error in material '//TRIM(Material(Construct(ConstrNum)%LayerPoint(1))%Name))
ErrorsFound = .true.
ENDIF
IF (InsideLayer > 0) THEN
IF (Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%Group == Air) THEN
CALL ShowSevereError('CheckAndSetConstructionProperties: Inside Layer is Air for construction '// &
TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError(' Error in material '//TRIM(Material(Construct(ConstrNum)%LayerPoint(InsideLayer))%Name))
ErrorsFound = .true.
ENDIF
ENDIF
IF (Material(Construct(ConstrNum)%LayerPoint(1))%Group == EcoRoof) THEN
Construct(ConstrNum)%TypeIsEcoRoof = .true.
!need to check EcoRoof is not non-outside layer
DO Layer=2,TotLayers
IF (Material(Construct(ConstrNum)%LayerPoint(Layer))%Group == EcoRoof) THEN
CALL ShowSevereError('CheckAndSetConstructionProperties: Interior Layer is EcoRoof for construction '// &
TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError(' Error in material '//TRIM(Material(Construct(ConstrNum)%LayerPoint(Layer))%Name))
ErrorsFound = .true.
ENDIF
ENDDO
ENDIF
IF (Material(Construct(ConstrNum)%LayerPoint(1))%Group == IRTMaterial) THEN
Construct(ConstrNum)%TypeIsIRT = .true.
IF (Construct(ConstrNum)%TotLayers /= 1) THEN
CALL ShowSevereError('CheckAndSetConstructionProperties: '// &
'Infrared Transparent (IRT) Construction is limited to 1 layer '// &
TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError(' Too many layers in referenced construction.')
ErrorsFound = .true.
ENDIF
ENDIF
RETURN
END SUBROUTINE CheckAndSetConstructionProperties