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 CalcThermalComfortAdaptiveASH55(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 ASHRAE55-2010 adaptive comfort model calculations.
          ! Output provided are state variables for the 80% and 90% acceptability limits
          ! in the model, the comfort temperature, and the 30-day running average or
          ! monthly average outdoor air temperature as parsed from the .STAT file.
          ! METHODOLOGY EMPLOYED:
          ! In order for the calculations to be possible the user must provide either
          ! a .STAT file or .EPW file for the purpose of computing a monthly average
          ! temperature or thirty-day running average. The subroutine need only open
          ! the relevant file once to initialize, and then operates within the loop.
USE DataHVACGlobals, ONLY: SysTimeElapsed
USE General, ONLY: InvJulianDay
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:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER, EXTERNAL :: GetNewUnitNumber
CHARACTER(len=200) :: lineIn
CHARACTER(len=200) :: lineAvg
CHARACTER(len=200) :: epwLine
CHARACTER(len=52) :: ioerrmsg
REAL(r64), SAVE :: avgDryBulbASH=0.0d0
REAL(r64) :: dryBulb
REAL(r64), SAVE :: runningAverageASH=0.0d0
REAL(r64), DIMENSION(12), SAVE :: monthlyTemp=0.0d0
REAL(r64) :: tComf
REAL(r64) :: numOccupants
INTEGER :: statFile
INTEGER :: epwFile
INTEGER :: lnPtr
INTEGER :: pMonth
INTEGER :: pDay
LOGICAL :: statFileExists
LOGICAL :: epwFileExists
LOGICAL, SAVE :: useStatData = .false.
LOGICAL, SAVE :: useEpwData = .false.
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
  avgDryBulbASH=0.0d0
  runningAverageASH=0.0d0
  monthlyTemp=0.0d0
  inavgdrybulb=avgdrybulb
ELSE
  weathersimulation=.false.
  inavgdrybulb=0.0d0
ENDIF
IF (initiate .and. weathersimulation) THEN
  INQUIRE(file='in.stat',EXIST=statFileExists)
  INQUIRE(file='in.epw',EXIST=epwFileExists)
  readStat=0
  IF (statFileExists) THEN
    statFile = GetNewUnitNumber()
    OPEN (unit=statFile, file='in.stat', action='READ', iostat=readStat)
    IF (readStat /= 0) THEN
      CALL ShowFatalError('CalcThermalComfortAdaptiveASH55: Could not open file "in.stat" for input (read).')
    ENDIF
    DO WHILE (readStat == 0)
      READ(unit=statFile,fmt='(A)',iostat=readStat) lineIn
      lnPtr = INDEX(lineIn,'Monthly Statistics for Dry Bulb temperatures')
      IF (lnPtr > 0) THEN
        DO i = 1, 7
          READ(unit=statFile,fmt='(A)',iostat=readStat)
        END DO
        READ(unit=statFile,fmt='(A)',iostat=readStat) lineAvg
        EXIT
      ENDIF
    END DO
    CLOSE(unit=statFile)
    DO i = 1, 12
      monthlyTemp(i) =  StrToReal(GetColumnUsingTabs(lineAvg,i+2))
    END DO
    useStatData = .true.
  ELSE IF (epwFileExists) THEN
    epwFile = GetNewUnitNumber()
    OPEN (unit=epwFile, file='in.epw', action='READ', iostat=readStat)
    IF (readStat /= 0) THEN
      CALL ShowFatalError('CalcThermalComfortAdaptiveASH55: 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 - 30
    IF (calcStartDay > 0) THEN
      calcStartHr  = 24 * (calcStartDay - 1) + 1
      DO i = 1, calcStartHr-1
        READ(unit=epwFile,fmt='(A)',iostat=readStat)
      END DO
      DO i = 1, 30
        avgDryBulbASH = 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))
          avgDryBulbASH = avgDryBulbASH + (dryBulb / 24.0d0)
        END DO
        runningAverageASH = (29.0d0 * runningAverageASH + avgDryBulbASH) / 30.0d0
      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
        avgDryBulbASH = 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))
          avgDryBulbASH = avgDryBulbASH + (dryBulb / 24.0d0)
        END DO
        runningAverageASH = (29.0d0 * runningAverageASH + avgDryBulbASH) / 30.0d0
      END DO
      DO i = calcEndHr+1, calcStartHr-1
        READ(unit=epwFile,fmt='(A)',iostat=readStat)
      END DO
      DO i = 1, 30-calcEndDay
        avgDryBulbASH = 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))
          avgDryBulbASH = avgDryBulbASH + (dryBulb / 24.0d0)
        END DO
        runningAverageASH = (29.0d0 * runningAverageASH + avgDryBulbASH) / 30.0d0
      END DO
    END IF
    CLOSE(unit=epwFile)
    useEpwData = .true.
  END IF
