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 | ||
---|---|---|---|---|---|---|
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 GetWindowShadingControlData(ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN November 1998
! MODIFIED Aug 2001 (FW): add handling of new ShadingControlIsScheduled
! and GlareControlIsActive fields
! Nov 2001 (FW): add ShadingDevice as alternative to ShadedConstruction
! Dec 2001 (FW): add slat angle controls for blinds
! Aug 2002 (FW): add Setpoint2; check that specified control type is legal
! Feb 2003 (FW): add error if Material Name of Shading Device is used with
! Shading Type = BetweenGlassShade or BetweenGlassBlind
! Dec 2003 (FW): improve BetweenGlassBlind error messages
! Feb 2009 (BG): improve error checking for OnIfScheduleAllows
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Reads in the window shading control information
! from the input data file, interprets it and puts it in the derived type
! METHODOLOGY EMPLOYED:
! REFERENCES:
! USE STATEMENTS:
USE DataIPShortCuts
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, FindItemInList, VerifyName
USE ScheduleManager, ONLY: GetScheduleIndex
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ErrorsFound ! If errors found in input
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: NumValidShadingTypes=8
CHARACTER(len=*), PARAMETER, DIMENSION(NumValidShadingTypes) :: cValidShadingTypes=(/ &
'INTERIORSHADE ', &
'EXTERIORSHADE ', &
'EXTERIORSCREEN ', &
'INTERIORBLIND ', &
'EXTERIORBLIND ', &
'BETWEENGLASSSHADE', &
'BETWEENGLASSBLIND', &
'SWITCHABLEGLAZING'/)
INTEGER, PARAMETER, DIMENSION(NumValidShadingTypes) :: ValidShadingTypes=(/ &
WSC_ST_InteriorShade , &
WSC_ST_ExteriorShade , &
WSC_ST_ExteriorScreen , &
WSC_ST_InteriorBlind , &
WSC_ST_ExteriorBlind , &
WSC_ST_BetweenGlassShade , &
WSC_ST_BetweenGlassBlind , &
WSC_ST_SwitchableGlazing /)
INTEGER, PARAMETER :: NumValidWindowShadingControlTypes=21
CHARACTER(len=*), PARAMETER, DIMENSION(NumValidWindowShadingControlTypes) :: cValidWindowShadingControlTypes=(/ &
'ALWAYSON ', &
'ALWAYSOFF ', &
'ONIFSCHEDULEALLOWS ', &
'ONIFHIGHSOLARONWINDOW ', &
'ONIFHIGHHORIZONTALSOLAR ', &
'ONIFHIGHOUTDOORAIRTEMPERATURE ', &
'ONIFHIGHZONEAIRTEMPERATURE ', &
'ONIFHIGHZONECOOLING ', &
'ONIFHIGHGLARE ', &
'MEETDAYLIGHTILLUMINANCESETPOINT ', &
'ONNIGHTIFLOWOUTDOORTEMPANDOFFDAY ', &
'ONNIGHTIFLOWINSIDETEMPANDOFFDAY ', &
'ONNIGHTIFHEATINGANDOFFDAY ', &
'ONNIGHTIFLOWOUTDOORTEMPANDONDAYIFCOOLING ', &
'ONNIGHTIFHEATINGANDONDAYIFCOOLING ', &
'OFFNIGHTANDONDAYIFCOOLINGANDHIGHSOLARONWINDOW ', &
'ONNIGHTANDONDAYIFCOOLINGANDHIGHSOLARONWINDOW ', &
'ONIFHIGHOUTDOORAIRTEMPANDHIGHSOLARONWINDOW ', &
'ONIFHIGHOUTDOORAIRTEMPANDHIGHHORIZONTALSOLAR ', &
'ONIFHIGHZONEAIRTEMPANDHIGHSOLARONWINDOW ', &
'ONIFHIGHZONEAIRTEMPANDHIGHHORIZONTALSOLAR '/)
INTEGER, PARAMETER, DIMENSION(NumValidWindowShadingControlTypes) :: ValidWindowShadingControlTypes=(/ &
WSCT_ALWAYSON , & ! 'ALWAYSON ', &
WSCT_ALWAYSOFF , & ! 'ALWAYSOFF ', &
WSCT_ONIFSCHEDULED , & ! 'ONIFSCHEDULEALLOWS ', &
WSCT_HISOLAR , & ! 'ONIFHIGHSOLARONWINDOW ', &
WSCT_HIHORZSOLAR , & ! 'ONIFHIGHHORIZONTALSOLAR ', &
WSCT_HIOUTAIRTEMP , & ! 'ONIFHIGHOUTDOORAIRTEMPERATURE ', &
WSCT_HIZONEAIRTEMP , & ! 'ONIFHIGHZONEAIRTEMPERATURE ', &
WSCT_HIZONECOOLING , & ! 'ONIFHIGHZONECOOLING ', &
WSCT_HIGLARE , & ! 'ONIFHIGHGLARE ', &
WSCT_MEETDAYLILUMSETP , & ! 'MEETDAYLIGHTILLUMINANCESETPOINT ', &
WSCT_ONNIGHTLOOUTTEMP_OFFDAY , & ! 'ONNIGHTIFLOWOUTDOORTEMPANDOFFDAY ', &
WSCT_ONNIGHTLOINTEMP_OFFDAY , & ! 'ONNIGHTIFLOWINSIDETEMPANDOFFDAY ', &
WSCT_ONNIGHTIFHEATING_OFFDAY , & ! 'ONNIGHTIFHEATINGANDOFFDAY ', &
WSCT_ONNIGHTLOOUTTEMP_ONDAYCOOLING , & ! 'ONNIGHTIFLOWOUTDOORTEMPANDONDAYIFCOOLING ', &
WSCT_ONNIGHTIFHEATING_ONDAYCOOLING , & ! 'ONNIGHTIFHEATINGANDONDAYIFCOOLING ', &
WSCT_OFFNIGHT_ONDAY_HISOLARWINDOW , & ! 'OFFNIGHTANDONDAYIFCOOLINGANDHIGHSOLARONWINDOW ', &
WSCT_ONNIGHT_ONDAY_HISOLARWINDOW , & ! 'ONNIGHTANDONDAYIFCOOLINGANDHIGHSOLARONWINDOW ', &
WSCT_ONHIOUTTEMP_HISOLARWINDOW , & ! 'ONIFHIGHOUTDOORAIRTEMPANDHIGHSOLARONWINDOW ', &
WSCT_ONHIOUTTEMP_HIHORZSOLAR , & ! 'ONIFHIGHOUTDOORAIRTEMPANDHIGHHORIZONTALSOLAR', &
WSCT_ONHIZONETEMP_HISOLARWINDOW , & ! 'ONIFHIGHZONEAIRTEMPANDHIGHSOLARONWINDOW ', &
WSCT_ONHIZONETEMP_HIHORZSOLAR /) ! 'ONIFHIGHZONEAIRTEMPANDHIGHHORIZONTALSOLAR '/)
! INTERFACE BLOCK SPECIFICATIONS:na
! DERIVED TYPE DEFINITIONS:na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: IOStat ! IO Status when calling get input subroutine
INTEGER :: ControlNumAlpha ! Number of control alpha names being passed
INTEGER :: ControlNumProp ! Number of control properties being passed
INTEGER :: ControlNum ! DO loop counter/index for window shading control number
INTEGER :: IShadedConst ! Construction number of shaded construction
INTEGER :: IShadingDevice ! Material number of shading device
INTEGER :: NLayers ! Layers in shaded construction
LOGICAL :: ErrorInName
LOGICAL :: IsBlank
INTEGER :: Loop
INTEGER :: ShTyp ! Shading type
CHARACTER(MaxNameLength) :: ControlType ! Shading control type
LOGICAL :: BGShadeBlindError ! True if problem with construction that is supposed to have between-glass
! shade or blind
INTEGER :: Found
! FLOW:
! Get the total number of window shading control blocks
cCurrentModuleObject='WindowProperty:ShadingControl'
TotWinShadingControl = GetNumObjectsFound(cCurrentModuleObject)
IF(TotWinShadingControl.EQ.0) RETURN
ALLOCATE (WindowShadingControl(TotWinShadingControl))
ControlNum=0
DO Loop = 1, TotWinShadingControl
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,ControlNumAlpha, &
rNumericArgs,ControlNumProp,IOSTAT, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
ErrorInName=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),WindowShadingControl%Name,ControlNum,ErrorInName,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (ErrorInName) THEN
ErrorsFound=.true.
CYCLE
ENDIF
ControlNum=ControlNum+1
WindowShadingControl(ControlNum)%Name = cAlphaArgs(1) ! Set the Control Name in the Derived Type
WindowShadingControl(ControlNum)%ShadedConstruction = FindIteminList(cAlphaArgs(3),Construct%Name,TotConstructs)
WindowShadingControl(ControlNum)%ShadingDevice = FindIteminList(cAlphaArgs(8),Material%Name,TotMaterials)
WindowShadingControl(ControlNum)%Schedule = GetScheduleIndex(cAlphaArgs(5))
WindowShadingControl(ControlNum)%SetPoint = rNumericArgs(1)
WindowShadingControl(ControlNum)%SetPoint2 = rNumericArgs(2)
WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .FALSE.
IF(cAlphaArgs(6) == 'YES') WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .TRUE.
WindowShadingControl(ControlNum)%GlareControlIsActive = .FALSE.
IF(cAlphaArgs(7) == 'YES') WindowShadingControl(ControlNum)%GlareControlIsActive = .TRUE.
WindowShadingControl(ControlNum)%SlatAngleSchedule = GetScheduleIndex(cAlphaArgs(10))
ControlType = cAlphaArgs(4)
IF(ControlType=='SCHEDULE') THEN
ControlType = 'ONIFSCHEDULEALLOWS'
WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .TRUE.
WindowShadingControl(ControlNum)%GlareControlIsActive = .FALSE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'", changing to "'//TRIM(ControlType)//'"')
! Error if schedule has not been specified
IF(WindowShadingControl(ControlNum)%Schedule <= 0) THEN
ErrorsFound = .TRUE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
' has '//TRIM(cAlphaFieldNames(4))//' "'//TRIM(ControlType)// &
'" but a schedule has not been specified.')
END IF
END IF
IF(ControlType(1:11)=='SCHEDULEAND') THEN
ControlType = 'ONIFHIGH'//ControlType(12:)
WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .TRUE.
WindowShadingControl(ControlNum)%GlareControlIsActive = .FALSE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'", changing to "'//TRIM(ControlType)//'"')
! Error if schedule has not been specified
IF(WindowShadingControl(ControlNum)%Schedule <= 0) THEN
ErrorsFound = .TRUE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
' has '//TRIM(cAlphaFieldNames(4))//' "'//TRIM(ControlType)// &
'" but a schedule has not been specified.')
END IF
END IF
IF(ControlType(1:7)=='GLAREOR') THEN
ControlType = 'ONIFHIGH'//ControlType(8:)
WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .FALSE.
WindowShadingControl(ControlNum)%GlareControlIsActive = .TRUE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'", changing to "'//TRIM(ControlType)//'"')
END IF
IF(ControlType=='GLARE') THEN
ControlType = 'ONIFHIGHGLARE'
WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .FALSE.
WindowShadingControl(ControlNum)%GlareControlIsActive = .TRUE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'", changing to "'//TRIM(ControlType)//'"')
END IF
IF(WindowShadingControl(ControlNum)%ShadingDevice .GT. 0)THEN
IF(Material(WindowShadingControl(ControlNum)%ShadingDevice)%Group == Screen .AND. .NOT. &
(ControlType == 'ALWAYSON' .OR. ControlType == 'ALWAYSOFF' .OR. &
ControlType == 'ONIFSCHEDULEALLOWS'))THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'" for exterior screens.')
CALL ShowContinueError('Valid shading control types for exterior window screens'// &
' are ALWAYSON, ALWAYSOFF, or ONIFSCHEDULEALLOWS.')
END IF
ELSE
IF (WindowShadingControl(ControlNum)%ShadedConstruction > 0) THEN
Construct(WindowShadingControl(ControlNum)%ShadedConstruction)%IsUsed=.true.
IF(Material(Construct(WindowShadingControl(ControlNum)%ShadedConstruction)%LayerPoint(1))%Group == Screen .AND. .NOT. &
(ControlType == 'ALWAYSON' .OR. ControlType == 'ALWAYSOFF' .OR. &
ControlType == 'ONIFSCHEDULEALLOWS'))THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'" for exterior screens.')
CALL ShowContinueError('Valid shading control types for exterior window screens'// &
' are ALWAYSON, ALWAYSOFF, or ONIFSCHEDULEALLOWS.')
END IF
ELSEIF (lAlphaFieldBlanks(3)) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'", '//trim(cAlphaFieldNames(3))//' is blank.')
CALL ShowContinueError('A valid construction is required.')
ErrorsFound=.true.
ELSE
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'", '//trim(cAlphaFieldNames(3))//' is invalid.')
CALL ShowContinueError('Construction="'//trim(cAlphaArgs(3))//'" was used. A valid construction is required.')
ErrorsFound=.true.
ENDIF
END IF
! Warning if setpoint is unintentionally zero
IF(WindowShadingControl(ControlNum)%SetPoint == 0 .AND. &
ControlType /= 'ALWAYSON' .AND. &
ControlType /= 'ALWAYSOFF' .AND. &
ControlType /= 'ONIFSCHEDULEALLOWS' .AND. ControlType /= 'SCHEDULE' .AND. &
ControlType /= 'ONIFHIGHGLARE' .AND. ControlType /= 'GLARE' .AND. &
ControlType /= 'DAYLIGHTILLUMINANCE' ) THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'", The first SetPoint is zero.')
CALL ShowContinueError('..You may have forgotten to specify that setpoint.')
END IF
! Upward compatibility for old Shading Control Type names
IF(ControlType=='SOLARONWINDOW' .OR. ControlType=='HORIZONTALSOLAR' .OR. ControlType=='OUTSIDEAIRTEMP' .OR. &
ControlType=='ZONEAIRTEMP' .OR. ControlType=='ZONECOOLING') THEN
ControlType = 'ONIFHIGH'//TRIM(ControlType)
WindowShadingControl(ControlNum)%ShadingControlIsScheduled = .FALSE.
WindowShadingControl(ControlNum)%GlareControlIsActive = .FALSE.
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))// &
'", changing to "'//TRIM(ControlType)//'"')
END IF
! Error if illegal control type
Found=FindItemInList(ControlType,cValidWindowShadingControlTypes,NumValidWindowShadingControlTypes)
IF (Found == 0) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))//'".')
ELSE
WindowShadingControl(ControlNum)%ShadingControlType = ValidWindowShadingControlTypes(Found)
END IF
! Error checks
IF(cAlphaArgs(6) /= 'YES' .AND. cAlphaArgs(6) /= 'NO') THEN
ErrorsFound = .true.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(6))//'="'//TRIM(cAlphaArgs(6))//'".')
END IF
IF(cAlphaArgs(7) /= 'YES' .AND. cAlphaArgs(7) /= 'NO') THEN
ErrorsFound = .true.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(7))//'="'//TRIM(cAlphaArgs(7))//'".')
END IF
IF ((WindowShadingControl(ControlNum)%ShadingControlType == WSCT_ONIFSCHEDULED) .and. &
(.NOT. WindowShadingControl(ControlNum)%ShadingControlIsScheduled)) THEN ! CR 7709 BG
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//' = "'//TRIM(WindowShadingControl(ControlNum)%Name)//'" invalid, '// &
TRIM(cAlphaFieldNames(6))//' must be set to "Yes" for '//TRIM(cAlphaFieldNames(4))//' = OnIfScheduleAllows')
ENDIF
IF(cAlphaArgs(9) /= 'FIXEDSLATANGLE' .AND. cAlphaArgs(9) /= 'SCHEDULEDSLATANGLE' .AND. &
cAlphaArgs(9) /= 'BLOCKBEAMSOLAR') THEN
ErrorsFound = .true.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(9))//'="'//TRIM(cAlphaArgs(9))//'".')
ELSEIF (cAlphaArgs(9) == 'FIXEDSLATANGLE') THEN
WindowShadingControl(ControlNum)%SlatAngleControlForBlinds = WSC_SAC_FixedSlatAngle
ELSEIF (cAlphaArgs(9) == 'SCHEDULEDSLATANGLE') THEN
WindowShadingControl(ControlNum)%SlatAngleControlForBlinds = WSC_SAC_ScheduledSlatAngle
ELSEIF (cAlphaArgs(9) == 'BLOCKBEAMSOLAR') THEN
WindowShadingControl(ControlNum)%SlatAngleControlForBlinds = WSC_SAC_BlockBeamSolar
END IF
! For upward compatibility change old "noninsulating" and "insulating" shade types to
! INTERIORSHADE or EXTERIORSHADE
IF(cAlphaArgs(2) == 'INTERIORNONINSULATINGSHADE' .OR. &
cAlphaArgs(2) == 'INTERIORINSULATINGSHADE') THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'", changing to "InteriorShade"')
WindowShadingControl(ControlNum)%ShadingType = WSC_ST_InteriorShade
cAlphaArgs(2)='INTERIORSHADE'
ENDIF
IF(cAlphaArgs(2) == 'EXTERIORNONINSULATINGSHADE' .OR. &
cAlphaArgs(2) == 'EXTERIORINSULATINGSHADE') THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" is using obsolete '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'", changing to "ExteriorShade"')
WindowShadingControl(ControlNum)%ShadingType = WSC_ST_ExteriorShade
cAlphaArgs(2)='EXTERIORSHADE'
ENDIF
IF (ControlType == 'MEETDAYLIGHTILLUMINANCESETPOINT' .and. &
cAlphaArgs(2) /= 'SWITCHABLEGLAZING') THEN
ErrorsFound = .true.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))//'".')
CALL ShowContinueError('...'//trim(cAlphaFieldNames(2))//' must be SwitchableGlazing for this control, but'// &
' entered type="'//trim(cAlphaArgs(2))//'".')
ENDIF
! Check for illegal shading type name
Found=FindItemInList(cAlphaArgs(2),cValidShadingTypes,NumValidShadingTypes)
IF (Found == 0) THEN
ErrorsFound = .true.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" invalid '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))//'".')
ELSE
WindowShadingControl(ControlNum)%ShadingType=ValidShadingTypes(Found)
END IF
ShTyp = WindowShadingControl(ControlNum)%ShadingType
IShadedConst = WindowShadingControl(ControlNum)%ShadedConstruction
IShadingDevice = WindowShadingControl(ControlNum)%ShadingDevice
IF(IShadedConst==0 .AND. IShadingDevice == 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has no matching shaded construction or shading device.')
ErrorsFound=.true.
ELSE IF(IShadedConst == 0 .AND. IShadingDevice > 0) THEN
IF(ShTyp == WSC_ST_SwitchableGlazing) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaArgs(2))//'= SwitchableGlazing but no matching shaded construction')
ErrorsFound = .true.
END IF
IF((ShTyp==WSC_ST_InteriorShade.OR. ShTyp==WSC_ST_ExteriorShade).AND. Material(IShadingDevice)%Group /= Shade) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaArgs(2))//'= InteriorShade or ExteriorShade but matching shading device is not a window shade')
CALL ShowContinueError(TRIM(cAlphaFieldNames(8))//' in error="'//TRIM(Material(IShadingDevice)%Name)//'".')
ErrorsFound = .true.
END IF
IF((ShTyp==WSC_ST_ExteriorScreen).AND. Material(IShadingDevice)%Group /= Screen) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaArgs(2))//'= ExteriorScreen but matching shading device is not a window screen')
CALL ShowContinueError(TRIM(cAlphaFieldNames(8))//' in error="'//TRIM(Material(IShadingDevice)%Name)//'".')
ErrorsFound = .true.
END IF
IF((ShTyp==WSC_ST_InteriorBlind.OR. ShTyp==WSC_ST_ExteriorBlind).AND. Material(IShadingDevice)%Group /= WindowBlind) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaArgs(2))//'= InteriorBlind or ExteriorBlind but matching shading device is not a window blind')
CALL ShowContinueError(TRIM(cAlphaFieldNames(8))//' in error="'//TRIM(Material(IShadingDevice)%Name)//'".')
ErrorsFound = .true.
END IF
IF(ShTyp==WSC_ST_BetweenGlassBlind.OR. ShTyp==WSC_ST_BetweenGlassBlind) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaArgs(2))//'= BetweenGlassShade or BetweenGlassBlind and')
CALL ShowContinueError(TRIM(cAlphaFieldNames(8))//' is specified. This is illegal. Specify shaded construction instead.')
ErrorsFound = .true.
END IF
ELSE IF(IShadedConst > 0 .AND. IShadingDevice > 0) THEN
IShadingDevice = 0
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" Both '//TRIM(cAlphaFieldNames(3))//' and '//TRIM(cAlphaFieldNames(8))//' are specified.')
CALL ShowContinueError('The '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(Construct(IShadedConst)%Name)//'" will be used.')
END IF
! If type = interior or exterior shade or blind require that the shaded construction
! have a shade layer in the correct position
IF(IShadedConst /= 0) THEN
NLayers = Construct(IShadedConst)%TotLayers
BGShadeBlindError = .FALSE.
IShadingDevice=0
IF (Construct(IShadedConst)%LayerPoint(NLayers) /= 0) THEN
IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_InteriorShade) THEN
IShadingDevice=Construct(IShadedConst)%LayerPoint(NLayers)
IF(Material(Construct(IShadedConst)%LayerPoint(NLayers))%Group /= Shade) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have a shade layer on the inside of the window.')
END IF
ELSE IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_ExteriorShade) THEN
IShadingDevice=Construct(IShadedConst)%LayerPoint(1)
IF(Material(Construct(IShadedConst)%LayerPoint(1))%Group /= Shade) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have a shade layer on the outside of the window.')
END IF
ELSE IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_ExteriorScreen) THEN
IShadingDevice=Construct(IShadedConst)%LayerPoint(1)
IF(Material(Construct(IShadedConst)%LayerPoint(1))%Group /= Screen) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have a screen layer on the outside of the window.')
END IF
ELSE IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_InteriorBlind) THEN
IShadingDevice=Construct(IShadedConst)%LayerPoint(NLayers)
IF(Material(Construct(IShadedConst)%LayerPoint(NLayers))%Group /= WindowBlind) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have a blind layer on the inside of the window.')
END IF
ELSE IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_ExteriorBlind) THEN
IShadingDevice=Construct(IShadedConst)%LayerPoint(1)
IF(Material(Construct(IShadedConst)%LayerPoint(1))%Group /= WindowBlind) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have a blind layer on the outside of the window.')
END IF
ELSE IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_BetweenGlassShade) THEN
IF(NLayers /= 5 .AND. NLayers /= 7) BGShadeBlindError = .TRUE.
IF(NLayers==5) THEN
IF(Material(Construct(IShadedConst)%LayerPoint(3))%Group /= Shade) BGShadeBlindError = .TRUE.
END IF
IF(NLayers==7) THEN
IF(Material(Construct(IShadedConst)%LayerPoint(5))%Group /= Shade) BGShadeBlindError = .TRUE.
END IF
IF(BGShadeBlindError) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have two or three glass layers and a')
CALL ShowContinueError('between-glass shade layer with a gas layer on each side.')
END IF
ELSE IF(WindowShadingControl(ControlNum)%ShadingType == WSC_ST_BetweenGlassBlind) THEN
IF(NLayers /= 5 .AND. NLayers /= 7) BGShadeBlindError = .TRUE.
IF(NLayers==5) THEN
IF(Material(Construct(IShadedConst)%LayerPoint(3))%Group /= WindowBlind) BGShadeBlindError = .TRUE.
END IF
IF(NLayers==7) THEN
IF(Material(Construct(IShadedConst)%LayerPoint(5))%Group /= WindowBlind) BGShadeBlindError = .TRUE.
END IF
IF(BGShadeBlindError) THEN
ErrorsFound = .TRUE.
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" the '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'"')
CALL ShowContinueError('of '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" should have two or three glass layers and a')
CALL ShowContinueError('between-glass blind layer with a gas layer on each side.')
END IF
END IF
ENDIF
IF(IShadingDevice > 0) THEN
IF((ShTyp==WSC_ST_InteriorShade.OR. ShTyp==WSC_ST_ExteriorShade).AND. Material(IShadingDevice)%Group /= Shade) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaFieldNames(2))//'= InteriorShade or ExteriorShade '// &
'but matching shading device is not a window shade')
CALL ShowContinueError('Shading Device in error="'//TRIM(Material(IShadingDevice)%Name)//'".')
ErrorsFound = .true.
END IF
IF((ShTyp==WSC_ST_ExteriorScreen).AND. Material(IShadingDevice)%Group /= Screen) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaFieldNames(2))//'= ExteriorScreen '// &
'but matching shading device is not an exterior window screen.')
CALL ShowContinueError('Shading Device in error="'//TRIM(Material(IShadingDevice)%Name)//'".')
ErrorsFound = .true.
END IF
IF((ShTyp==WSC_ST_InteriorBlind.OR. ShTyp==WSC_ST_ExteriorBlind).AND. Material(IShadingDevice)%Group /= WindowBlind) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(WindowShadingControl(ControlNum)%Name)// &
'" has '//TRIM(cAlphaFieldNames(2))//'= InteriorBlind or ExteriorBlind '// &
'but matching shading device is not a window blind.')
CALL ShowContinueError('Shading Device in error="'//TRIM(Material(IShadingDevice)%Name)//'".')
ErrorsFound = .true.
END IF
END IF
END IF
END DO ! End of loop over window shading controls
RETURN
END SUBROUTINE GetWindowShadingControlData