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.
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 FillWeatherPredefinedEntries
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer
! DATE WRITTEN Feb 2008
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Read the STAT file for the active weather file and summarize in a predefined report.
! The stat file that is attached may have several formats -- from evolution of the
! stat file from the weather converter (or others that produce a similar stat file).
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE OutputReportPredefined
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=1), PARAMETER :: degChar='°'
! LineTypes for reading the stat file
INTEGER, PARAMETER :: StatisticsLine=1
INTEGER, PARAMETER :: LocationLine=2
INTEGER, PARAMETER :: LatLongLine=3
INTEGER, PARAMETER :: ElevationLine=4
INTEGER, PARAMETER :: StdPressureLine=5
INTEGER, PARAMETER :: DataSourceLine=6
INTEGER, PARAMETER :: WMOStationLine=7
INTEGER, PARAMETER :: DesignConditionsLine=8
INTEGER, PARAMETER :: heatingConditionsLine=9
INTEGER, PARAMETER :: coolingConditionsLine=10
INTEGER, PARAMETER :: stdHDDLine=11
INTEGER, PARAMETER :: stdCDDLine=12
INTEGER, PARAMETER :: maxDryBulbLine=13
INTEGER, PARAMETER :: minDryBulbLine=14
INTEGER, PARAMETER :: maxDewPointLine=15
INTEGER, PARAMETER :: minDewPointLine=16
INTEGER, PARAMETER :: wthHDDLine=17
INTEGER, PARAMETER :: wthCDDLine=18
INTEGER, PARAMETER :: KoppenLine=19
INTEGER, PARAMETER :: KoppenDes1Line=20
INTEGER, PARAMETER :: KoppenDes2Line=21
INTEGER, PARAMETER :: AshStdLine=22
INTEGER, PARAMETER :: AshStdDes1Line=23
INTEGER, PARAMETER :: AshStdDes2Line=24
INTEGER, PARAMETER :: AshStdDes3Line=25
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER, EXTERNAL :: GetNewUnitNumber ! External function to "get" a unit number
CHARACTER(len=200) :: lineIn
INTEGER :: statFile
LOGICAL :: fileExists
INTEGER :: lineType = 0
INTEGER :: lineTypeinterim = 0
INTEGER :: readStat
LOGICAL :: isASHRAE
LOGICAL :: iscalc
LOGICAL :: isKoppen
INTEGER :: ashPtr
INTEGER :: lnPtr
INTEGER :: col1
INTEGER :: col2
INTEGER :: col3
INTEGER :: sposlt
INTEGER :: eposlt
INTEGER :: sposlg
INTEGER :: eposlg
INTEGER :: spostz
INTEGER :: epostz
character(len=5) ashDesYear
CHARACTER(2) :: ashZone !ashrae climate zone
CHARACTER(len=MaxNameLength) :: curNameWithSIUnits
CHARACTER(len=MaxNameLength) :: curNameAndUnits
INTEGER :: indexUnitConv
CHARACTER(len=10) :: storeASHRAEHDD
CHARACTER(len=10) :: storeASHRAECDD
LOGICAL :: heatingDesignlinepassed
LOGICAL :: coolingDesignlinepassed
LOGICAL :: desConditionlinepassed
INQUIRE(file='in.stat',EXIST=fileExists)
readStat=0
isASHRAE=.false.
iscalc=.false.
isKoppen=.false.
heatingDesignlinepassed=.false.
coolingDesignlinepassed=.false.
desConditionlinepassed=.false.
storeASHRAEHDD=' '
storeASHRAECDD=' '
lineTypeinterim=0
IF (fileExists) THEN
statFile = GetNewUnitNumber()
OPEN (unit=statFile, file='in.stat', action='READ', iostat=readStat)
IF (readStat /= 0) THEN
CALL ShowFatalError('FillWeatherPredefinedEntries: Could not open file "in.stat" for input (read).')
ENDIF
DO WHILE (readStat == 0) !end of file, or error
lineType=lineTypeinterim
READ(UNIT=statFile,FMT='(A)',IOSTAT=readStat) lineIn
! reconcile line with different versions of stat file
! v7.1 added version as first line.
lineIn=ADJUSTL(lineIn)
if (lineIn(1:10) == 'Statistics') then
lineType=StatisticsLine
elseif (lineIn(1:8) == 'Location') then
lineType=LocationLine
elseif (lineIn(1:1) == '{') then
lineType=LatLongLine
elseif (lineIn(1:9) == 'Elevation') then
lineType=ElevationLine
elseif (lineIn(1:17) == 'Standard Pressure') then
lineType=StdPressureLine
elseif (lineIn(1:11) == 'Data Source') then
lineType=DataSourceLine
elseif (lineIn(1:11) == 'WMO Station') then
lineType=WMOStationLine
elseif (INDEX(lineIn,'Design Conditions') > 0) then
if (.not. desConditionlinepassed) then
desConditionlinepassed=.true.
lineType=DesignConditionsLine
endif
elseif (lineIn(2:8) == 'Heating') then
if (.not. heatingDesignlinepassed) then
heatingDesignlinepassed=.true.
lineType=heatingConditionsLine
endif
elseif (lineIn(2:8) == 'Cooling') then
if (.not. coolingDesignlinepassed) then
coolingDesignlinepassed=.true.
lineType=coolingConditionsLine
endif
elseif (INDEX(lineIn,'(standard) heating degree-days (10°C baseline)') > 0) then
lineType=stdHDDLine
elseif (INDEX(lineIn,'(standard) cooling degree-days (18.3°C baseline)') > 0) then
lineType=stdCDDLine
elseif (INDEX(lineIn,'Maximum Dry Bulb') > 0) then
lineType=maxDryBulbLine
elseif (INDEX(lineIn,'Minimum Dry Bulb') > 0) then
lineType=minDryBulbLine
elseif (INDEX(lineIn,'Maximum Dew Point') > 0) then
lineType=maxDewPointLine
elseif (INDEX(lineIn,'Minimum Dew Point') > 0) then
lineType=minDewPointLine
elseif (INDEX(lineIn,'(wthr file) heating degree-days (10°C baseline)') > 0 .or. &
INDEX(lineIn,'heating degree-days (10°C baseline)') > 0) then
lineType=wthHDDLine
elseif (INDEX(lineIn,'(wthr file) cooling degree-days (18°C baseline)') > 0 .or. &
INDEX(lineIn,'cooling degree-days (18°C baseline)') > 0) then
lineType=wthCDDLine
endif
! these not part of big if/else because sequential
if (lineType == KoppenDes1Line .and. isKoppen) lineType=KoppenDes2Line
if (lineType == KoppenLine .and. isKoppen) lineType=KoppenDes1Line
if (INDEX(lineIn,'(Köppen classification)') > 0) lineType=KoppenLine
if (lineType == AshStdDes2Line) lineType=AshStdDes3Line
if (lineType == AshStdDes1Line) lineType=AshStdDes2Line
if (lineType == AshStdLine) lineType=AshStdDes1Line
if (INDEX(lineIn,'ASHRAE Standards') > 0) lineType=AshStdLine
SELECT CASE (lineType)
CASE (StatisticsLine) ! Statistics for USA_CA_San.Francisco_TMY2
CALL PreDefTableEntry(pdchWthrVal, 'Reference', lineIn(16:))
CASE (LocationLine) ! Location -- SAN_FRANCISCO CA USA
CALL PreDefTableEntry(pdchWthrVal, 'Site:Location', lineIn(12:))
CASE (LatLongLine) ! {N 37° 37'} {W 122° 22'} {GMT -8.0 Hours}
! find the {}
sposlt=INDEX(lineIn,'{')
eposlt=INDEX(lineIn,'}')
IF (sposlt > 0 .and. eposlt > 0) THEN
CALL PreDefTableEntry(pdchWthrVal, 'Latitude', lineIn(sposlt:eposlt))
! redefine so next scan can go with {}
lineIn(sposlt:sposlt)='['
lineIn(eposlt:eposlt)=']'
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Latitude', 'not found')
ENDIF
sposlg=INDEX(lineIn,'{')
eposlg=INDEX(lineIn,'}')
IF (sposlg > 0 .and. eposlg > 0) THEN
CALL PreDefTableEntry(pdchWthrVal, 'Longitude', lineIn(sposlg:eposlg))
! redefine so next scan can go with {}
lineIn(sposlg:sposlg)='['
lineIn(eposlg:eposlg)=']'
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Longitude', 'not found')
ENDIF
spostz=INDEX(lineIn,'{')
epostz=INDEX(lineIn,'}')
IF (spostz > 0 .and. epostz > 0) THEN
CALL PreDefTableEntry(pdchWthrVal, 'Time Zone', lineIn(spostz:epostz))
! redefine so next scan can go with {}
lineIn(spostz:spostz)='['
lineIn(epostz:epostz)=']'
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Time Zone', 'not found')
ENDIF
CASE (ElevationLine) ! Elevation -- 5m above sea level
lnPtr=index(lineIn(13:),'m')
if (lnPtr > 0) then
curNameWithSIUnits = 'Elevation (m) '//lineIn(13+lnPtr+1:)
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(lineIn(13:13+lnPtr-2))),1)))
ELSE
CALL PreDefTableEntry(pdchWthrVal, trim(curNameWithSIUnits), lineIn(13:13+lnPtr-2))
ENDIF
else
CALL PreDefTableEntry(pdchWthrVal, 'Elevation', 'not found')
ENDIF
CASE (StdPressureLine) ! Standard Pressure at Elevation -- 101265Pa
CALL PreDefTableEntry(pdchWthrVal, 'Standard Pressure at Elevation', lineIn(35:))
CASE (DataSourceLine) ! Data Source -- TMY2-23234
CALL PreDefTableEntry(pdchWthrVal, 'Data Source', lineIn(16:))
CASE (WMOStationLine) ! WMO Station 724940
CALL PreDefTableEntry(pdchWthrVal, 'WMO Station', lineIn(13:))
CASE (DesignConditionsLine) ! - Using Design Conditions from "Climate Design Data 2005 ASHRAE Handbook"
ashPtr=INDEX(lineIn,'ASHRAE')
IF (ashPtr .GT. 0) THEN
isASHRAE = .TRUE.
iscalc = .true.
IF (ashPtr > 5) THEN !Objexx:BoundsViolation IF block added to protect against ashPtr<=5
ashDesYear=lineIn(ashPtr-5:ashPtr-1)
ELSE
ashDesYear=''
ENDIF
CALL PreDefTableEntry(pdchWthrVal, 'Weather File Design Conditions ', 'Climate Design Data '// &
ashDesYear//'ASHRAE Handbook')
ELSEIF (INDEX(lineIn,'not calculated') > 0 .or. lineIn == ' ') THEN
iscalc = .false.
CALL PreDefTableEntry(pdchWthrVal, 'Weather File Design Conditions ', 'not calculated, Number of days < 1 year')
ELSE
isASHRAE = .FALSE.
iscalc = .true.
CALL PreDefTableEntry(pdchWthrVal, 'Weather File Design Conditions ', 'Calculated from the weather file')
END IF
CASE (heatingConditionsLine) ! winter/heating design conditions
IF (iscalc) THEN
IF (isASHRAE) THEN
IF (ashDesYear == '2001') THEN
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Heating Design Temperature 99.6% (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,2))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,3))),1))//degChar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99.6% (C)', &
trim(GetColumnUsingTabs(lineIn,2))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99% (C)', &
trim(GetColumnUsingTabs(lineIn,3))//degChar)
ENDIF
ELSE ! 2005 and 2009 are the same
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Heating Design Temperature 99.6% (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,4))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,5))),1))//degChar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99.6% (C)', &
trim(GetColumnUsingTabs(lineIn,4))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99% (C)', &
trim(GetColumnUsingTabs(lineIn,5))//degChar)
ENDIF
ENDIF
ELSE ! from weather file
IF (GetColumnUsingTabs(lineIn,5) == ' ') THEN
col1=3
col2=4
ELSE
col1=4
col2=5
ENDIF
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Heating Design Temperature 99.6% (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,col1))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,col2))),1))//degChar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99.6% (C)', &
trim(GetColumnUsingTabs(lineIn,col1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Heating Design Temperature 99% (C)', &
trim(GetColumnUsingTabs(lineIn,col2))//degChar)
ENDIF
ENDIF
ENDIF
CASE (coolingConditionsLine) ! summer/cooling design conditions
IF (iscalc) THEN
IF (isASHRAE) THEN
IF (ashDesYear == '2001') THEN
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Cooling Design Temperature 0.4% (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,2))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 1% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,4))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 2% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,6))),1))//degChar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 0.4% (C)', &
trim(GetColumnUsingTabs(lineIn,2))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 1% (C)', &
trim(GetColumnUsingTabs(lineIn,4))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 2% (C)', &
trim(GetColumnUsingTabs(lineIn,6))//degChar)
ENDIF
ELSE ! 2005 and 2009 are the same
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Cooling Design Temperature 0.4% (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,5))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 1% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,7))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 2% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,9))),1))//degChar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 0.4% (C)', &
trim(GetColumnUsingTabs(lineIn,5))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 1% (C)', &
trim(GetColumnUsingTabs(lineIn,7))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 2% (C)', &
trim(GetColumnUsingTabs(lineIn,9))//degChar)
ENDIF
ENDIF
ELSE ! from weather file
IF (GetColumnUsingTabs(lineIn,6) == ' ') THEN
col1=3
col2=4
col3=5
ELSE
col1=4
col2=5
col3=6
ENDIF
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Cooling Design Temperature 0.4% (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,col1))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 1% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,col2))),1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 2% (F)', &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(GetColumnUsingTabs(lineIn,col3))),1))//degChar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 0.4% (C)', &
trim(GetColumnUsingTabs(lineIn,col1))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 1% (C)', &
trim(GetColumnUsingTabs(lineIn,col2))//degChar)
CALL PreDefTableEntry(pdchWthrVal, 'Cooling Design Temperature 2% (C)', &
trim(GetColumnUsingTabs(lineIn,col3))//degChar)
ENDIF
END IF
ENDIF
CASE (stdHDDLine) ! - 1745 annual (standard) heating degree-days (10°C baseline)
storeASHRAEHDD=lineIn(3:6)
CASE (stdCDDLine) ! - 464 annual (standard) cooling degree-days (18.3°C baseline)
storeASHRAECDD=lineIn(3:6)
CASE (maxDryBulbLine) ! - Maximum Dry Bulb temperature of 35.6°C on Jul 9
sposlt=INDEX(lineIn,'of')
eposlt=INDEX(lineIn,'C')
sposlt=sposlt+2
eposlt=eposlt-2
if (sposlt > 0 .and. eposlt > 0) then
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Maximum Dry Bulb Temperature (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(lineIn(sposlt:eposlt))),1))//degchar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dry Bulb Temperature (C)', lineIn(sposlt:eposlt)//degchar)
ENDIF
else
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dry Bulb Temperature','not found')
endif
sposlt=INDEX(lineIn,'on')
sposlt=sposlt+2
if (sposlt > 0) then
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dry Bulb Occurs on', lineIn(sposlt:))
else
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dry Bulb Occurs on', 'not found')
endif
CASE (minDryBulbLine) ! - Minimum Dry Bulb temperature of -22.8°C on Jan 7
sposlt=INDEX(lineIn,'of')
eposlt=INDEX(lineIn,'C')
sposlt=sposlt+2
eposlt=eposlt-2
if (sposlt > 0 .and. eposlt > 0) then
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Minimum Dry Bulb Temperature (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(lineIn(sposlt:eposlt))),1))//degchar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dry Bulb Temperature (C)', lineIn(sposlt:eposlt)//degchar)
ENDIF
else
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dry Bulb Temperature','not found')
endif
sposlt=INDEX(lineIn,'on')
sposlt=sposlt+2
if (sposlt > 0) then
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dry Bulb Occurs on', lineIn(sposlt:))
else
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dry Bulb Occurs on', 'not found')
endif
CASE (maxDewPointLine) ! - Maximum Dew Point temperature of 25.6°C on Aug 4
sposlt=INDEX(lineIn,'of')
eposlt=INDEX(lineIn,'C')
sposlt=sposlt+2
eposlt=eposlt-2
if (sposlt > 0 .and. eposlt > 0) then
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Maximum Dew Point Temperature (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(lineIn(sposlt:eposlt))),1))//degchar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dew Point Temperature (C)', lineIn(sposlt:eposlt)//degchar)
ENDIF
else
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dew Point Temperature','not found')
endif
sposlt=INDEX(lineIn,'on')
sposlt=sposlt+2
if (sposlt > 0) then
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dew Point Occurs on', lineIn(sposlt:))
else
CALL PreDefTableEntry(pdchWthrVal, 'Maximum Dew Point Occurs on', 'not found')
endif
CASE (minDewPointLine) ! - Minimum Dew Point temperature of -28.9°C on Dec 31
sposlt=INDEX(lineIn,'of')
eposlt=INDEX(lineIn,'C')
sposlt=sposlt+2
eposlt=eposlt-2
if (sposlt > 0 .and. eposlt > 0) then
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Minimum Dew Point Temperature (C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIP(indexUnitConv,StrToReal(lineIn(sposlt:eposlt))),1))//degchar)
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dew Point Temperature (C)', lineIn(sposlt:eposlt)//degchar)
ENDIF
else
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dew Point Temperature','not found')
endif
sposlt=INDEX(lineIn,'on')
sposlt=sposlt+2
if (sposlt > 0) then
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dew Point Occurs on', lineIn(sposlt:))
else
CALL PreDefTableEntry(pdchWthrVal, 'Minimum Dew Point Occurs on', 'not found')
endif
CASE (wthHDDLine) ! - 1745 (wthr file) annual heating degree-days (10°C baseline)
IF (storeASHRAEHDD /= ' ') THEN
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Standard Heating Degree-Days - base 50°(C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIPDelta(indexUnitConv,StrToReal(storeASHRAEHDD)),1)))
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Standard Heating Degree-Days (base 10°C)', storeASHRAEHDD)
ENDIF
ELSE
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
CALL PreDefTableEntry(pdchWthrVal, 'Standard Heating Degree-Days (base 50°F)', 'not found')
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Standard Heating Degree-Days (base 10°C)', 'not found')
ENDIF
ENDIF
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Weather File Heating Degree-Days - base 50°(C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIPDelta(indexUnitConv,StrToReal(lineIn(3:6))),1)))
CALL PreDefTableEntry(pdchLeedGenData, 'Heating Degree Days', &
trim(RealToStr(ConvertIPDelta(indexUnitConv,StrToReal(lineIn(3:6))),1)))
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Weather File Heating Degree-Days (base 10°C)', lineIn(3:6))
CALL PreDefTableEntry(pdchLeedGenData, 'Heating Degree Days', lineIn(3:6))
ENDIF
CASE (wthCDDLine) ! - 464 (wthr file) annual cooling degree-days (18°C baseline)
IF (storeASHRAECDD /= ' ') THEN
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Standard Cooling Degree-Days - base 65°(C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIPDelta(indexUnitConv,StrToReal(storeASHRAECDD)),1)))
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Standard Cooling Degree-Days (base 18.3°C)', storeASHRAECDD)
ENDIF
ELSE
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
CALL PreDefTableEntry(pdchWthrVal, 'Standard Cooling Degree-Days (base 65°F)', 'not found')
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Standard Cooling Degree-Days (base 18.3°C)', 'not found')
ENDIF
ENDIF
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
curNameWithSIUnits = 'Weather File Cooling Degree-Days - base 64.4°(C)'
CALL LookupSItoIP(curNameWithSIUnits, indexUnitConv, curNameAndUnits)
CALL PreDefTableEntry(pdchWthrVal, trim(curNameAndUnits), &
trim(RealToStr(ConvertIPDelta(indexUnitConv,StrToReal(lineIn(3:6))),1)))
CALL PreDefTableEntry(pdchLeedGenData, 'Cooling Degree Days', &
trim(RealToStr(ConvertIPDelta(indexUnitConv,StrToReal(lineIn(3:6))),1)))
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Weather File Cooling Degree-Days (base 18°C)', lineIn(3:6))
CALL PreDefTableEntry(pdchLeedGenData, 'Cooling Degree Days',lineIn(3:6))
ENDIF
CASE (KoppenLine) ! - Climate type "BSk" (Köppen classification)
IF (INDEX(lineIn,'not shown') == 0) THEN
isKoppen=.true.
IF (lineIn(19:19) .EQ. '"') THEN ! two character classification
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Classification', lineIn(17:18))
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Classification', lineIn(17:19))
END IF
ELSE
isKoppen=.false.
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Recommendation', lineIn(3:))
ENDIF
CASE (KoppenDes1Line) ! - Tropical monsoonal or tradewind-coastal (short dry season, lat. 5-25°)
IF (isKoppen) THEN
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Description', lineIn(3:))
ENDIF
CASE (KoppenDes2Line) ! - Unbearably humid periods in summer, but passive cooling is possible
IF (isKoppen) THEN
IF (LEN_TRIM(lineIn) .GT. 3) THEN ! avoid blank lines
IF (lineIn(3:4) .NE. '**') THEN ! avoid line with warning
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Recommendation', lineIn(3:))
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Recommendation', '')
END IF
ELSE
CALL PreDefTableEntry(pdchWthrVal, 'Köppen Recommendation', '')
END IF
ENDIF
CASE (AshStdLine,AshStdDes1Line,AshStdDes2Line,AshStdDes3Line)
! - Climate type "1A" (ASHRAE Standards 90.1-2004 and 90.2-2004 Climate Zone)**
IF (INDEX(lineIn,'Standards') .GT. 0) THEN
ashZone = lineIn(17:18)
if (ashZone(2:2) == '"') ashZone(2:2)=' '
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Climate Zone', ashZone)
CALL PreDefTableEntry(pdchLeedGenData,'Climate Zone',ashZone)
IF (ashZone .EQ. '1A') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Very Hot-Humid')
ELSEIF (ashZone .EQ. '1B') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Very Hot-Dry')
ELSEIF (ashZone .EQ. '2A') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Hot-Humid')
ELSEIF (ashZone .EQ. '2B') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Hot-Dry')
ELSEIF (ashZone .EQ. '3A') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Warm-Humid')
ELSEIF (ashZone .EQ. '3B') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Warm-Dry')
ELSEIF (ashZone .EQ. '3C') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Warm-Marine')
ELSEIF (ashZone .EQ. '4A') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Mixed-Humid')
ELSEIF (ashZone .EQ. '4B') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Mixed-Dry')
ELSEIF (ashZone .EQ. '4C') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Mixed-Marine')
ELSEIF (ashZone .EQ. '5A') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Cool-Humid')
ELSEIF (ashZone .EQ. '5B') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Cool-Dry')
ELSEIF (ashZone .EQ. '5C') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Cool-Marine')
ELSEIF (ashZone .EQ. '6A') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Cold-Humid')
ELSEIF (ashZone .EQ. '6B') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Cold-Dry')
ELSEIF (ashZone .EQ. '7 ') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Very Cold')
ELSEIF (ashZone .EQ. '8 ') THEN
CALL PreDefTableEntry(pdchWthrVal, 'ASHRAE Description', 'Subarctic')
END IF
END IF
END SELECT
LineIn = ''
lineTypeinterim=0
if (lineType == AshStdDes3Line) lineTypeinterim=0
if (lineType == AshStdDes2Line) lineTypeinterim=AshStdDes2Line
if (lineType == AshStdDes1Line) lineTypeinterim=AshStdDes1Line
if (lineType == AshStdLine) lineTypeinterim=AshStdLine
if (lineType == KoppenDes2Line) lineTypeinterim=0
if (lineType == KoppenDes1Line) lineTypeinterim=KoppenDes1Line
if (lineType == KoppenLine) lineTypeinterim=KoppenLine
END DO
CLOSE(UNIT=statFile)
ENDIF
END SUBROUTINE FillWeatherPredefinedEntries