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) | :: | HeaderString | |||
character(len=*), | intent(inout) | :: | Line | |||
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 ProcessEPWHeader(HeaderString,Line,ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Linda Lawrie
! DATE WRITTEN December 1999
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine processes each header line in the EPW weather file.
! METHODOLOGY EMPLOYED:
! File is positioned to the correct line, then backspaced. This routine
! reads in the line and processes as appropriate.
! REFERENCES:
! na
! USE STATEMENTS:
USE InputProcessor, ONLY: ProcessNumber, FindItemInList, MakeUPPERCase, GetNumObjectsFound, SameString
USE General, ONLY: JulianDay
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=*), INTENT(IN) :: HeaderString
CHARACTER(len=*), INTENT(INOUT) :: Line
LOGICAL, INTENT(INOUT) :: ErrorsFound
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: AFormat="(A)"
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
CHARACTER(len=100) :: Title=Blank
INTEGER :: Count
CHARACTER(len=20) WMO
INTEGER Pos
REAL(r64) Number
LOGICAL IOStatus
INTEGER PMonth,Pday,PWeekDay,PYear,DateType
INTEGER NumHdArgs
LOGICAL ErrFlag
CHARACTER(len=20) ErrNum
INTEGER CurCount
INTEGER CurOne
INTEGER NumEPWHolidays
INTEGER NumGrndTemps
INTEGER endcol
INTEGER TropExtremeCount ! because these can show up as "no dry" need to count and separate.
INTEGER actcount
LOGICAL errflag1
! Strip off Header value from Line
Pos=INDEX(Line,',')
IF (Pos == 0 .and. MakeUPPERCase(HeaderString(1:8)) /= 'COMMENTS') THEN
CALL ShowSevereError('Invalid Header line in in.epw -- no commas')
CALL ShowContinueError('Line='//TRIM(Line))
CALL ShowFatalError('Previous conditions cause termination.')
ENDIF
Line=Line(Pos+1:)
SELECT CASE(MakeUPPERCase(HeaderString))
CASE ('LOCATION')
! LOCATION, A1 [City], A2 [State/Province/Region], A3 [Country],
! A4 [Source], N1 [WMO], N2 [Latitude],
! N3 [Longitude], N4 [Time Zone], N5 [Elevation {m}]
NumHdArgs=9
Count=1
DO WHILE (Count <= NumHdArgs)
Line=ADJUSTL(Line)
Pos=INDEX(Line,',')
IF (Pos == 0) THEN
IF (LEN_TRIM(Line) == 0) THEN
DO WHILE (Pos == 0)
READ(WeatherFileUnitNumber,AFormat) Line
IF (StripCR) THEN
endcol=LEN_TRIM(Line)
IF (endcol > 0) THEN
IF (ICHAR(Line(endcol:endcol)) == iASCII_CR) Line(endcol:endcol)=Blank
ENDIF
ENDIF
Line=ADJUSTL(Line)
Line=MakeUPPERCase(Line)
Pos=INDEX(Line,',')
ENDDO
ELSE
Pos=LEN_TRIM(Line)+1
ENDIF
ENDIF
SELECT CASE(Count)
CASE (1)
Title=TRIM(Line(1:Pos-1))
CASE (2,3,4)
Title=TRIM(Title)//Blank//TRIM(Line(1:Pos-1))
CASE (5)
WMO=TRIM(Line(1:Pos-1))
Title=TRIM(Title)//' WMO#='//TRIM(WMO)
CASE (6,7,8,9)
Number=ProcessNumber(Line(1:Pos-1),ErrFlag)
IF (.not. ErrFlag) THEN
SELECT CASE (Count)
CASE (6)
WeatherFileLatitude=Number
CASE (7)
WeatherFileLongitude=Number
CASE (8)
WeatherFileTimeZone=Number
CASE (9)
WeatherFileElevation=Number
END SELECT
ELSE
CALL ShowSevereError('GetEPWHeader:LOCATION, invalid numeric='//Line(1:Pos-1))
ErrorsFound=.true.
ENDIF
END SELECT
Line=Line(Pos+1:)
Count=Count+1
ENDDO
WeatherFileLocationTitle=ADJUSTL(Title)
CASE ('DESIGN CONDITIONS')
! No action
CASE ('TYPICAL/EXTREME PERIODS')
TropExtremeCount=0
Line=ADJUSTL(Line)
Pos=INDEX(Line,',')
IF (Pos == 0) THEN
IF (LEN_TRIM(Line) == 0) THEN
DO WHILE (Pos == 0 .and. LEN_TRIM(Line) == 0)
READ(WeatherFileUnitNumber,AFormat) Line
Line=ADJUSTL(Line)
Pos=INDEX(Line,',')
ENDDO
ELSE
Pos=LEN_TRIM(Line)+1
ENDIF
ENDIF
NumEPWTypExtSets=ProcessNumber(Line(1:Pos-1),IOStatus)
Line=Line(Pos+1:)
ALLOCATE(TypicalExtremePeriods(NumEPWTypExtSets))
TropExtremeCount=0
Count=1
DO WHILE (Count <= NumEPWTypExtSets)
Line=ADJUSTL(Line)
Pos=INDEX(Line,',')
IF (Pos /= 0) THEN
TypicalExtremePeriods(Count)%Title=TRIM(Line(1:Pos-1))
Line=Line(Pos+1:)
ELSE
CALL ShowWarningError('ProcessEPWHeader: Invalid Typical/Extreme Periods Header(WeatherFile)='// &
TRIM(Line(1:Pos-1)))
CALL ShowContinueError('...on processing Typical/Extreme period #'//TRIM(RoundSigDigits(Count)))
NumEPWTypExtSets=Count-1
EXIT
ENDIF
Pos=INDEX(Line,',')
IF (Pos /= 0) THEN
TypicalExtremePeriods(Count)%TEType=TRIM(Line(1:Pos-1))
Line=Line(Pos+1:)
IF (SameString(TypicalExtremePeriods(Count)%TEType,'EXTREME')) THEN
IF (SameString(TypicalExtremePeriods(Count)%Title(1:36), &
'NO DRY SEASON - WEEK NEAR ANNUAL MAX')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoDrySeasonMax'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:36), &
'NO DRY SEASON - WEEK NEAR ANNUAL MIN')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoDrySeasonMin'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:36), &
'NO WET SEASON - WEEK NEAR ANNUAL MAX')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoWetSeasonMax'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:36), &
'NO WET SEASON - WEEK NEAR ANNUAL MIN')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoWetSeasonMin'
! to account for problems earlier in weather files:
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'NO DRY')) THEN
IF (TropExtremeCount == 0) THEN
TypicalExtremePeriods(Count)%Title='No Dry Season - Week Near Annual Max'
TypicalExtremePeriods(Count)%ShortTitle='NoDrySeasonMax'
TropExtremeCount=TropExtremeCount+1
ELSEIF (TropExtremeCount == 1) THEN
TypicalExtremePeriods(Count)%Title='No Dry Season - Week Near Annual Min'
TypicalExtremePeriods(Count)%ShortTitle='NoDrySeasonMin'
TropExtremeCount=TropExtremeCount+1
ENDIF
ELSE ! make new short titles
IF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'SUMMER')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Summer'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'WINTER')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Winter'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:12),'TROPICAL HOT')) THEN
TypicalExtremePeriods(Count)%ShortTitle='TropicalHot'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:13),'TROPICAL COLD')) THEN
TypicalExtremePeriods(Count)%ShortTitle='TropicalCold'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'AUTUMN')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Autumn'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'NO DRY')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoDrySeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'NO WET')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoWetSeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:4),'WET ')) THEN
TypicalExtremePeriods(Count)%ShortTitle='WetSeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:4),'DRY ')) THEN
TypicalExtremePeriods(Count)%ShortTitle='DrySeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:5),'SPRING')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Spring'
ENDIF
ENDIF
ELSE ! not extreme
IF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'SUMMER')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Summer'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'WINTER')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Winter'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:12),'TROPICAL HOT')) THEN
TypicalExtremePeriods(Count)%ShortTitle='TropicalHot'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:13),'TROPICAL COLD')) THEN
TypicalExtremePeriods(Count)%ShortTitle='TropicalCold'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'AUTUMN')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Autumn'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'NO DRY')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoDrySeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:6),'NO WET')) THEN
TypicalExtremePeriods(Count)%ShortTitle='NoWetSeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:4),'WET ')) THEN
TypicalExtremePeriods(Count)%ShortTitle='WetSeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:4),'DRY ')) THEN
TypicalExtremePeriods(Count)%ShortTitle='DrySeason'
ELSEIF (SameString(TypicalExtremePeriods(Count)%Title(1:5),'SPRING')) THEN
TypicalExtremePeriods(Count)%ShortTitle='Spring'
ENDIF
ENDIF
ELSE
CALL ShowWarningError('ProcessEPWHeader: Invalid Typical/Extreme Periods Header(WeatherFile)='// &
TRIM(TypicalExtremePeriods(Count)%Title)//Blank//TRIM(Line(1:Pos-1)))
CALL ShowContinueError('...on processing Typical/Extreme period #'//TRIM(RoundSigDigits(Count)))
NumEPWTypExtSets=Count-1
EXIT
ENDIF
Pos=INDEX(Line,',')
IF (Pos /= 0) THEN
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound)
IF (DateType /= InvalidDate) THEN
IF (PMonth /= 0 .and. PDay /= 0) THEN
TypicalExtremePeriods(Count)%StartMonth=PMonth
TypicalExtremePeriods(Count)%StartDay=PDay
ENDIF
ELSE
CALL ShowSevereError('ProcessEPWHeader: Invalid Typical/Extreme Periods Start Date Field(WeatherFile)='// &
TRIM(Line(1:Pos-1)))
CALL ShowContinueError('...on processing Typical/Extreme period #'//TRIM(RoundSigDigits(Count)))
ErrorsFound=.true.
ENDIF
Line=Line(Pos+1:)
ENDIF
Pos=INDEX(Line,',')
IF (Pos /= 0) THEN
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound)
IF (DateType /= InvalidDate) THEN
IF (PMonth /= 0 .and. PDay /= 0) THEN
TypicalExtremePeriods(Count)%EndMonth=PMonth
TypicalExtremePeriods(Count)%EndDay=PDay
ENDIF
ELSE
CALL ShowSevereError('ProcessEPWHeader: Invalid Typical/Extreme Periods End Date Field(WeatherFile)='// &
TRIM(Line(1:Pos-1)))
CALL ShowContinueError('...on processing Typical/Extreme period #'//TRIM(RoundSigDigits(Count)))
ErrorsFound=.true.
ENDIF
Line=Line(Pos+1:)
ELSE ! Pos=0, probably last one
CALL ProcessDateString(Line(1:LEN_TRIM(Line)),PMonth,PDay,PWeekDay,DateType,ErrorsFound)
IF (DateType /= InvalidDate) THEN
IF (PMonth /= 0 .and. PDay /= 0) THEN
TypicalExtremePeriods(Count)%EndMonth=PMonth
TypicalExtremePeriods(Count)%EndDay=PDay
ENDIF
ELSE
CALL ShowSevereError('ProcessEPWHeader: Invalid Typical/Extreme Periods End Date Field(WeatherFile)='// &
TRIM(Line(1:Pos-1)))
ErrorsFound=.true.
ENDIF
ENDIF
Count=Count+1
ENDDO
! Process periods to set up other values.
DO Count=1,NumEPWTypExtSets
! JulianDay (Month,Day,LeapYearValue)
SELECT CASE(MakeUPPERCase(TypicalExtremePeriods(Count)%ShortTitle))
CASE ('SUMMER')
IF (SameString(TypicalExtremePeriods(Count)%TEType,'EXTREME')) THEN
TypicalExtremePeriods(Count)%MatchValue = 'SummerExtreme'
TypicalExtremePeriods(Count)%MatchValue1= 'TropicalHot'
TypicalExtremePeriods(Count)%MatchValue2= 'NoDrySeasonMax'
ELSE
TypicalExtremePeriods(Count)%MatchValue = 'SummerTypical'
ENDIF
CASE ('WINTER')
IF (SameString(TypicalExtremePeriods(Count)%TEType,'EXTREME')) THEN
TypicalExtremePeriods(Count)%MatchValue = 'WinterExtreme'
TypicalExtremePeriods(Count)%MatchValue1= 'TropicalCold'
TypicalExtremePeriods(Count)%MatchValue2= 'NoDrySeasonMin'
ELSE
TypicalExtremePeriods(Count)%MatchValue = 'WinterTypical'
ENDIF
CASE ('AUTUMN')
TypicalExtremePeriods(Count)%MatchValue = 'AutumnTypical'
CASE ('SPRING')
TypicalExtremePeriods(Count)%MatchValue = 'SpringTypical'
CASE ('WETSEASON')
TypicalExtremePeriods(Count)%MatchValue = 'WetSeason'
CASE ('DRYSEASON')
TypicalExtremePeriods(Count)%MatchValue = 'DrySeason'
CASE ('NOWETSEASON')
TypicalExtremePeriods(Count)%MatchValue = 'NoWetSeason'
CASE ('NODRYSEASON')
TypicalExtremePeriods(Count)%MatchValue = 'NoDrySeason'
CASE ('NODRYSEASONMAX','NOWETSEASONMAX')
TypicalExtremePeriods(Count)%MatchValue = TypicalExtremePeriods(Count)%ShortTitle
TypicalExtremePeriods(Count)%MatchValue1= 'TropicalHot'
TypicalExtremePeriods(Count)%MatchValue2= 'SummerExtreme'
CASE ('NODRYSEASONMIN','NOWETSEASONMIN')
TypicalExtremePeriods(Count)%MatchValue = TypicalExtremePeriods(Count)%ShortTitle
TypicalExtremePeriods(Count)%MatchValue1= 'TropicalCold'
TypicalExtremePeriods(Count)%MatchValue2= 'WinterExtreme'
CASE ('TROPICALHOT')
TypicalExtremePeriods(Count)%MatchValue = 'TropicalHot'
TypicalExtremePeriods(Count)%MatchValue1= 'SummerExtreme'
TypicalExtremePeriods(Count)%MatchValue2= 'NoDrySeasonMax'
CASE ('TROPICALCOLD')
TypicalExtremePeriods(Count)%MatchValue = 'TropicalCold'
TypicalExtremePeriods(Count)%MatchValue1= 'WinterExtreme'
TypicalExtremePeriods(Count)%MatchValue2= 'NoDrySeasonMin'
CASE DEFAULT
TypicalExtremePeriods(Count)%MatchValue = 'Invalid - no match'
END SELECT
TypicalExtremePeriods(Count)%StartJDay=JulianDay(TypicalExtremePeriods(Count)%StartMonth, &
TypicalExtremePeriods(Count)%StartDay,0)
TypicalExtremePeriods(Count)%EndJDay=JulianDay(TypicalExtremePeriods(Count)%EndMonth, &
TypicalExtremePeriods(Count)%EndDay,0)
IF (TypicalExtremePeriods(Count)%StartJDay <= TypicalExtremePeriods(Count)%EndJDay) THEN
TypicalExtremePeriods(Count)%TotalDays=TypicalExtremePeriods(Count)%EndJDay-TypicalExtremePeriods(Count)%StartJDay+1
ELSE
TypicalExtremePeriods(Count)%TotalDays=JulianDay(12,31,LeapYearAdd)- &
TypicalExtremePeriods(Count)%StartJDay+1+TypicalExtremePeriods(Count)%EndJDay
ENDIF
ENDDO
CASE ('GROUND TEMPERATURES')
! Added for ground surfaces defined with F or c factor method. TH 7/2009
! Assume the 0.5 m set of ground temperatures
! or first set on a weather file, if any.
Pos=INDEX(Line,',')
IF (Pos /= 0) THEN
NumGrndTemps=ProcessNumber(Line(1:Pos-1),ErrFlag)
IF (.not. ErrFlag .AND. NumGrndTemps >=1 ) THEN
Line=Line(Pos+1:)
! skip depth, soil conductivity, soil density, soil specific heat
do count=1,4
Pos=INDEX(Line,',')
if (Pos == 0) then
Line=Blank
exit
endif
Line=Line(Pos+1:)
enddo
GroundTempsFC=0.0d0
actcount=0
do count=1,12 ! take the first set of ground temperatures.
Pos=INDEX(Line,',')
IF (Pos /= 0) THEN
Number=ProcessNumber(Line(1:Pos-1),ErrFlag)
GroundTempsFC(Count) = Number
actcount=actcount+1
ELSE
IF (Len_Trim(Line) > 0) THEN
Number=ProcessNumber(Line(1:Pos-1),ErrFlag)
GroundTempsFC(Count) = Number
actcount=actcount+1
ENDIF
EXIT
ENDIF
Line=Line(Pos+1:)
ENDDO
if (actcount == 12) wthFCGroundTemps=.true.
ENDIF
ENDIF
CASE ('HOLIDAYS/DAYLIGHT SAVING')
!A1, \field LeapYear Observed
! \type choice
! \key Yes
! \key No
! \note Yes if Leap Year will be observed for this file
! \note No if Leap Year days (29 Feb) should be ignored in this file
!A2, \field Daylight Saving Start Day
!A3, \field Daylight Saving End Day
!N1, \field Number of Holidays
!A4, \field Holiday 1 Name
!A5, \field Holiday 1 Day
! etc.
! Start with Minimum number of NumHdArgs
Line=MakeUPPERCase(Line)
NumHdArgs=4
Count=1
DO WHILE (Count <= NumHdArgs)
Line=ADJUSTL(Line)
Pos=INDEX(Line,',')
IF (Pos == 0) THEN
IF (LEN_TRIM(Line) == 0) THEN
DO WHILE (Pos == 0)
READ(WeatherFileUnitNumber,AFormat) Line
IF (StripCR) THEN
endcol=LEN_TRIM(Line)
IF (endcol > 0) THEN
IF (ICHAR(Line(endcol:endcol)) == iASCII_CR) Line(endcol:endcol)=Blank
ENDIF
ENDIF
Line=ADJUSTL(Line)
Line=MakeUPPERCase(Line)
Pos=INDEX(Line,',')
ENDDO
ELSE
Pos=LEN_TRIM(Line)+1
ENDIF
ENDIF
SELECT CASE(Count)
CASE(1)
IF (Line(1:1) == 'Y') THEN
! LeapYear=.true.
WFAllowsLeapYears=.true.
WFLeapYearInd=0 !1
ELSE
! LeapYear=.false.
WFAllowsLeapYears=.false.
WFLeapYearInd=0
ENDIF
CASE(2)
errflag1=ErrorsFound
ErrorsFound=.false.
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound)
IF (DateType /= InvalidDate) THEN
IF (PMonth == 0 .and. PDay == 0) THEN
EPWDaylightSaving=.false.
ELSE
EPWDaylightSaving=.true.
EPWDST%StDateType=DateType
EPWDST%StMon=PMonth
EPWDST%StDay=PDay
EPWDST%STWeekDay=PWeekDay
ENDIF
ELSE
ErrorsFound=errflag1
CALL ShowContinueError('ProcessEPWHeader: Invalid Daylight Saving Period Start Date Field(WeatherFile)='// &
TRIM(Line(1:Pos-1)))
CALL ShowContinueError('...invalid header='//trim(HeaderString))
CALL ShowContinueError('...Setting Weather File DST to false.')
EPWDaylightSaving=.false.
ENDIF
CASE(3)
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound)
IF (EPWDaylightSaving) THEN
IF (DateType /= InvalidDate) THEN
EPWDST%EnDateType=DateType
EPWDST%EnMon=PMonth
EPWDST%EnDay=PDay
EPWDST%EnWeekDay=PWeekDay
ELSE
CALL ShowWarningError('ProcessEPWHeader: Invalid Daylight Saving Period End Date Field(WeatherFile)='// &
TRIM(Line(1:Pos-1)))
CALL ShowContinueError('...Setting Weather File DST to false.')
EPWDaylightSaving=.false.
ENDIF
DST=EPWDST
ENDIF
CASE(4)
NumEPWHolidays=ProcessNumber(Line(1:Pos-1),IOStatus)
NumSpecialDays=NumEPWHolidays+GetNumObjectsFound('RunPeriodControl:SpecialDays')
ALLOCATE(SpecialDays(NumSpecialDays))
NumHdArgs=4+NumEPWHolidays*2
CurCount=0
CASE(5:)
IF (MOD(Count,2) /= 0) THEN
CurCount=CurCount+1
IF (CurCount > NumSpecialDays) THEN
CALL ShowSevereError('Too many SpecialDays')
ErrorsFound=.true.
ELSE
SpecialDays(CurCount)%Name=Line(1:Pos-1)
ENDIF
! Process name
ELSE
IF (CurCount <= NumSpecialDays) THEN
! Process date
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound)
IF (DateType == MonthDay) THEN
SpecialDays(CurCount)%DateType=DateType
SpecialDays(CurCount)%Month=PMonth
SpecialDays(CurCount)%Day=PDay
SpecialDays(CurCount)%WeekDay=0
SpecialDays(CurCount)%CompDate=Pmonth*32+Pday
SpecialDays(CurCount)%Duration=1
SpecialDays(CurCount)%DayType=1
SpecialDays(CurCount)%WthrFile=.true.
ELSEIF (DateType /= InvalidDate) THEN
SpecialDays(CurCount)%DateType=DateType
SpecialDays(CurCount)%Month=PMonth
SpecialDays(CurCount)%Day=PDay
SpecialDays(CurCount)%WeekDay=PWeekDay
SpecialDays(CurCount)%CompDate=0
SpecialDays(CurCount)%Duration=1
SpecialDays(CurCount)%DayType=1
SpecialDays(CurCount)%WthrFile=.true.
ELSEIF (DateType == InvalidDate) THEN
CALL ShowSevereError('Invalid SpecialDay Date Field(WeatherFile)='//TRIM(Line(1:Pos-1)))
ErrorsFound=.true.
ENDIF
ENDIF
ENDIF
END SELECT
Line=Line(Pos+1:)
Count=Count+1
ENDDO
DO Count=1,NumEPWTypExtSets
! JulianDay (Month,Day,LeapYearValue)
TypicalExtremePeriods(Count)%StartJDay=JulianDay(TypicalExtremePeriods(Count)%StartMonth, &
TypicalExtremePeriods(Count)%StartDay,LeapYearAdd)
TypicalExtremePeriods(Count)%EndJDay=JulianDay(TypicalExtremePeriods(Count)%EndMonth, &
TypicalExtremePeriods(Count)%EndDay,LeapYearAdd)
IF (TypicalExtremePeriods(Count)%StartJDay <= TypicalExtremePeriods(Count)%EndJDay) THEN
TypicalExtremePeriods(Count)%TotalDays=TypicalExtremePeriods(Count)%EndJDay-TypicalExtremePeriods(Count)%StartJDay+1
ELSE
TypicalExtremePeriods(Count)%TotalDays=JulianDay(12,31,LeapYearAdd)- &
TypicalExtremePeriods(Count)%StartJDay+1+TypicalExtremePeriods(Count)%EndJDay
ENDIF
ENDDO
CASE ('COMMENTS 1','COMMENTS 2')
CASE ('DATA PERIODS')
! N1, \field Number of Data Periods
! N2, \field Number of Records per hour
! A1, \field Data Period 1 Name/Description
! A2, \field Data Period 1 Start Day of Week
! \type choice
! \key Sunday
! \key Monday
! \key Tuesday
! \key Wednesday
! \key Thursday
! \key Friday
! \key Saturday
! A3, \field Data Period 1 Start Day
! A4, \field Data Period 1 End Day
Line=MakeUPPERCase(Line)
NumHdArgs=2
Count=1
DO WHILE (Count <= NumHdArgs)
Line=ADJUSTL(Line)
Pos=INDEX(Line,',')
IF (Pos == 0) THEN
IF (LEN_TRIM(Line) == 0) THEN
DO WHILE (Pos == 0)
READ(WeatherFileUnitNumber,AFormat) Line
IF (StripCR) THEN
endcol=LEN_TRIM(Line)
IF (endcol > 0) THEN
IF (ICHAR(Line(endcol:endcol)) == iASCII_CR) Line(endcol:endcol)=Blank
ENDIF
ENDIF
Line=ADJUSTL(Line)
Line=MakeUPPERCase(Line)
Pos=INDEX(Line,',')
ENDDO
ELSE
Pos=LEN_TRIM(Line)+1
ENDIF
ENDIF
SELECT CASE(Count)
CASE(1)
NumDataPeriods=ProcessNumber(Line(1:Pos-1),IOStatus)
ALLOCATE(DataPeriods(NumDataPeriods))
NumHdArgs=NumHdArgs+4*NumDataPeriods
IF (NumDataPeriods > 0) THEN
DataPeriods(1:NumDataPeriods)%NumDays=0
ENDIF
CurCount=0
CASE(2)
NumIntervalsPerHour=ProcessNumber(Line(1:Pos-1),IOStatus)
! IF (NumIntervalsPerHour /= 1) THEN
! CALL ShowSevereError('Process EPW: Not ready for more than one interval per hour')
! ErrorsFound=.true.
! ENDIF
CASE(3:)
CurOne=MOD(Count-3,4)
SELECT CASE(CurOne)
CASE(0)
! Description of Data Period
CurCount=CurCount+1
IF (CurCount > NumDataPeriods) THEN
CALL ShowSevereError('Too many data periods')
ErrorsFound=.true.
ELSE
DataPeriods(CurCount)%Name=Line(1:Pos-1)
ENDIF
CASE(1)
! Start Day of Week
IF (CurCount <= NumDataPeriods) THEN
DataPeriods(CurCount)%DayOfWeek=Line(1:Pos-1)
DataPeriods(CurCount)%WeekDay=FindItemInList(DataPeriods(CurCount)%DayOfWeek,DaysOfWeek,7)
IF (DataPeriods(CurCount)%WeekDay == 0) THEN
WRITE(ErrNum,*) CurCount
ErrNum=ADJUSTL(ErrNum)
CALL ShowSevereError('Weather File -- Invalid Start Day of Week for Data Period #'//TRIM(ErrNum)// &
', Invalid day='//TRIM(DataPeriods(CurCount)%DayOfWeek))
ErrorsFound=.true.
ENDIF
ENDIF
CASE(2)
! DataPeriod Start Day
IF (CurCount <= NumDataPeriods) THEN
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound,PYear)
IF (DateType == MonthDay) THEN
DataPeriods(CurCount)%StMon=PMonth
DataPeriods(CurCount)%StDay=PDay
DataPeriods(CurCount)%StYear=PYear
IF (PYear /= 0) DataPeriods(CurCount)%HasYearData=.true.
ELSE
CALL ShowSevereError('Data Periods must be of the form <DayOfYear> or <Month Day> (WeatherFile), found=' &
//TRIM(Line(1:Pos-1)))
ErrorsFound=.true.
ENDIF
ENDIF
CASE(3)
IF (CurCount <= NumDataPeriods) THEN
CALL ProcessDateString(Line(1:Pos-1),PMonth,PDay,PWeekDay,DateType,ErrorsFound,PYear)
IF (DateType == MonthDay) THEN
DataPeriods(CurCount)%EnMon=PMonth
DataPeriods(CurCount)%EnDay=PDay
DataPeriods(CurCount)%EnYear=PYear
IF (PYear == 0 .and. DataPeriods(CurCount)%HasYearData) THEN
CALL ShowWarningError('Data Period (WeatherFile) - Start Date contains year. End Date does not.')
CALL ShowContinueError('...Assuming same year as Start Date for this data.')
DataPeriods(CurCount)%EnYear=DataPeriods(CurCount)%StYear
ENDIF
ELSE
CALL ShowSevereError('Data Periods must be of the form <DayOfYear> or <Month Day>, (WeatherFile) found=' &
//TRIM(Line(1:Pos-1)))
ErrorsFound=.true.
ENDIF
ENDIF
IF (DataPeriods(CurCount)%StYear == 0 .or. DataPeriods(CurCount)%EnYear == 0) THEN
DataPeriods(CurCount)%DataStJDay=JulianDay(DataPeriods(CurCount)%StMon,DataPeriods(CurCount)%StDay,LeapYearAdd)
DataPeriods(CurCount)%DataEnJDay=JulianDay(DataPeriods(CurCount)%EnMon,DataPeriods(CurCount)%EnDay,LeapYearAdd)
IF (DataPeriods(CurCount)%DataStJDay <= DataPeriods(CurCount)%DataEnJDay) THEN
DataPeriods(CurCount)%NumDays=DataPeriods(CurCount)%DataEnJDay-DataPeriods(CurCount)%DataStJDay+1
ELSE
DataPeriods(CurCount)%NumDays=(365-DataPeriods(CurCount)%DataStJDay+1)+(DataPeriods(CurCount)%DataEnJDay-1+1)
ENDIF
ELSE ! weather file has actual year(s)
CALL jgDate(GregorianToJulian,DataPeriods(CurCount)%DataStJDay, &
DataPeriods(CurCount)%StYear,DataPeriods(CurCount)%StMon,DataPeriods(CurCount)%StDay)
CALL jgDate(GregorianToJulian,DataPeriods(CurCount)%DataEnJDay, &
DataPeriods(CurCount)%EnYear,DataPeriods(CurCount)%EnMon,DataPeriods(CurCount)%EnDay)
DataPeriods(CurCount)%NumDays=DataPeriods(CurCount)%DataEnJDay-DataPeriods(CurCount)%DataStJDay+1
ENDIF
! Have processed the last item for this, can set up Weekdays for months
DataPeriods(CurCount)%MonWeekDay=0
IF (.not. ErrorsFound) THEN
CALL SetupWeekDaysByMonth(DataPeriods(CurCount)%StMon,DataPeriods(CurCount)%StDay, &
DataPeriods(CurCount)%WeekDay,DataPeriods(CurCount)%MonWeekDay)
ENDIF
END SELECT
END SELECT
Line=Line(Pos+1:)
Count=Count+1
ENDDO
CASE DEFAULT
CALL ShowFatalError('Invalid EPW Header designation found='//TRIM(HeaderString))
END SELECT
RETURN
END SUBROUTINE ProcessEPWHeader