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.
ALLOCATE (DeflectionState(W7DeflectionStates))
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(inout) | :: | MaterNum | |||
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 SetupComplexFenestrationMaterialInput(MaterNum,ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Simon Vidanovic
! DATE WRITTEN March 2012
! MODIFIED May 2013 (Simon Vidanovic)
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! get input for complex fenestration materials
! METHODOLOGY EMPLOYED:
! usual GetInput processing.
! REFERENCES:
! na
! USE STATEMENTS:
USE DataHeatBalance, ONLY : Material
USE General, ONLY : RoundSigDigits
! SUBROUTINE ARGUMENT DEFINITIONS:
Integer, Intent(InOut) :: MaterNum ! num of material items thus far
Logical, Intent(InOut) :: ErrorsFound
! SUBROUTINE PARAMETER DEFINITIONS
character(len=*), parameter :: RoutineName = 'SetupComplexFenestrationMaterialInput: '
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: IOStat ! IO Status when calling get input subroutine
CHARACTER(len=MaxNameLength),DIMENSION(5) &
:: MaterialNames ! Number of Material Alpha names defined
INTEGER :: MaterialNumAlpha ! Number of material alpha names being passed
INTEGER :: MaterialNumProp ! Number of material properties being passed
REAL(r64), DIMENSION(27) :: MaterialProps !Temporary array to transfer material properties
INTEGER :: Loop
INTEGER :: NumAlphas ! Number of Alphas for each GetObjectItem call
INTEGER :: NumNumbers ! Number of Numbers for each GetObjectItem call
INTEGER :: IOStatus ! Used in GetObjectItem
LOGICAL :: IsNotOK ! Flag to verify name
LOGICAL :: IsBlank ! Flag for blank name
!Reading WindowGap:SupportPillar
cCurrentModuleObject = 'WindowGap:SupportPillar'
W7SupportPillars = GetNumObjectsFound(cCurrentModuleObject);
ALLOCATE (SupportPillar(W7SupportPillars))
DO Loop=1,W7SupportPillars
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.FALSE.
IsBlank=.FALSE.
! Verify unique names
CALL VerifyName(cAlphaArgs(1),SupportPillar%Name,Loop,IsNotOK,IsBlank,TRIM(CurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cAlphaFieldNames(1))//' has been found.')
CALL ShowContinueError('...All Material names must be unique regardless of subtype.')
CYCLE
ENDIF
SupportPillar(Loop)%Name = cAlphaArgs(1)
SupportPillar(Loop)%Spacing = rNumericArgs(1)
SupportPillar(Loop)%Radius = rNumericArgs(2)
IF(rNumericArgs(1) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(1))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(1))//' must be > 0, entered value = '//TRIM(RoundSigDigits(rNumericArgs(1),2)))
END IF
IF(rNumericArgs(2) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(2))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(2))//' must be > 0, entered value = '//TRIM(RoundSigDigits(rNumericArgs(2),2)))
END IF
ENDDO
!Reading WindowGap:DeflectionState
cCurrentModuleObject = 'WindowGap:DeflectionState'
W7DeflectionStates = GetNumObjectsFound(cCurrentModuleObject)
ALLOCATE (DeflectionState(W7DeflectionStates))
DO Loop=1,W7DeflectionStates
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.FALSE.
IsBlank=.FALSE.
! Verify unique names
CALL VerifyName(cAlphaArgs(1),DeflectionState%Name,Loop,IsNotOK,IsBlank,TRIM(CurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cAlphaFieldNames(1))//' has been found.')
CALL ShowContinueError('...All Material names must be unique regardless of subtype.')
CYCLE
ENDIF
DeflectionState(Loop)%Name = cAlphaArgs(1)
DeflectionState(Loop)%DeflectedThickness = rNumericArgs(1)
IF(rNumericArgs(1) < 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(1))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(1))//' must be >= 0, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(1),2)))
END IF
ENDDO
!Reading WindowMaterial:Gap
cCurrentModuleObject = 'WindowMaterial:Gap'
W7MaterialGaps = GetNumObjectsFound(cCurrentModuleObject);
!!ALLOCATE (DeflectionState(W7DeflectionStates))
DO Loop=1,W7MaterialGaps
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.FALSE.
IsBlank=.FALSE.
! Verify unique names
CALL VerifyName(cAlphaArgs(1),Material%Name,MaterNum-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cAlphaFieldNames(1))//' has been found.')
CALL ShowContinueError('...All Material names must be unique regardless of subtype.')
CYCLE
ENDIF
MaterNum = MaterNum + 1
Material(MaterNum)%Group = ComplexWindowGap
Material(MaterNum)%Roughness = Rough
Material(MaterNum)%ROnly = .TRUE.
Material(MaterNum)%Name = cAlphaArgs(1)
Material(MaterNum)%Thickness = rNumericArgs(1)
IF(rNumericArgs(1) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(1))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(1))//' must be > 0, entered '//TRIM(RoundSigDigits(rNumericArgs(1),2)))
END IF
Material(MaterNum)%Pressure = rNumericArgs(2)
IF(rNumericArgs(2) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(2))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(2))//' must be > 0, entered '//TRIM(RoundSigDigits(rNumericArgs(2),2)))
END IF
IF( .NOT. lAlphaFieldBlanks(2) ) THEN
Material(MaterNum)%GasPointer = FindIteminList(cAlphaArgs(2),Material%Name,TotMaterials)
ELSE
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cAlphaFieldNames(1))//' has been found.')
CALL ShowContinueError(TRIM(cCurrentModuleObject)//' does not have assigned WindowMaterial:Gas or WindowMaterial:GasMixutre.')
END IF
IF( .NOT. lAlphaFieldBlanks(3) ) THEN
Material(MaterNum)%DeflectionStatePtr = FindIteminList(cAlphaArgs(3),DeflectionState%Name,W7DeflectionStates)
END IF
if( .NOT. lAlphaFieldBlanks(4) ) THEN
Material(MaterNum)%SupportPillarPtr = FindIteminList(cAlphaArgs(4),SupportPillar%Name,W7SupportPillars)
END IF
ENDDO
!Reading WindowMaterial:ComplexShade
cCurrentModuleObject = 'WindowMaterial:ComplexShade'
TotComplexShades=GetNumObjectsFound(cCurrentModuleObject)
IF(TotComplexShades > 0) THEN
ALLOCATE (ComplexShade(TotComplexShades))! Allocate the array Size to the number of complex shades
ENDIF
DO Loop=1,TotComplexShades
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
IsNotOK=.FALSE.
IsBlank=.FALSE.
! Verify unique names
CALL VerifyName(cAlphaArgs(1),ComplexShade%Name,Loop,IsNotOK,IsBlank,TRIM(CurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cAlphaFieldNames(1))//' has been found.')
CALL ShowContinueError('...All Material names must be unique regardless of subtype.')
CYCLE
ENDIF
MaterNum=MaterNum + 1
Material(MaterNum)%Group = ComplexWindowShade
Material(MaterNum)%Roughness = Rough
Material(MaterNum)%ROnly = .true.
!Assign pointer to ComplexShade
Material(MaterNum)%ComplexShadePtr = Loop
Material(MaterNum)%Name = cAlphaArgs(1)
ComplexShade(Loop)%Name = cAlphaArgs(1)
SELECT CASE (TRIM(cAlphaArgs(2)))
CASE ('OTHERSHADINGTYPE')
ComplexShade(Loop)%LayerType = csOtherShadingType
CASE ('VENETIAN')
ComplexShade(Loop)%LayerType = csVenetian
CASE ('WOVEN')
ComplexShade(Loop)%LayerType = csWoven
CASE ('PERFORATED')
ComplexShade(Loop)%LayerType = csPerforated
CASE ('BSDF')
ComplexShade(Loop)%LayerType = csBSDF
CASE DEFAULT
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cAlphaFieldNames(2))//' has been found.')
CALL ShowContinueError(TRIM(cAlphaFieldNames(2))//' entered value = "'//TRIM(cAlphaArgs(2))// &
'" should be OtherShadingType, Venetian, Woven, Perforated or BSDF.')
END SELECT
ComplexShade(Loop)%Thickness = rNumericArgs(1)
Material(MaterNum)%Thickness = rNumericArgs(1)
ComplexShade(Loop)%Conductivity = rNumericArgs(2)
Material(MaterNum)%Conductivity = rNumericArgs(2)
ComplexShade(Loop)%IRTransmittance = rNumericArgs(3)
ComplexShade(Loop)%FrontEmissivity = rNumericArgs(4)
ComplexShade(Loop)%BackEmissivity = rNumericArgs(5)
! Simon: in heat balance radiation exchange routines AbsorpThermal is used
! and program will crash if value is not assigned. Not sure if this is correct
! or some additional calculation is necessary. Simon TODO
Material(MaterNum)%AbsorpThermal = rNumericArgs(5)
Material(MaterNum)%AbsorpThermalFront = rNumericArgs(4)
Material(MaterNum)%AbsorpThermalBack = rNumericArgs(5)
ComplexShade(Loop)%TopOpeningMultiplier = rNumericArgs(6)
ComplexShade(Loop)%BottomOpeningMultiplier = rNumericArgs(7)
ComplexShade(Loop)%LeftOpeningMultiplier = rNumericArgs(8)
ComplexShade(Loop)%RightOpeningMultiplier = rNumericArgs(9)
ComplexShade(Loop)%FrontOpeningMultiplier = rNumericArgs(10)
ComplexShade(Loop)%SlatWidth = rNumericArgs(11)
ComplexShade(Loop)%SlatSpacing = rNumericArgs(12)
ComplexShade(Loop)%SlatThickness = rNumericArgs(13)
ComplexShade(Loop)%SlatAngle = rNumericArgs(14)
ComplexShade(Loop)%SlatConductivity = rNumericArgs(15)
ComplexShade(Loop)%SlatCurve = rNumericArgs(16)
!IF (Material(MaterNum)%Conductivity > 0.0) THEN
! NominalR(MaterNum)=Material(MaterNum)%Thickness/Material(MaterNum)%Conductivity
!ELSE
! NominalR(MaterNum)=1.0
!ENDIF
IF(rNumericArgs(1) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(1))//' has been found.')
CALL ShowContinueError(trim(cNumericFieldNames(1))//' must be > 0, entered value = '//TRIM(RoundSigDigits(rNumericArgs(1),2)))
END IF
IF(rNumericArgs(2) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(2))//' has been found.')
CALL ShowContinueError(trim(cNumericFieldNames(2))//' must be > 0, entered value = '//TRIM(RoundSigDigits(rNumericArgs(2),2)))
END IF
IF((rNumericArgs(3) < 0.0d0).or.(rNumericArgs(3) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(3))//' has been found.')
CALL ShowContinueError(trim(cNumericFieldNames(3))//' value must be >= 0 and <= 1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(3),2)))
END IF
IF((rNumericArgs(4) < 0.0d0).or.(rNumericArgs(4) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(4))//' has been found.')
CALL ShowContinueError(trim(cNumericFieldNames(4))//' value must be >= 0 and <= 1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(4),2)))
END IF
IF((rNumericArgs(5) < 0.0d0).or.(rNumericArgs(5) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(5))//' has been found.')
CALL ShowContinueError(trim(cNumericFieldNames(5))//' value must be >= 0 and <= 1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(5),2)))
END IF
IF((rNumericArgs(6) < 0.0d0).or.(rNumericArgs(6) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(6))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(6))//' must be >= 0 or <= 1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(6),2)))
END IF
IF((rNumericArgs(7) < 0.0d0).or.(rNumericArgs(7) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(7))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(7))//' must be >=0 or <=1, entered '//TRIM(RoundSigDigits(rNumericArgs(7),2)))
END IF
IF((rNumericArgs(8) < 0.0d0).or.(rNumericArgs(8) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(8))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(8))//' must be >=0 or <=1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(8),2)))
END IF
IF((rNumericArgs(9) < 0.0d0).or.(rNumericArgs(9) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(9))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(9))//' must be >=0 or <=1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(9),2)))
END IF
IF((rNumericArgs(10) < 0.0d0).or.(rNumericArgs(10) > 1.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(10))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(10))//' must be >=0 or <=1, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(10),2)))
END IF
if (ComplexShade(Loop)%LayerType == csVenetian) then
IF(rNumericArgs(11) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(11))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(11))//' must be >0, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(11),2)))
END IF
IF(rNumericArgs(12) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(12))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(12))//' must be >0, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(12),2)))
END IF
IF(rNumericArgs(13) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(13))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(13))//' must be >0, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(13),2)))
END IF
IF((rNumericArgs(14) < -90.0d0).or.(rNumericArgs(14) > 90.0d0)) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(14))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(14))//' must be >=-90 and <=90, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(14),2)))
END IF
IF(rNumericArgs(15) <= 0.0d0) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(15))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(15))//' must be >0, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(15),2)))
END IF
IF((rNumericArgs(16) < 0.0d0).or.((rNumericArgs(16) > 0.0d0).and.(rNumericArgs(16) < (rNumericArgs(11)/2)))) THEN
ErrorsFound = .true.
CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//', object. Illegal value for '// &
TRIM(cNumericFieldNames(16))//' has been found.')
CALL ShowContinueError(TRIM(cNumericFieldNames(16))//' must be =0 or greater than SlatWidth/2, entered value = '// &
TRIM(RoundSigDigits(rNumericArgs(16),2)))
END IF
end if
IF (ErrorsFound) CALL ShowFatalError('Error in complex fenestration material input.')
ENDDO
END SUBROUTINE SetupComplexFenestrationMaterialInput