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 | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | cRoutineName | |||
logical, | intent(inout) | :: | ErrorsFound | |||
integer, | intent(in) | :: | SurfNum | |||
integer, | intent(in) | :: | FrameField |
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 CheckWindowShadingControlFrameDivider(cRoutineName,ErrorsFound,SurfNum,FrameField)
! SUBROUTINE INFORMATION:
! AUTHOR Linda Lawrie
! DATE WRITTEN December 2008
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This routine performs checks on WindowShadingControl settings and Frame/Divider Settings.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE DataIPShortCuts
USE InputProcessor, ONLY: FindItemInList
USE General, ONLY: TrimSigDigits,RoundSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), INTENT(IN) :: cRoutineName ! routine name calling this one (for error messages)
LOGICAL, INTENT(INOUT) :: ErrorsFound ! true if errors have been found or are found here
INTEGER, INTENT(IN) :: SurfNum ! current surface number
INTEGER, INTENT(IN) :: FrameField ! field number for frame/divider
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: WSCPtr ! WindowShadingControl Index
INTEGER :: ConstrNumSh ! Construction number with Shade
INTEGER :: ConstrNum ! Construction number
INTEGER :: ShDevNum ! Shading Device number
INTEGER :: Lay ! Layer number
INTEGER :: TotGlassLayers ! Number of glass layers in window construction
INTEGER :: TotLayers ! Number of layers in unshaded construction
INTEGER :: TotShLayers ! Number of layers in shaded construction
INTEGER :: MatGap ! Gap material number
INTEGER :: MatGap1 ! Material number of gap to left (outer side) of between-glass shade/blind
INTEGER :: MatGap2 ! Material number of gap to right (inner side) of between-glass shade/blind
INTEGER :: MatSh ! Between-glass shade/blind material number
REAL(r64) :: MatGapCalc ! Calculated MatGap diff for shaded vs non-shaded constructions
! If WindowShadingControl has been specified for this window --
! Set shaded construction number if shaded construction was specified in WindowShadingControl.
! Otherwise, create shaded construction if WindowShadingControl for this window has
! interior or exterior shade/blind (but not between-glass shade/blind) specified.
WSCptr = SurfaceTmp(SurfNum)%WindowShadingControlPtr
ConstrNumSh=0
IF(.NOT.ErrorsFound .AND. WSCptr > 0) THEN
ConstrNumSh = WindowShadingControl(WSCptr)%ShadedConstruction
IF(ConstrNumSh > 0) THEN
SurfaceTmp(SurfNum)%ShadedConstruction = ConstrNumSh
ELSE
IF(WindowShadingControl(WSCptr)%ShadingType==WSC_ST_InteriorShade.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_InteriorBlind.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_ExteriorShade.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_ExteriorScreen.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_ExteriorBlind) THEN
ShDevNum = WindowShadingControl(WSCptr)%ShadingDevice
IF(ShDevNum > 0) THEN
CALL CreateShadedWindowConstruction(SurfNum,WSCptr,ShDevNum)
ConstrNumSh = SurfaceTmp(SurfNum)%ShadedConstruction
ENDIF
END IF
END IF
END IF
! Error checks for shades and blinds
ConstrNum = SurfaceTmp(SurfNum)%Construction
IF (.NOT.ErrorsFound .AND. WSCptr > 0 .AND. ConstrNum > 0 .AND. ConstrNumSh > 0) THEN
IF(WindowShadingControl(WSCptr)%ShadingType==WSC_ST_InteriorShade.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_InteriorBlind) THEN
TotLayers = Construct(ConstrNum)%TotLayers
TotShLayers = Construct(ConstrNumSh)%TotLayers
IF (TotShLayers-1 /= TotLayers) THEN
CALL ShowWarningError('WindowProperty:ShadingControl: Interior shade or blind: Potential problem in match of '// &
'unshaded/shaded constructions, shaded should have 1 more layers than unshaded.')
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name))
CALL ShowContinueError('If preceding two constructions are same name, you have likely specified a '// &
'WindowProperty:ShadingControl (Field #3) with the Window Construction rather than '// &
'a shaded construction.')
ENDIF
DO Lay = 1,Construct(ConstrNum)%TotLayers
IF(Construct(ConstrNum)%LayerPoint(Lay) /= Construct(ConstrNumSh)%LayerPoint(Lay)) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError &
(' The glass and gas layers in the shaded and unshaded constructions do not match for window=' &
//TRIM(SurfaceTmp(SurfNum)%Name))
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name))
EXIT
END IF
END DO
END IF
IF(WindowShadingControl(WSCptr)%ShadingType==WSC_ST_ExteriorShade.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_ExteriorScreen.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_ExteriorBlind) THEN
TotLayers = Construct(ConstrNum)%TotLayers
TotShLayers = Construct(ConstrNumSh)%TotLayers
IF (TotShLayers-1 /= TotLayers) THEN
CALL ShowWarningError('WindowProperty:ShadingControl: Exterior shade, screen or blind: '// &
'Potential problem in match of unshaded/shaded constructions, shaded should have 1 more layer than unshaded.')
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name))
CALL ShowContinueError('If preceding two constructions have the same name, you have likely specified a '// &
'WindowProperty:ShadingControl (Field #3) with the Window Construction rather than '// &
'a shaded construction.')
ENDIF
DO Lay = 1,Construct(ConstrNum)%TotLayers
IF(Construct(ConstrNum)%LayerPoint(Lay) /= Construct(ConstrNumSh)%LayerPoint(Lay+1)) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError &
(' The glass and gas layers in the shaded and unshaded constructions do not match for window=' &
//TRIM(SurfaceTmp(SurfNum)%Name))
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name))
EXIT
END IF
END DO
END IF
IF(WindowShadingControl(WSCptr)%ShadingType==WSC_ST_BetweenGlassShade.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_BetweenGlassBlind) THEN
! Divider not allowed with between-glass shade or blind
IF(SurfaceTmp(SurfNum)%FrameDivider > 0) THEN
IF(FrameDivider(SurfaceTmp(SurfNum)%FrameDivider)%DividerWidth > 0.0d0) THEN
CALL ShowWarningError('A divider cannot be specified for window '//TRIM(SurfaceTmp(SurfNum)%Name))
CALL ShowContinueError(', which has a between-glass shade or blind.')
CALL ShowContinueError('Calculation will proceed without the divider for this window.')
FrameDivider(SurfaceTmp(SurfNum)%FrameDivider)%DividerWidth = 0.0d0
END IF
END IF
! Check consistency of gap widths between unshaded and shaded constructions
TotGlassLayers = Construct(ConstrNum)%TotGlassLayers
TotLayers = Construct(ConstrNum)%TotLayers
TotShLayers = Construct(ConstrNumSh)%TotLayers
IF (TotShLayers-2 /= TotLayers) THEN
CALL ShowWarningError('WindowProperty:ShadingControl: Between Glass Shade/Blind: Potential problem in match of '// &
'unshaded/shaded constructions, shaded should have 2 more layers than unshaded.')
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name))
CALL ShowContinueError('If preceding two constructions are same name, you have likely specified a '// &
'WindowProperty:ShadingControl (Field #3) with the Window Construction rather than '// &
'a shaded construction.')
ENDIF
IF (Construct(ConstrNum)%LayerPoint(TotLayers) /= Construct(ConstrNumSh)%LayerPoint(TotShLayers)) THEN
CALL ShowSevereError(trim(cRoutineName)//': Mis-match in unshaded/shaded inside layer materials. These should match.')
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name)// &
', Material='//TRIM(Material(Construct(ConstrNum)%LayerPoint(TotLayers))%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name)// &
', Material='//TRIM(Material(Construct(ConstrNumSh)%LayerPoint(TotShLayers))%Name))
ErrorsFound=.true.
ENDIF
IF (Construct(ConstrNum)%LayerPoint(1) /= Construct(ConstrNumSh)%LayerPoint(1)) THEN
CALL ShowSevereError(trim(cRoutineName)//': Mis-match in unshaded/shaded inside layer materials. These should match.')
CALL ShowContinueError('Unshaded construction='//TRIM(Construct(ConstrNum)%Name)// &
', Material='//TRIM(Material(Construct(ConstrNum)%LayerPoint(1))%Name))
CALL ShowContinueError('Shaded construction='//TRIM(Construct(ConstrNumSh)%Name)// &
', Material='//TRIM(Material(Construct(ConstrNumSh)%LayerPoint(1))%Name))
ErrorsFound=.true.
ENDIF
IF(TotGlassLayers == 2 .OR. TotGlassLayers == 3) THEN
MatGap = Construct(ConstrNum)%LayerPoint(2*TotGlassLayers-2)
MatGap1 = Construct(ConstrNumSh)%LayerPoint(2*TotGlassLayers-2)
MatGap2 = Construct(ConstrNumSh)%LayerPoint(2*TotGlassLayers)
MatSh = Construct(ConstrNumSh)%LayerPoint(2*TotGlassLayers-1)
IF(WindowShadingControl(WSCptr)%ShadingType==WSC_ST_BetweenGlassBlind) THEN
MatGapCalc=ABS(Material(MatGap)%Thickness-(Material(MatGap1)%Thickness+Material(MatGap2)%Thickness))
IF(MatGapCalc > 0.001d0) THEN
CALL ShowSevereError(trim(cRoutineName)//': The gap width(s) for the unshaded window construction ' &
//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('are inconsistent with the gap widths for shaded window construction ' &
//TRIM(Construct(ConstrNumSh)%Name))
CALL ShowContinueError('for window '//TRIM(SurfaceTmp(SurfNum)%Name)//', which has a between-glass blind.')
CALL ShowContinueError('..Material='//TRIM(Material(MatGap)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatGap)%Thickness,3))//' -')
CALL ShowContinueError('..( Material='//TRIM(Material(MatGap1)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatGap1)%Thickness,3))//' +')
CALL ShowContinueError('..Material='//TRIM(Material(MatGap2)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatGap2)%Thickness,3))//' )=['// &
trim(RoundSigDigits(MatGapCalc,3))//'] >.001')
ErrorsFound=.true.
END IF
ELSE ! Between-glass shade
MatGapCalc=ABS(Material(MatGap)%Thickness- &
(Material(MatGap1)%Thickness+Material(MatGap2)%Thickness+Material(MatSh)%Thickness))
IF(MatGapCalc > 0.001d0) THEN
CALL ShowSevereError(trim(cRoutineName)//': The gap width(s) for the unshaded window construction ' &
//TRIM(Construct(ConstrNum)%Name))
CALL ShowContinueError('are inconsistent with the gap widths for shaded window construction ' &
//TRIM(Construct(ConstrNumSh)%Name))
CALL ShowContinueError('for window '//TRIM(SurfaceTmp(SurfNum)%Name)//', which has a between-glass shade.')
CALL ShowContinueError('..Material='//TRIM(Material(MatGap)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatGap)%Thickness,3))//' -')
CALL ShowContinueError('...( Material='//TRIM(Material(MatGap1)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatGap1)%Thickness,3))//' +')
CALL ShowContinueError('..Material='//TRIM(Material(MatGap2)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatGap2)%Thickness,3))//' +')
CALL ShowContinueError('..Material='//TRIM(Material(MatSh)%Name)// &
' thickness='//TRIM(RoundSigDigits(Material(MatSh)%Thickness,3))//' )=['// &
trim(RoundSigDigits(MatGapCalc,3))//'] >.001')
ErrorsFound=.true.
END IF
END IF
END IF
END IF
END IF
IF(SurfaceTmp(SurfNum)%Sides /= 3) THEN ! Rectangular Window
! Initialize the FrameDivider number for this window. W5FrameDivider will be positive if
! this window's construction came from the Window5 data file and that construction had an
! associated frame or divider. It will be zero if the window's construction is not from the
! Window5 data file, or the construction is from the data file, but the construction has no
! associated frame or divider. Note that if there is a FrameDivider candidate for this
! window from the Window5 data file it is used instead of the window's input FrameDivider.
IF(SurfaceTmp(SurfNum)%Construction /= 0) THEN
SurfaceTmp(SurfNum)%FrameDivider = Construct(SurfaceTmp(SurfNum)%Construction)%W5FrameDivider
! Warning if FrameAndDivider for this window is over-ridden by one from Window5 Data File
IF(SurfaceTmp(SurfNum)%FrameDivider > 0 .AND. .not. lAlphaFieldBlanks(FrameField)) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(SurfaceTmp(SurfNum)%Name)// &
'", '//TRIM(cAlphaFieldNames(FrameField))//'="'//TRIM(cAlphaArgs(FrameField))//'"')
CALL ShowContinueError('will be replaced with FrameAndDivider from Window5 Data File entry ' &
//TRIM(Construct(SurfaceTmp(SurfNum)%Construction)%Name))
END IF
IF (.not. lAlphaFieldBlanks(FrameField) .AND. SurfaceTmp(SurfNum)%FrameDivider == 0) THEN
SurfaceTmp(SurfNum)%FrameDivider = &
FindIteminList(cAlphaArgs(FrameField),FrameDivider%Name,TotFrameDivider)
IF(SurfaceTmp(SurfNum)%FrameDivider == 0) THEN
IF (.NOT. Construct(SurfaceTmp(SurfNum)%Construction)%WindowTypeEQL) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(SurfaceTmp(SurfNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(FrameField))//'="'//TRIM(cAlphaArgs(FrameField))//'"')
ErrorsFound=.true.
ELSE
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(SurfaceTmp(SurfNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(FrameField))//'="'//TRIM(cAlphaArgs(FrameField))//'"')
CALL ShowContinueError('...Frame/Divider is not supported in Equivalent Layer Window model.')
ENDIF
END IF
! Divider not allowed with between-glass shade or blind
IF(.NOT.ErrorsFound .AND. WSCptr > 0 .AND. ConstrNumSh > 0) THEN
IF(WindowShadingControl(WSCptr)%ShadingType==WSC_ST_BetweenGlassShade.OR. &
WindowShadingControl(WSCptr)%ShadingType==WSC_ST_BetweenGlassBlind) THEN
IF(SurfaceTmp(SurfNum)%FrameDivider > 0) THEN
IF(FrameDivider(SurfaceTmp(SurfNum)%FrameDivider)%DividerWidth > 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(SurfaceTmp(SurfNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(FrameField))//'="'//TRIM(cAlphaArgs(FrameField))//'"')
CALL ShowContinueError('Divider cannot be specified because the construction has a between-glass shade or blind.')
CALL ShowContinueError('Calculation will proceed without the divider for this window.')
CALL ShowContinueError('Divider width = ['// &
trim(RoundSigDigits(FrameDivider(SurfaceTmp(SurfNum)%FrameDivider)%DividerWidth,2))//'].')
FrameDivider(SurfaceTmp(SurfNum)%FrameDivider)%DividerWidth = 0.0d0
END IF
END IF ! End of check if window has divider
END IF ! End of check if window has a between-glass shade or blind
END IF ! End of check if window has a shaded construction
END IF ! End of check if window has an associated FrameAndDivider
END IF ! End of check if window has a construction
END IF
IF (Construct(SurfaceTmp(SurfNum)%Construction)%WindowTypeEQL) THEN
IF(SurfaceTmp(SurfNum)%FrameDivider > 0) THEN
! Equivalent Layer window does not have frame/divider model
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(SurfaceTmp(SurfNum)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(FrameField))//'="'//TRIM(cAlphaArgs(FrameField))//'"')
CALL ShowContinueError('Frame/Divider is not supported in Equivalent Layer Window model.')
SurfaceTmp(SurfNum)%FrameDivider = 0
ENDIF
ENDIF
RETURN
END SUBROUTINE CheckWindowShadingControlFrameDivider