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(in) | :: | initiate | |||
logical, | intent(in), | optional | :: | wthrsim | ||
real(kind=r64), | intent(in), | optional | :: | avgdrybulb |
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 CalcThermalComfortAdaptiveCEN15251(initiate,wthrsim,avgdrybulb)
! SUBROUTINE INFORMATION:
! AUTHOR Tyler Hoyt
! DATE WRITTEN July 2011
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Sets up and carries out CEN-15251 adaptive comfort model calculations.
! Output provided are state variables for the Category I, II, and III
! limits of the model, the comfort temperature, and the 5-day weighted
! moving average of the outdoor air temperature.
! METHODOLOGY EMPLOYED:
! na
USE DataHVACGlobals, ONLY: SysTimeElapsed
USE DataEnvironment, ONLY: OutDryBulbTemp, DayOfYear, Month
USE OutputReportTabular, ONLY: GetColumnUsingTabs, StrToReal
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(IN) :: initiate ! true if supposed to initiate
LOGICAL, INTENT(IN), OPTIONAL :: wthrsim ! true if this is a weather simulation
REAL(r64), INTENT(IN), OPTIONAL :: avgdrybulb ! approximate avg drybulb for design day. will be used as previous period in design day
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64),PARAMETER :: alpha = 0.8d0
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER, EXTERNAL :: GetNewUnitNumber
CHARACTER(len=200) :: epwLine
REAL(r64), SAVE :: avgDryBulbCEN=0.0d0
REAL(r64) :: dryBulb
REAL(r64) :: tComf
REAL(r64) :: tComfLow
REAL(r64), SAVE :: runningAverageCEN=0.0d0
REAL(r64) :: numOccupants
INTEGER :: epwFile
LOGICAL :: epwFileExists
LOGICAL, SAVE :: useEpwData = .false.
LOGICAL, SAVE :: firstDaySet=.false. ! first day is set with initiate -- so do not update
INTEGER :: readStat
INTEGER :: jStartDay
INTEGER :: calcStartDay
INTEGER :: calcStartHr
INTEGER :: calcEndDay
INTEGER :: calcEndHr
INTEGER :: pos
INTEGER :: ind
INTEGER :: i
INTEGER :: j
LOGICAL :: weathersimulation
REAL(r64) :: inavgdrybulb
IF (initiate) THEN ! not optional on initiate=true. would otherwise check for presence
weathersimulation=wthrsim
inavgdrybulb=avgdrybulb
avgDryBulbCEN=0.0d0
runningAverageCEN=0.0d0
ELSE
weathersimulation=.false.
inavgdrybulb=0.0d0
ENDIF
IF (initiate .and. weathersimulation) THEN
INQUIRE(file='in.epw',EXIST=epwFileExists)
readStat=0
IF (epwFileExists) THEN
epwFile = GetNewUnitNumber()
OPEN (unit=epwFile, file='in.epw', action='READ', iostat=readStat)
IF (readStat /= 0) THEN
CALL ShowFatalError('CalcThermalComfortAdaptiveCEN15251: Could not open file "in.epw" for input (read).')
ENDIF
DO i = 1, 9 ! Headers
READ(unit=epwFile,fmt='(A)',iostat=readStat)
END DO
jStartDay = DayOfYear - 1
calcStartDay = jStartDay - 7
IF (calcStartDay > 0) THEN
calcStartHr = 24 * (calcStartDay - 1) + 1
DO i = 1, calcStartHr - 1
READ(unit=epwFile,fmt='(A)',iostat=readStat)
END DO
runningAverageCEN = 0.0d0
DO i = 1, 7
avgDryBulbCEN = 0.0d0
DO j = 1, 24
READ(unit=epwFile,fmt='(A)',iostat=readStat) epwLine
DO ind = 1, 6
pos = INDEX(epwLine,',')
epwLine = epwLine(pos+1:)
END DO
pos = INDEX(epwLine,',')
dryBulb = StrToReal(epwLine(1:pos-1))
avgDryBulbCEN = avgDryBulbCEN + (dryBulb / 24.0d0)
END DO
runningAverageCEN = runningAverageCEN + alpha**(7-i)*avgDryBulbCEN
END DO
ELSE ! Do special things for wrapping the epw
calcEndDay = jStartDay
calcStartDay = calcStartDay + 365
calcEndHr = 24 * calcEndDay
calcStartHr = 24 * (calcStartDay - 1) + 1
DO i = 1, calcEndDay
avgDryBulbCEN = 0.0d0
DO j = 1, 24
READ(unit=epwFile,fmt='(A)',iostat=readStat) epwLine
DO ind = 1, 6
pos = INDEX(epwLine,',')
epwLine = epwLine(pos+1:)
END DO
pos = INDEX(epwLine,',')
dryBulb = StrToReal(epwLine(1:pos-1))
avgDryBulbCEN = avgDryBulbCEN + (dryBulb / 24.0d0)
END DO
runningAverageCEN = runningAverageCEN + alpha**(calcEndDay-i)*avgDryBulbCEN
END DO
DO i = calcEndHr+1, calcStartHr-1
READ(unit=epwFile,fmt='(A)',iostat=readStat)
END DO
DO i = 1, 7-calcEndDay
avgDryBulbCEN = 0.0d0
DO j = 1, 24
READ(unit=epwFile,fmt='(A)',iostat=readStat) epwLine
DO ind = 1, 6
pos = INDEX(epwLine,',')
epwLine = epwLine(pos+1:)
END DO
pos = INDEX(epwLine,',')
dryBulb = StrToReal(epwLine(1:pos-1))
avgDryBulbCEN = avgDryBulbCEN + (dryBulb / 24.0d0)
END DO
runningAverageCEN = runningAverageCEN + alpha**(7-i)*avgDryBulbCEN
END DO
END IF
runningAverageCEN = (1.0d0-alpha) * runningAverageCEN
avgDryBulbCEN = 0.0d0
CLOSE(unit=epwFile)
useEpwData = .true.
firstDaySet=.true.
END IF
ELSEIF (initiate .and. .not. weathersimulation) THEN
runningAverageCEN = inavgdrybulb
avgDryBulbCEN = 0.0d0
ENDIF
IF (initiate) RETURN
IF (BeginDayFlag .and. .not. firstDaySet) THEN
! Update the running average, reset the daily avg
runningAverageCEN = 0.2d0 * runningAverageCEN + 0.8d0 * avgDryBulbCEN
avgDryBulbCEN = 0.0d0
END IF
firstDaySet=.false.
! Update the daily average
IF (BeginHourFlag) THEN
avgDryBulbCEN = avgDryBulbCEN + (OutDryBulbTemp / 24.0d0)
ENDIF
DO PeopleNum = 1, TotPeople
IF(.NOT. People(PeopleNum)%AdaptiveCEN15251) CYCLE
ZoneNum = People(PeopleNum)%ZonePtr
IF (IsZoneDV(ZoneNum) .or. IsZoneUI(ZoneNum)) THEN
AirTemp = TCMF(ZoneNum)
ELSE
AirTemp = ZTAV(ZoneNum)
END IF
RadTemp = CalcRadTemp(PeopleNum)
OpTemp = (AirTemp + RadTemp) / 2.0d0
ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = OpTemp
ThermalComfortData(PeopleNum)%CEN15251RunningMeanOutdoorTemp = runningAverageCEN
IF (runningAverageCEN >= 10.0d0 .and. runningAverageCEN <= 30.0d0) THEN
! Calculate the comfort here (people/output handling loop)
numOccupants = People(PeopleNum)%NumberOfPeople * GetCurrentScheduleValue(People(PeopleNum)%NumberOfPeoplePtr)
tComf = 0.33d0 * runningAverageCEN + 18.8d0
ThermalComfortData(PeopleNum)%TComfCEN15251 = tComf
IF (numOccupants > 0) THEN
IF (runningAverageCEN < 15) THEN
tComfLow = 23.75d0 ! Lower limit is constant in this region
ELSE
tComfLow = tComf
END IF
IF (OpTemp < tComf+2.0d0 .and. OpTemp > tComfLow-2.0d0) THEN
! Within Cat I, II, III Limits
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatI = 1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatII = 1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatIII = 1
ELSE IF (OpTemp < tComf+3.0d0 .and. OpTemp > tComfLow-3.0d0) THEN
! Within Cat II, III Limits
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatI = 0
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatII = 1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatIII = 1
People(PeopleNum)%TimeNotMetCEN15251CatI = People(PeopleNum)%TimeNotMetCEN15251CatI + SysTimeElapsed
ELSE IF (OpTemp < tComf+4.0d0 .and. OpTemp > tComfLow-4.0d0) THEN
! Within Cat III Limits
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatI = 0
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatII = 0
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatIII = 1
People(PeopleNum)%TimeNotMetCEN15251CatI = People(PeopleNum)%TimeNotMetCEN15251CatI + SysTimeElapsed
People(PeopleNum)%TimeNotMetCEN15251CatII = People(PeopleNum)%TimeNotMetCEN15251CatII + SysTimeElapsed
ELSE
! None
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatI = 0
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatII = 0
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatIII = 0
People(PeopleNum)%TimeNotMetCEN15251CatI = People(PeopleNum)%TimeNotMetCEN15251CatI + SysTimeElapsed
People(PeopleNum)%TimeNotMetCEN15251CatII = People(PeopleNum)%TimeNotMetCEN15251CatII + SysTimeElapsed
People(PeopleNum)%TimeNotMetCEN15251CatIII = People(PeopleNum)%TimeNotMetCEN15251CatIII + SysTimeElapsed
END IF
ELSE
! Unoccupied
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatI = -1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatII = -1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatIII = -1
END IF
ELSE
! Monthly temp out of range
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatI = -1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatII = -1
ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveCEN15251CatIII = -1
ThermalComfortData(PeopleNum)%TComfCEN15251 = -1.0d0
END IF
END DO
END SUBROUTINE CalcThermalComfortAdaptiveCEN15251