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 GetStormWindowData(ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN December 2003
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Reads in the storm window data from the input 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 General, ONLY: JulianDay,TrimSigDigits
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:na
! INTERFACE BLOCK SPECIFICATIONS:na
! DERIVED TYPE DEFINITIONS:na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: IOStat ! IO Status when calling get input subroutine
INTEGER :: StormWinNumAlpha ! Number of alpha names being passed
INTEGER :: StormWinNumProp ! Number of properties being passed
INTEGER :: StormWinNum ! Index for storm window number
INTEGER :: loop ! Do loop counter
INTEGER :: SurfNum ! Surface number
INTEGER :: MatNum ! Material number
! FLOW:
! Get the total number of storm window input objects
cCurrentModuleObject='WindowProperty:StormWindow'
TotStormWin = GetNumObjectsFound(cCurrentModuleObject)
IF(TotStormWin == 0) RETURN
ALLOCATE (StormWindow(TotStormWin))
StormWinNum = 0
DO loop = 1,TotStormWin
CALL GetObjectItem(cCurrentModuleObject,loop,cAlphaArgs,StormWinNumAlpha, &
rNumericArgs,StormWinNumProp,IOSTAT, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
StormWinNum=StormWinNum+1
StormWindow(StormWinNum)%BaseWindowNum = FindIteminList(cAlphaArgs(1),Surface%Name,TotSurfaces)
StormWindow(StormWinNum)%StormWinMaterialNum = FindIteminList(cAlphaArgs(2),Material%Name,TotMaterials)
StormWindow(StormWinNum)%StormWinDistance = rNumericArgs(1)
StormWindow(StormWinNum)%MonthOn = rNumericArgs(2)
StormWindow(StormWinNum)%DayOfMonthOn = rNumericArgs(3)
StormWindow(StormWinNum)%DateOn=JulianDay(StormWindow(StormWinNum)%MonthOn,StormWindow(StormWinNum)%DayOfMonthOn,1)
StormWindow(StormWinNum)%MonthOff = rNumericArgs(4)
StormWindow(StormWinNum)%DayOfMonthOff = rNumericArgs(5)
StormWindow(StormWinNum)%DateOff=JulianDay(StormWindow(StormWinNum)%MonthOff,StormWindow(StormWinNum)%DayOfMonthOff,1)
IF (StormWindow(StormWinNum)%DateOn == StormWindow(StormWinNum)%DateOff) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date On = Date Off -- not allowed,'// &
' occured in WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
SELECT CASE (StormWindow(StormWinNum)%MonthOn)
CASE (1,3,5,7,8,10,12)
IF (StormWindow(StormWinNum)%DayOfMonthOn > 31) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date On (Day of Month) ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOn))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
CASE (4,6,9,11)
IF (StormWindow(StormWinNum)%DayOfMonthOn > 30) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date On (Day of Month) ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOn))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
CASE (2)
IF (StormWindow(StormWinNum)%DayOfMonthOn > 29) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date On (Day of Month) ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOn))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
CASE DEFAULT
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date On Month ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%MonthOn))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
END SELECT
SELECT CASE (StormWindow(StormWinNum)%MonthOff)
CASE (1,3,5,7,8,10,12)
IF (StormWindow(StormWinNum)%DayOfMonthOff > 31) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date Off (Day of Month) ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOff))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
CASE (4,6,9,11)
IF (StormWindow(StormWinNum)%DayOfMonthOff > 30) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date Off (Day of Month) ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOff))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
CASE (2)
IF (StormWindow(StormWinNum)%DayOfMonthOff > 29) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date Off (Day of Month) ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOff))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
ENDIF
CASE DEFAULT
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Date Off Month ['// &
TRIM(TrimSigDigits(StormWindow(StormWinNum)%MonthOff))//'],'// &
' invalid for WindowProperty:StormWindow Input #'//TRIM(TrimSigDigits(StormWinNum)))
ErrorsFound=.true.
END SELECT
END DO
! Error checks
DO StormWinNum = 1,TotStormWin
! Require BaseWindowNum be that of an exterior window
SurfNum = StormWindow(StormWinNum)%BaseWindowNum
IF(SurfNum == 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))// &
'" invalid.')
ErrorsFound = .true.
ELSE
IF(Surface(SurfNum)%Class /= SurfaceClass_Window .OR. Surface(SurfNum)%ExtBoundCond /= 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'"')
CALL ShowSevereError('cannot be used with surface='//TRIM(Surface(SurfNum)%Name))
CALL ShowContinueError('because that surface is not an exterior window.')
ErrorsFound = .true.
END IF
END IF
! Require that storm window material be glass
MatNum = StormWindow(StormWinNum)%StormWinMaterialNum
IF(SurfNum > 0) THEN
IF(MatNum == 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'"')
CALL ShowContinueError(TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'" not found as storm window layer.')
ErrorsFound = .true.
ELSE
IF(Material(MatNum)%Group /= WindowGlass) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'"')
CALL ShowContinueError(TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))// &
'must be a WindowMaterial:Glazing or WindowMaterial:Glazing:RefractionExtinctionMethod')
ErrorsFound = .true.
END IF
END IF
END IF
! Error if base window has airflow control
IF(SurfNum > 0) THEN
IF(SurfaceWindow(SurfNum)%AirflowControlType /= 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'"')
CALL ShowContinueError(' cannot be used '// &
'because it is an airflow window (i.e., has WindowProperty:AirflowControl specified)')
ErrorsFound = .true.
END IF
END IF
! Check for reversal of on and off times
IF(SurfNum > 0) THEN
IF((Latitude > 0.0d0 .AND. (StormWindow(StormWinNum)%MonthOn < StormWindow(StormWinNum)%MonthOff)) .OR. &
(Latitude <= 0.0d0 .AND. (StormWindow(StormWinNum)%MonthOn > StormWindow(StormWinNum)%MonthOff))) THEN
CALL ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'" check times that storm window')
CALL ShowContinueError('is put on (month='//TRIM(TrimSigDigits(StormWindow(StormWinNum)%MonthOn))// &
', day='//TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOn))//')'// &
' and taken off (month='//TRIM(TrimSigDigits(StormWindow(StormWinNum)%MonthOff))// &
', day='//TRIM(TrimSigDigits(StormWindow(StormWinNum)%DayOfMonthOff))//');')
CALL ShowContinueError('these times may be reversed for your building latitude='// &
TRIM(TrimSigDigits(Latitude,2))//' deg.')
END IF
END IF
END DO
RETURN
END SUBROUTINE GetStormWindowData