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 GetWeatherProperties(ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Linda Lawrie
! DATE WRITTEN July 2009
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Weather properties are an advanced concept for simulation. Primarily, these properties are
! used in the test suite runs that have specific requirements for certain properties (such as
! sky temperature).
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! WeatherProperty:SkyTemperature,
! \memo This object is used to override internal sky temperature calculations.
! A1, \field Name
! \reference DesignDays
! \note leave blank for RunPeriods (until we name them)
! \note This field references the applicable design day or runperiod(s) if left blank.
! A2, \field Calculation Type
! \type choice
! \key ScheduleValue
! \key DifferenceScheduleDryBulbValue
! \key DifferenceScheduleDewPointValue
! \key AlgorithmA
! A3; \field Schedule Name
! \type object-list
! \object-list DayScheduleNames
! \object-list ScheduleNames
! USE STATEMENTS:
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, SameString, FindItemInList, VerifyName
USE ScheduleManager, ONLY: GetScheduleIndex,GetDayScheduleIndex
USE DataIPShortCuts
USE General, ONLY: FindNumberInList
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ErrorsFound
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName='GetWeatherProperties:'
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: Item
INTEGER :: IOSTAT
INTEGER :: NumAlpha
INTEGER :: NumNumerics
LOGICAL :: IsNotOk
LOGICAL :: IsBlank
INTEGER :: Found
INTEGER :: envFound
INTEGER :: Count
INTEGER :: schPtr
LOGICAL :: MultipleEnvironments
CHARACTER(len=15) :: units
cCurrentModuleObject='WeatherProperty:SkyTemperature'
NumWPSkyTemperatures=GetNumObjectsFound(cCurrentModuleObject)
ALLOCATE(WPSkyTemperature(NumWPSkyTemperatures)) ! by default, not used.
DO Item=1,NumWPSkyTemperatures
MultipleEnvironments=.false.
CALL GetObjectItem(cCurrentModuleObject,Item,cAlphaArgs,NumAlpha,rNumericArgs,NumNumerics,IOSTAT, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
SELECT CASE (cAlphaArgs(1))
CASE (' ')
Found=0
DO Count=1,NumOfEnvrn
IF (Environment(Count)%KindOfEnvrn /= ksRunPeriodWeather) CYCLE
IF (Environment(Count)%WP_Type1 /= 0) THEN
CALL ShowSevereError(RoutineName//trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))// &
'", indicated Environment Name already assigned.')
IF (Environment(Count)%Title /= Blank) THEN
CALL ShowContinueError('...Environment="'//trim(Environment(Count)%Title)// &
'", already using '//trim(cCurrentModuleObject)//'="'// &
trim(WPSkyTemperature(Environment(Count)%WP_Type1)%Name)//'".')
ELSE
CALL ShowContinueError('... Runperiod Environment, already using '//trim(cCurrentModuleObject)//'="'// &
trim(WPSkyTemperature(Environment(Count)%WP_Type1)%Name)//'".')
ENDIF
ErrorsFound=.true.
ELSE
Environment(Count)%WP_Type1=Item
Found=Count
ENDIF
ENDDO
MultipleEnvironments=.true.
IF (Found == 0) THEN
CALL ShowWarningError('GetWeatherProperties: WeatherProperty:SkyTemperature=blank, no run periods found.')
CALL ShowContinueError('...SkyTemperature will not be applied.')
CYCLE
ENDIF
CASE DEFAULT ! really a name
Found=FindItemInList(cAlphaArgs(1),Environment%Title,NumOfEnvrn)
envFound=Found
IF (Found == 0) THEN
CALL ShowSevereError(RoutineName//trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))// &
'", invalid Environment Name referenced.')
CALL ShowContinueError('...remainder of object not processed.')
ErrorsFound=.true.
CYCLE
ELSE
IF (Environment(Found)%WP_Type1 /= 0) THEN
CALL ShowSevereError(RoutineName//trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))// &
'", indicated Environment Name already assigned.')
CALL ShowContinueError('...Environment="'//trim(Environment(Found)%Title)// &
'", already using '//trim(cCurrentModuleObject)//'="'// &
trim(WPSkyTemperature(Environment(Found)%WP_Type1)%Name)//'".')
ErrorsFound=.true.
ELSE
Environment(Found)%WP_Type1=Item
ENDIF
ENDIF
END SELECT
IF (.not. lAlphaFieldBlanks(1)) THEN
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),WPSkyTemperature%Name,Item-1,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
IF (IsBlank) cAlphaArgs(1)='xxxxx'
ENDIF
WPSkyTemperature(Item)%Name = cAlphaArgs(1) ! Name
ELSE
WPSkyTemperature(Item)%Name = 'All RunPeriods'
ENDIF
! Validate Calculation Type.
IF (SameString(cAlphaArgs(2),'ScheduleValue')) THEN
WPSkyTemperature(Item)%CalculationType=WP_ScheduleValue
WPSkyTemperature(Item)%IsSchedule=.true.
units='[C]'
ELSEIF (SameString(cAlphaArgs(2),'DifferenceScheduleDryBulbValue')) THEN
WPSkyTemperature(Item)%CalculationType=WP_DryBulbDelta
WPSkyTemperature(Item)%IsSchedule=.true.
units='[deltaC]'
ELSEIF (SameString(cAlphaArgs(2),'DifferenceScheduleDewPointValue')) THEN
WPSkyTemperature(Item)%CalculationType=WP_DewPointDelta
WPSkyTemperature(Item)%IsSchedule=.true.
units='[deltaC]'
ELSE
CALL ShowSevereError(RoutineName//trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))// &
'", invalid '//trim(cAlphaFieldNames(2))//'.')
CALL ShowContinueError('...entered value="'//trim(cAlphaArgs(2))//'", should be one of: '// &
'ScheduleValue, DifferenceScheduleDryBulbValue, DifferenceScheduleDewPointValue.')
ErrorsFound=.true.
ENDIF
WPSkyTemperature(Item)%ScheduleName=cAlphaArgs(3)
IF (Environment(Found)%KindOfEnvrn == ksRunPeriodWeather .or. &
Environment(Found)%KindOfEnvrn == ksRunPeriodDesign) THEN
WPSkyTemperature(Item)%ScheduleName=cAlphaArgs(3)
! See if it's a schedule.
Found=GetScheduleIndex(cAlphaArgs(3))
IF (Found == 0) THEN
CALL ShowSevereError(RoutineName//trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))// &
'", invalid '//trim(cAlphaFieldNames(3))//'.')
CALL ShowContinueError('...Entered name="'//trim(cAlphaArgs(3))//'".')
CALL ShowContinueError('...Should be a full year schedule ("Schedule:Year", "Schedule:Compact",'// &
' "Schedule:File", or "Schedule:Constant" objects.')
ErrorsFound=.true.
ELSE
WPSkyTemperature(Item)%IsSchedule=.true.
WPSkyTemperature(Item)%SchedulePtr=Found
ENDIF
ELSE ! See if it's a valid schedule.
Found=GetDayScheduleIndex(cAlphaArgs(3))
IF (Found == 0) THEN
CALL ShowSevereError(RoutineName//trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))// &
'", invalid '//trim(cAlphaFieldNames(3))//'.')
CALL ShowContinueError('...Entered name="'//trim(cAlphaArgs(3))//'".')
CALL ShowContinueError('...Should be a single day schedule ("Schedule:Day:Hourly",'// &
' "Schedule:Day:Interval", or "Schedule:Day:List" objects.')
ErrorsFound=.true.
ELSE
IF (envFound /= 0) THEN
schPtr=FindNumberInList(Found,SPSiteScheduleNamePtr,NumSPSiteScheduleNamePtrs)
IF (schPtr == 0) THEN
NumSPSiteScheduleNamePtrs=NumSPSiteScheduleNamePtrs+1
SPSiteScheduleNamePtr(NumSPSiteScheduleNamePtrs)=Found
SPSiteScheduleUnits(NumSPSiteScheduleNamePtrs)=units
CALL SetupOutputVariable('Sizing Period Site Sky Temperature Schedule Value '//units, &
SPSiteSkyTemperatureScheduleValue(envFound),'Zone','Average',cAlphaArgs(3))
ELSEIF (SPSiteScheduleUnits(schPtr)/= units) THEN
NumSPSiteScheduleNamePtrs=NumSPSiteScheduleNamePtrs+1
SPSiteScheduleNamePtr(NumSPSiteScheduleNamePtrs)=Found
SPSiteScheduleUnits(NumSPSiteScheduleNamePtrs)=units
CALL SetupOutputVariable('Sizing Period Site Sky Temperature Schedule Value '//units, &
SPSiteSkyTemperatureScheduleValue(envFound),'Zone','Average',cAlphaArgs(3))
ENDIF
WPSkyTemperature(Item)%IsSchedule=.true.
WPSkyTemperature(Item)%SchedulePtr=Found
ENDIF
ENDIF
ENDIF
ENDDO
RETURN
END SUBROUTINE GetWeatherProperties