ELSEIF (initiate .and. .not. weathersimulation) THEN
  runningAverageASH=inavgdrybulb
  monthlyTemp=inavgdrybulb
  avgDryBulbASH = 0.0d0
END IF
IF (initiate) RETURN
IF (BeginDayFlag .and. useEpwData) THEN
  ! Update the running average, reset the daily avg
  runningAverageASH = (29.0d0 * runningAverageASH + avgDryBulbASH) / 30.0d0
  avgDryBulbASH = 0.0d0
END IF
! If exists BeginMonthFlag we can use it to call InvJulianDay once per month.
IF (BeginDayFlag .and. useStatData) THEN
!  CALL InvJulianDay(DayOfYear,pMonth,pDay,0)
!  runningAverageASH = monthlyTemp(pMonth)
  runningAverageASH = monthlyTemp(Month)
END IF
! Update the daily average
!IF (BeginHourFlag .and. useEpwData) THEN
IF (BeginHourFlag) THEN
  avgDryBulbASH = avgDryBulbASH + (OutDryBulbTemp / 24.0d0)
END IF
DO PeopleNum = 1, TotPeople
  IF(.NOT. People(PeopleNum)%AdaptiveASH55) CYCLE
  ZoneNum = People(PeopleNum)%ZonePtr
  IF (IsZoneDV(ZoneNum) .or. IsZoneUI(ZoneNum)) THEN
    AirTemp = TCMF(ZoneNum)
  ELSE
    AirTemp = ZTAV(ZoneNum)
  ENDIF
  RadTemp = CalcRadTemp(PeopleNum)
  OpTemp = (AirTemp + RadTemp) / 2.0d0
  ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = OpTemp
  ThermalComfortData(PeopleNum)%ASHRAE55RunningMeanOutdoorTemp = runningAverageASH
  IF (runningAverageASH >= 10.0d0 .and. runningAverageASH <= 33.5d0) THEN
    ! Calculate the comfort here  (people/output handling loop)
    numOccupants = People(PeopleNum)%NumberOfPeople * GetCurrentScheduleValue(People(PeopleNum)%NumberOfPeoplePtr)
    tComf = 0.31d0 * runningAverageASH + 17.8d0
    ThermalComfortData(PeopleNum)%TComfASH55 = tComf
    IF (numOccupants > 0) THEN
      IF (OpTemp < tComf+2.5d0 .and. OpTemp > tComf-2.5d0) THEN
        ! 80% and 90% limits okay
        ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5590 = 1
        ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5580 = 1
      ELSE IF (OpTemp < tComf+3.5d0 .and. OpTemp > tComf-3.5d0) THEN
        ! 80% only
        ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5590 = 0
        ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5580 = 1
        People(PeopleNum)%TimeNotMetASH5590 = People(PeopleNum)%TimeNotMetASH5590 + SysTimeElapsed
      ELSE
        ! Neither
        ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5590 = 0
        ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5580 = 0
        People(PeopleNum)%TimeNotMetASH5580 = People(PeopleNum)%TimeNotMetASH5580 + SysTimeElapsed
        People(PeopleNum)%TimeNotMetASH5590 = People(PeopleNum)%TimeNotMetASH5590 + SysTimeElapsed
      END IF
    ELSE
      ! Unoccupied
      ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5590 = -1
      ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5580 = -1
    END IF
  ELSE
    ! Monthly temp out of range
    ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5590 = -1
    ThermalComfortData(PeopleNum)%ThermalComfortAdaptiveASH5580 = -1
    ThermalComfortData(PeopleNum)%TComfASH55 = -1.0d0
  END IF
END DO
END SUBROUTINE CalcThermalComfortAdaptiveASH55