InitVRF Subroutine

private subroutine InitVRF(VRFTUNum, ZoneNum, FirstHVACIteration, OnOffAirFlowRatio, QZnReq)

proc~~initvrf~~UsesGraph proc~initvrf InitVRF module~general General module~general->proc~initvrf module~fluidproperties FluidProperties module~general->module~fluidproperties module~psychrometrics Psychrometrics module~general->module~psychrometrics module~inputprocessor InputProcessor module~inputprocessor->proc~initvrf module~faultsmanager FaultsManager module~inputprocessor->module~faultsmanager module~plantutilities PlantUtilities module~plantutilities->proc~initvrf module~fans Fans module~fans->proc~initvrf module~schedulemanager ScheduleManager module~schedulemanager->proc~initvrf module~schedulemanager->module~fans module~mixedair MixedAir module~schedulemanager->module~mixedair module~dataenvironment DataEnvironment module~dataenvironment->proc~initvrf module~dataenvironment->module~fans module~dataenvironment->module~schedulemanager module~dataenvironment->module~mixedair module~dataenvironment->module~psychrometrics module~mixedair->proc~initvrf module~dataheatbalfansys DataHeatBalFanSys module~dataheatbalfansys->proc~initvrf module~datasizing DataSizing module~datasizing->proc~initvrf module~datasizing->module~inputprocessor module~datasizing->module~mixedair module~datazoneequipment DataZoneEquipment module~datazoneequipment->proc~initvrf module~fluidproperties->proc~initvrf module~dataprecisionglobals DataPrecisionGlobals module~dataprecisionglobals->module~general module~dataprecisionglobals->module~inputprocessor module~dataprecisionglobals->module~plantutilities module~dataprecisionglobals->module~fans module~dataprecisionglobals->module~schedulemanager module~dataprecisionglobals->module~dataenvironment module~dataprecisionglobals->module~mixedair module~dataprecisionglobals->module~dataheatbalfansys module~dataprecisionglobals->module~datasizing module~dataprecisionglobals->module~datazoneequipment module~dataprecisionglobals->module~fluidproperties module~dataglobals DataGlobals module~dataprecisionglobals->module~dataglobals module~dataipshortcuts DataIPShortCuts module~dataprecisionglobals->module~dataipshortcuts module~datasystemvariables DataSystemVariables module~dataprecisionglobals->module~datasystemvariables module~datainterfaces DataInterfaces module~dataprecisionglobals->module~datainterfaces module~emsmanager EMSManager module~dataprecisionglobals->module~emsmanager module~datahvacglobals DataHVACGlobals module~dataprecisionglobals->module~datahvacglobals module~dataprecisionglobals->module~psychrometrics module~dataloopnode DataLoopNode module~dataprecisionglobals->module~dataloopnode module~dataruntimelanguage DataRuntimeLanguage module~dataprecisionglobals->module~dataruntimelanguage module~dataprecisionglobals->module~faultsmanager module~dataairloop DataAirLoop module~dataprecisionglobals->module~dataairloop module~datacontaminantbalance DataContaminantBalance module~dataprecisionglobals->module~datacontaminantbalance module~datasurfaces DataSurfaces module~dataprecisionglobals->module~datasurfaces module~databsdfwindow DataBSDFWindow module~dataprecisionglobals->module~databsdfwindow module~datavectortypes DataVectorTypes module~dataprecisionglobals->module~datavectortypes module~datastringglobals DataStringGlobals module~datastringglobals->module~inputprocessor module~datastringglobals->module~datasystemvariables module~dataglobals->module~inputprocessor module~dataglobals->module~fans module~dataglobals->module~schedulemanager module~dataglobals->module~dataenvironment module~dataglobals->module~mixedair module~dataglobals->module~datasizing module~dataglobals->module~datazoneequipment module~dataglobals->module~fluidproperties module~dataglobals->module~dataipshortcuts module~dataglobals->module~emsmanager module~dataglobals->module~datahvacglobals module~dataglobals->module~psychrometrics module~dataglobals->module~dataloopnode module~dataglobals->module~dataruntimelanguage module~dataglobals->module~faultsmanager module~dataglobals->module~dataairloop module~dataglobals->module~datacontaminantbalance module~dataglobals->module~datasurfaces module~dataglobals->module~databsdfwindow module~dataipshortcuts->module~inputprocessor module~datasystemvariables->module~inputprocessor module~datainterfaces->module~inputprocessor module~datainterfaces->module~plantutilities module~datainterfaces->module~fans module~datainterfaces->module~schedulemanager module~datainterfaces->module~mixedair module~datainterfaces->module~fluidproperties module~datainterfaces->module~emsmanager module~datainterfaces->module~psychrometrics module~datainterfaces->module~faultsmanager module~emsmanager->module~fans module~datahvacglobals->module~fans module~datahvacglobals->module~mixedair module~psychrometrics->module~fans module~dataloopnode->module~fans module~dataloopnode->module~mixedair module~dataruntimelanguage->module~emsmanager module~faultsmanager->module~mixedair module~dataairloop->module~mixedair module~datacontaminantbalance->module~mixedair module~datasurfaces->module~datacontaminantbalance module~databsdfwindow->module~datasurfaces module~datavectortypes->module~datasurfaces module~datavectortypes->module~databsdfwindow
Help

!LKL Discrepancy < 0

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: VRFTUNum
integer, intent(in) :: ZoneNum
logical, intent(in) :: FirstHVACIteration
real(kind=r64), intent(inout) :: OnOffAirFlowRatio
real(kind=r64), intent(out) :: QZnReq

Calls

proc~~initvrf~~CallsGraph proc~initvrf InitVRF checkzoneequipmentlist checkzoneequipmentlist proc~initvrf->checkzoneequipmentlist node node proc~initvrf->node getdensityglycol getdensityglycol proc~initvrf->getdensityglycol initcomponentnodes initcomponentnodes proc~initvrf->initcomponentnodes roundsigdigits roundsigdigits proc~initvrf->roundsigdigits getfanvolflow getfanvolflow proc~initvrf->getfanvolflow zonecomp zonecomp proc~initvrf->zonecomp proc~sizevrf SizeVRF proc~initvrf->proc~sizevrf samestring samestring proc~initvrf->samestring interface~showcontinueerror ShowContinueError proc~initvrf->interface~showcontinueerror plantloop plantloop proc~initvrf->plantloop proc~setcompflowrate SetCompFlowRate proc~initvrf->proc~setcompflowrate trimsigdigits trimsigdigits proc~initvrf->trimsigdigits interface~showwarningerror ShowWarningError proc~initvrf->interface~showwarningerror interface~showrecurringwarningerroratend ShowRecurringWarningErrorAtEnd proc~initvrf->interface~showrecurringwarningerroratend interface~showsevereerror ShowSevereError proc~initvrf->interface~showsevereerror interface~showwarningmessage ShowWarningMessage proc~initvrf->interface~showwarningmessage simoamixer simoamixer proc~initvrf->simoamixer zonesysenergydemand zonesysenergydemand proc~initvrf->zonesysenergydemand proc~setaverageairflow~5 SetAverageAirFlow proc~initvrf->proc~setaverageairflow~5 cvrftutypes cvrftutypes proc~initvrf->cvrftutypes proc~initializeoperatingmode InitializeOperatingMode proc~initvrf->proc~initializeoperatingmode tempcontroltype tempcontroltype proc~initvrf->tempcontroltype zoneequiplist zoneequiplist proc~initvrf->zoneequiplist proc~calcvrf CalcVRF proc~initvrf->proc~calcvrf getcurrentschedulevalue getcurrentschedulevalue proc~initvrf->getcurrentschedulevalue interface~showcontinueerrortimestamp ShowContinueErrorTimeStamp proc~initvrf->interface~showcontinueerrortimestamp proc~sizevrf->roundsigdigits proc~sizevrf->interface~showcontinueerror proc~sizevrf->cvrftutypes proc~sizevrf->proc~calcvrf proc~checkzonesizing CheckZoneSizing proc~sizevrf->proc~checkzonesizing zoneeqsizing zoneeqsizing proc~sizevrf->zoneeqsizing getdxcoilcap getdxcoilcap proc~sizevrf->getdxcoilcap curvevalue curvevalue proc~sizevrf->curvevalue reportsizingoutput reportsizingoutput proc~sizevrf->reportsizingoutput 6 6 proc~sizevrf->6 interface~showmessage ShowMessage proc~sizevrf->interface~showmessage finalzonesizing finalzonesizing proc~sizevrf->finalzonesizing proc~setaverageairflow~5->node proc~setaverageairflow~5->getcurrentschedulevalue proc~initializeoperatingmode->node proc~initializeoperatingmode->proc~setcompflowrate proc~initializeoperatingmode->simoamixer proc~initializeoperatingmode->zonesysenergydemand proc~initializeoperatingmode->tempcontroltype proc~initializeoperatingmode->proc~calcvrf proc~initializeoperatingmode->getcurrentschedulevalue zonethermostatsetpointhi zonethermostatsetpointhi proc~initializeoperatingmode->zonethermostatsetpointhi zonethermostatsetpointlo zonethermostatsetpointlo proc~initializeoperatingmode->zonethermostatsetpointlo zt zt proc~initializeoperatingmode->zt proc~calcvrf->node proc~calcvrf->simoamixer proc~calcvrf->proc~setaverageairflow~5 simdxcoil simdxcoil proc~calcvrf->simdxcoil proc~psyhfntdbw PsyHFnTdbW proc~calcvrf->proc~psyhfntdbw simulatefancomponents simulatefancomponents proc~calcvrf->simulatefancomponents proc~showsevereerror ShowSevereError proc~checkzonesizing->proc~showsevereerror proc~showcontinueerror ShowContinueError proc~checkzonesizing->proc~showcontinueerror proc~showfatalerror ShowFatalError proc~checkzonesizing->proc~showfatalerror proc~showerrormessage ShowErrorMessage proc~showsevereerror->proc~showerrormessage matchcounts matchcounts proc~showsevereerror->matchcounts messagesearch messagesearch proc~showsevereerror->messagesearch createsqliteerrorrecord createsqliteerrorrecord proc~showsevereerror->createsqliteerrorrecord proc~showcontinueerror->proc~showerrormessage updatesqliteerrorrecord updatesqliteerrorrecord proc~showcontinueerror->updatesqliteerrorrecord proc~showfatalerror->roundsigdigits proc~showfatalerror->proc~showerrormessage proc~showfatalerror->createsqliteerrorrecord proc~displaystring DisplayString proc~showfatalerror->proc~displaystring proc~abortenergyplus AbortEnergyPlus proc~showfatalerror->proc~abortenergyplus proc~showerrormessage->proc~showfatalerror proc~showerrormessage->proc~displaystring proc~abortenergyplus->roundsigdigits proc~abortenergyplus->proc~displaystring proc~testairpathintegrity TestAirPathIntegrity proc~abortenergyplus->proc~testairpathintegrity updatesqlitesimulationrecord updatesqlitesimulationrecord proc~abortenergyplus->updatesqlitesimulationrecord checkmarkednodes checkmarkednodes proc~abortenergyplus->checkmarkednodes reportairloopconnections reportairloopconnections proc~abortenergyplus->reportairloopconnections proc~showrecurringerrors ShowRecurringErrors proc~abortenergyplus->proc~showrecurringerrors testcompsetinletoutletnodes testcompsetinletoutletnodes proc~abortenergyplus->testcompsetinletoutletnodes proc~summarizeerrors SummarizeErrors proc~abortenergyplus->proc~summarizeerrors reportsurfaceerrors reportsurfaceerrors proc~abortenergyplus->reportsurfaceerrors reportloopconnections reportloopconnections proc~abortenergyplus->reportloopconnections proc~closemiscopenfiles CloseMiscOpenFiles proc~abortenergyplus->proc~closemiscopenfiles setupnodevarsforreporting setupnodevarsforreporting proc~abortenergyplus->setupnodevarsforreporting closesocket closesocket proc~abortenergyplus->closesocket proc~closeoutopenfiles CloseOutOpenFiles proc~abortenergyplus->proc~closeoutopenfiles proc~reportsurfaces ReportSurfaces proc~abortenergyplus->proc~reportsurfaces testbranchintegrity testbranchintegrity proc~abortenergyplus->testbranchintegrity checkplantonabort checkplantonabort proc~abortenergyplus->checkplantonabort proc~epelapsedtime epElapsedTime proc~abortenergyplus->proc~epelapsedtime proc~epstoptime epStopTime proc~abortenergyplus->proc~epstoptime proc~epsummarytimes epSummaryTimes proc~abortenergyplus->proc~epsummarytimes proc~showmessage ShowMessage proc~abortenergyplus->proc~showmessage checknodeconnections checknodeconnections proc~abortenergyplus->checknodeconnections proc~testairpathintegrity->proc~showsevereerror proc~testairpathintegrity->proc~showcontinueerror airtozonenodeinfo airtozonenodeinfo proc~testairpathintegrity->airtozonenodeinfo nodeid nodeid proc~testairpathintegrity->nodeid proc~showrecurringerrors->roundsigdigits proc~showrecurringerrors->createsqliteerrorrecord proc~showrecurringerrors->updatesqliteerrorrecord proc~showrecurringerrors->proc~showmessage removetrailingzeros removetrailingzeros proc~showrecurringerrors->removetrailingzeros recurringerrors recurringerrors proc~showrecurringerrors->recurringerrors proc~summarizeerrors->matchcounts proc~summarizeerrors->proc~showmessage summaries summaries proc~summarizeerrors->summaries moredetails moredetails proc~summarizeerrors->moredetails closedfsfile closedfsfile proc~closemiscopenfiles->closedfsfile closereportillummaps closereportillummaps proc~closemiscopenfiles->closereportillummaps proc~detailsforsurfaces DetailsForSurfaces proc~reportsurfaces->proc~detailsforsurfaces proc~setupschemecolors SetUpSchemeColors proc~reportsurfaces->proc~setupschemecolors proc~vrmlout VRMLOut proc~reportsurfaces->proc~vrmlout scanforreports scanforreports proc~reportsurfaces->scanforreports proc~dxfoutwireframe DXFOutWireFrame proc~reportsurfaces->proc~dxfoutwireframe proc~costinfoout CostInfoOut proc~reportsurfaces->proc~costinfoout proc~linesout LinesOut proc~reportsurfaces->proc~linesout proc~showwarningerror ShowWarningError proc~reportsurfaces->proc~showwarningerror proc~dxfout DXFOut proc~reportsurfaces->proc~dxfout proc~epstoptime->proc~showfatalerror tstop tstop proc~epstoptime->tstop proc~epsummarytimes->roundsigdigits proc~showmessage->proc~showerrormessage proc~detailsforsurfaces->roundsigdigits proc~detailsforsurfaces->trimsigdigits getschedulename getschedulename proc~detailsforsurfaces->getschedulename oscm oscm proc~detailsforsurfaces->oscm nominalu nominalu proc~detailsforsurfaces->nominalu zone zone proc~detailsforsurfaces->zone framedivider framedivider proc~detailsforsurfaces->framedivider getschedulemaxvalue getschedulemaxvalue proc~detailsforsurfaces->getschedulemaxvalue 2 2 proc~detailsforsurfaces->2 proc~computenominaluwithconvcoeffs ComputeNominalUwithConvCoeffs proc~detailsforsurfaces->proc~computenominaluwithconvcoeffs 3 3 proc~detailsforsurfaces->3 osc osc proc~detailsforsurfaces->osc construct construct proc~detailsforsurfaces->construct 4 4 proc~detailsforsurfaces->4 proc~csurfaceclass cSurfaceClass proc~detailsforsurfaces->proc~csurfaceclass userintconvectioncoeffs userintconvectioncoeffs proc~detailsforsurfaces->userintconvectioncoeffs userextconvectioncoeffs userextconvectioncoeffs proc~detailsforsurfaces->userextconvectioncoeffs surface surface proc~detailsforsurfaces->surface getscheduleminvalue getscheduleminvalue proc~detailsforsurfaces->getscheduleminvalue surfacewindow surfacewindow proc~detailsforsurfaces->surfacewindow proc~setupschemecolors->proc~showwarningerror getobjectitemnum getobjectitemnum proc~setupschemecolors->getobjectitemnum getobjectdefmaxargs getobjectdefmaxargs proc~setupschemecolors->getobjectdefmaxargs proc~matchandsetcolortextstring MatchAndSetColorTextString proc~setupschemecolors->proc~matchandsetcolortextstring getobjectitem getobjectitem proc~setupschemecolors->getobjectitem proc~vrmlout->proc~showcontinueerror proc~vrmlout->proc~showfatalerror proc~vrmlout->proc~showwarningerror proc~vrmlout->zone proc~vrmlout->surface proc~triangulate Triangulate proc~vrmlout->proc~triangulate proc~getnewunitnumber GetNewUnitNumber proc~vrmlout->proc~getnewunitnumber proc~dxfoutwireframe->trimsigdigits proc~dxfoutwireframe->proc~showfatalerror proc~dxfoutwireframe->zone proc~dxfoutwireframe->surface proc~dxfoutwireframe->surfacewindow proc~dxfoutwireframe->proc~getnewunitnumber zonedaylight zonedaylight proc~dxfoutwireframe->zonedaylight dxfcolorno dxfcolorno proc~dxfoutwireframe->dxfcolorno proc~costinfoout->proc~showfatalerror proc~costinfoout->construct proc~costinfoout->proc~csurfaceclass proc~costinfoout->surface proc~costinfoout->proc~getnewunitnumber proc~linesout->roundsigdigits proc~linesout->proc~showcontinueerror proc~linesout->proc~showfatalerror proc~linesout->proc~showwarningerror proc~linesout->proc~csurfaceclass proc~linesout->surface proc~linesout->proc~getnewunitnumber proc~showwarningerror->proc~showerrormessage proc~showwarningerror->matchcounts proc~showwarningerror->messagesearch proc~showwarningerror->createsqliteerrorrecord proc~dxfout->trimsigdigits proc~dxfout->proc~showcontinueerror proc~dxfout->proc~showfatalerror proc~dxfout->proc~showwarningerror proc~dxfout->zone proc~dxfout->surface proc~dxfout->surfacewindow proc~dxfout->proc~triangulate proc~dxfout->proc~getnewunitnumber proc~dxfout->zonedaylight proc~dxfout->dxfcolorno illummapcalc illummapcalc proc~dxfout->illummapcalc proc~computenominaluwithconvcoeffs->surface finditem finditem proc~matchandsetcolortextstring->finditem proc~triangulate->roundsigdigits proc~triangulate->proc~showcontinueerror proc~triangulate->proc~showmessage proc~triangulate->proc~showwarningerror csurfaceclass csurfaceclass proc~triangulate->csurfaceclass proc~generate_ears generate_ears proc~triangulate->proc~generate_ears proc~calcrfflrcoordinatetransformation CalcRfFlrCoordinateTransformation proc~triangulate->proc~calcrfflrcoordinatetransformation proc~calcwallcoordinatetransformation CalcWallCoordinateTransformation proc~triangulate->proc~calcwallcoordinatetransformation proc~polygon_contains_point_2d polygon_contains_point_2d proc~generate_ears->proc~polygon_contains_point_2d proc~angle_2dvector angle_2dvector proc~generate_ears->proc~angle_2dvector
Help

Called By

proc~~initvrf~~CalledByGraph proc~initvrf InitVRF proc~simulatevrf SimulateVRF proc~simulatevrf->proc~initvrf
Help

Source Code


Source Code

SUBROUTINE InitVRF(VRFTUNum, ZoneNum, FirstHVACIteration, OnOffAirFlowRatio, QZnReq)

          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Richard Raustad, FSEC
          !       DATE WRITTEN   August 2010
          !       MODIFIED       July 2012, Chandan Sharma - FSEC: Added zone sys avail managers
          !       RE-ENGINEERED  na

          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine is for initializations of the VRF Components.

          ! METHODOLOGY EMPLOYED:
          ! Uses the status flags to trigger initializations.

          ! REFERENCES:
          ! na

          ! USE STATEMENTS:
  USE DataZoneEquipment, ONLY: ZoneEquipInputsFilled,CheckZoneEquipmentList,VRFTerminalUnit_Num
  USE DataHeatBalFanSys, ONLY: TempControlType, ZT, ZoneThermostatSetPointHi, ZoneThermostatSetPointLo
  USE InputProcessor,    ONLY: SameString
  USE ScheduleManager,   ONLY: GetCurrentScheduleValue
  USE DataEnvironment,   ONLY: StdBaroPress, StdRhoAir, OutDryBulbTemp, OutWetBulbTemp
  USE MixedAir,          ONLY: SimOAMixer, SimOAController
  USE DataZoneEquipment, ONLY: ZoneEquipList
  USE DataSizing,        ONLY: AutoSize
  USE Fans,              ONLY: GetFanVolFlow
  USE General,           ONLY: TrimSigDigits, RoundSigDigits
  USE FluidProperties,   ONLY: GetDensityGlycol
  USE PlantUtilities,    ONLY: InitComponentNodes

  IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine

          ! SUBROUTINE ARGUMENT DEFINITIONS:
  Integer, Intent(IN)      :: VRFTUNum
  INTEGER, INTENT (IN)     :: ZoneNum
  LOGICAL, INTENT(IN)      :: FirstHVACIteration
  REAL(r64), INTENT(InOut) :: OnOffAirFlowRatio
  REAL(r64), INTENT(Out)   :: QZnReq

          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na

          ! INTERFACE BLOCK SPECIFICATIONS
          ! na

          ! DERIVED TYPE DEFINITIONS
          ! na

          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  INTEGER             :: InNode          ! TU inlet node
  INTEGER             :: OutNode         ! TU outlet node
  INTEGER             :: OutsideAirNode  ! TU mixer outside air inlet node
  LOGICAL, SAVE       :: MyOneTimeFlag = .true.                ! False after allocating and initializing subroutine variables
  LOGICAL, SAVE       :: ZoneEquipmentListNotChecked = .TRUE.  ! False after the Zone Equipment List has been checked for items
  LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyEnvrnFlag       ! Flag for initializing at beginning of each new environment
  LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MySizeFlag        ! False after TU has been sized
  LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyBeginTimeStepFlag ! Flag to sense beginning of time step
  LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyVRFFlag         ! used for sizing VRF inputs one time
  LOGICAL, ALLOCATABLE,SAVE, DIMENSION(:) :: MyVRFCondFlag     ! used to reset timer counter
  INTEGER   :: NumTULoop        ! loop counter, number of TU's in list
  INTEGER   :: ELLoop           ! loop counter, number of zone equipment lists
  INTEGER   :: ListLoop         ! loop counter, number of equipment is each list
  INTEGER   :: VRFCond          ! index to VRF condenser
  INTEGER   :: TUIndex          ! index to TU
  INTEGER   :: TUListNum        ! index to VRF AC system terminal unit list
  INTEGER   :: TUListIndex      ! pointer to TU list for this VRF system
  INTEGER   :: IndexToTUInTUList      ! index to TU in TerminalUnilList
  REAL(r64) :: RhoAir           ! air density at InNode
  REAL(r64), SAVE :: CurrentEndTime     ! end time of current time step
  REAL(r64), SAVE :: CurrentEndTimeLast ! end time of last time step
  REAL(r64), SAVE :: TimeStepSysLast    ! system time step on last time step
  REAL(r64) :: TempOutput       ! Sensible output of TU
  REAL(r64) :: LoadToCoolingSP  ! thermostat load to cooling setpoint (W)
  REAL(r64) :: LoadToHeatingSP  ! thermostat load to heating setpoint (W)
  LOGICAL   :: EnableSystem     ! use to turn on secondary operating mode if OA temp limits exceeded
  REAL(r64) :: rho              ! density of water (kg/m3)
  REAL(r64):: OutsideDryBulbTemp ! Outdoor air temperature at external node height


          ! FLOW:

  ! ALLOCATE and Initialize subroutine variables
  IF (MyOneTimeFlag) THEN

    ALLOCATE(MyEnvrnFlag(NumVRFTU))
    ALLOCATE(MySizeFlag(NumVRFTU))
    ALLOCATE(MyVRFFlag(NumVRFTU))
    ALLOCATE(MyBeginTimeStepFlag(NumVRFCond))
    ALLOCATE(MaxDeltaT(NumVRFCond))
    ALLOCATE(MinDeltaT(NumVRFCond))
    ALLOCATE(LastModeCooling(NumVRFCond))
    ALLOCATE(LastModeHeating(NumVRFCond))
    ALLOCATE(HeatingLoad(NumVRFCond))
    ALLOCATE(CoolingLoad(NumVRFCond))
    ALLOCATE(NumCoolingLoads(NumVRFCond))
    ALLOCATE(SumCoolingLoads(NumVRFCond))
    ALLOCATE(NumHeatingLoads(NumVRFCond))
    ALLOCATE(SumHeatingLoads(NumVRFCond))
    ALLOCATE(MyVRFCondFlag(NumVRFCond))
    MyEnvrnFlag = .TRUE.
    MySizeFlag = .TRUE.
    MyVRFFlag = .TRUE.
    MyBeginTimeStepFlag = .TRUE.
    MaxDeltaT  = 0.d0
    MinDeltaT  = 0.d0
    LastModeCooling = .FALSE.
    LastModeHeating = .TRUE.
    NumCoolingLoads = 0
    SumCoolingLoads = 0.d0
    NumHeatingLoads = 0
    SumHeatingLoads = 0.d0

    MyOneTimeFlag = .FALSE.
    MyVRFCondFlag = .TRUE.

  END IF ! IF (MyOneTimeFlag) THEN

  ! identify VRF condenser connected to this TU
  VRFCond = VRFTU(VRFTUNum)%VRFSysNum
  TUListIndex = VRF(VRFCond)%ZoneTUListPtr
  InNode  = VRFTU(VRFTUNum)%VRFTUInletNodeNum
  OutNode = VRFTU(VRFTUNum)%VRFTUOutletNodeNum
  OutsideAirNode = VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum
  IndexToTUInTUList = VRFTU(VRFTUNum)%IndexToTUInTUList

  ! set condenser inlet temp, used as surrogate for OAT (used to check limits of operation)
  IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
    OutsideDryBulbTemp = Node(VRF(VRFCond)%CondenserNodeNum)%Temp
  ELSE
    IF(OutsideAirNode .EQ. 0)THEN
      OutsideDryBulbTemp = OutDryBulbTemp
    ELSE
      OutsideDryBulbTemp = Node(OutsideAirNode)%Temp
    END IF
  END IF

  IF (ALLOCATED(ZoneComp)) THEN
    ZoneComp(VRFTerminalUnit_Num)%ZoneCompAvailMgrs(VRFTUNum)%ZoneNum = ZoneNum
    VRFTU(VRFTUNum)%AvailStatus = ZoneComp(VRFTerminalUnit_Num)%ZoneCompAvailMgrs(VRFTUNum)%AvailStatus
  ENDIF

  ! If all VRF Terminal Units on this VRF AC System have been simulated, reset the IsSimulated flag
  ! The condenser will be simulated after all terminal units have been simulated (see Sub SimulateVRF)
  IF(ALL(TerminalUnitList(TUListIndex)%IsSimulated))THEN
!   this should be the first time through on the next iteration. All TU's and condenser have been simulated.
!   reset simulation flag for each terminal unit
    TerminalUnitList(TUListIndex)%IsSimulated = .FALSE.
!     after all TU's have been simulated, reset operating mode flag if necessary
      IF(LastModeHeating(VRFCond) .AND. CoolingLoad(VRFCond))THEN
        LastModeCooling(VRFCond) = .TRUE.
        LastModeHeating(VRFCond) = .FALSE.
!        SwitchedMode(VRFCond)    = .TRUE.
      END IF
      IF(LastModeCooling(VRFCond) .AND. HeatingLoad(VRFCond))THEN
        LastModeHeating(VRFCond) = .TRUE.
        LastModeCooling(VRFCond) = .FALSE.
!        SwitchedMode(VRFCond)    = .TRUE.
      END IF
  END IF ! IF(ALL(TerminalUnitList(VRFTU(VRFTUNum)%TUListIndex)%IsSimulated))THEN

  ! one-time check to see if VRF TU's are on Zone Equipment List or issue warning
  IF(ZoneEquipmentListNotChecked)THEN
    IF(ZoneEquipInputsFilled)THEN
      ZoneEquipmentListNotChecked=.FALSE.
      DO TUListNum = 1, NumVRFTULists
        DO NumTULoop=1,TerminalUnitList(TUListNum)%NumTUInList
          TUIndex = TerminalUnitList(TUListNum)%ZoneTUPtr(NumTULoop)
          EquipList: DO ELLoop=1,NumOfZones  ! NumofZoneEquipLists
            IF (ZoneEquipList(ELLoop)%Name == ' ') CYCLE    ! dimensioned by NumOfZones.  Only valid ones have names.
            DO ListLoop=1,ZoneEquipList(ELLoop)%NumOfEquipTypes
              IF (.NOT. SameString(ZoneEquipList(ELLoop)%EquipType(ListLoop),cVRFTUTypes(VRFTU(TUIndex)%VRFTUType_Num)))CYCLE
              IF (.NOT. SameString(ZoneEquipList(ELLoop)%EquipName(ListLoop), VRFTU(TUIndex)%Name)) CYCLE
              VRFTU(TUIndex)%ZoneNum = ELLoop
              IF(VRF(VRFTU(TUIndex)%VRFSysNum)%MasterZonePTR == ELLoop)THEN
                VRF(VRFTU(TUIndex)%VRFSysNum)%MasterZoneTUIndex = TUIndex
              END IF
              EXIT EquipList
            ENDDO
          ENDDO EquipList
        ENDDO

        IF (CheckZoneEquipmentList(cVRFTUTypes(VRFTU(TUIndex)%VRFTUType_Num),VRFTU(TUIndex)%Name)) CYCLE
        CALL ShowSevereError('InitVRF: VRF Terminal Unit = [' &
           //TRIM(cVRFTUTypes(VRFTU(TUIndex)%VRFTUType_Num))//','//TRIM(VRFTU(TUIndex)%Name)//  &
           '] is not on any ZoneHVAC:EquipmentList.  It will not be simulated.')
        CALL ShowContinueError('...The VRF AC System associated with this terminal unit may also not be simulated.')
    ENDDO
    END IF ! IF(ZoneEquipInputsFilled) THEN
  ENDIF ! IF(ZoneEquipmentListNotChecked)THEN

  ! Size TU
  IF (MySizeFlag(VRFTUNum)) THEN
    IF ( .NOT. SysSizingCalc) THEN
      CALL SizeVRF(VRFTUNum)
      TerminalUnitList(TUListIndex)%TerminalUnitNotSizedYet(IndexToTUInTUList) = .FALSE.
      MySizeFlag(VRFTUNum) = .FALSE.
    END IF ! IF ( .NOT. SysSizingCalc) THEN
  END IF ! IF (MySizeFlag(VRFTUNum)) THEN


! Do the Begin Environment initializations
  IF (BeginEnvrnFlag .and. MyEnvrnFlag(VRFTUNum)) THEN

    !Change the Volume Flow Rates to Mass Flow Rates

    RhoAir = StdRhoAir
    ! set the mass flow rates from the input volume flow rates
    VRFTU(VRFTUNum)%MaxCoolAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxCoolAirVolFlow
    VRFTU(VRFTUNum)%CoolOutAirMassFlow = RhoAir*VRFTU(VRFTUNum)%CoolOutAirVolFlow
    VRFTU(VRFTUNum)%MaxHeatAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxHeatAirVolFlow
    VRFTU(VRFTUNum)%HeatOutAirMassFlow = RhoAir*VRFTU(VRFTUNum)%HeatOutAirVolFlow
    VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow
    VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow = RhoAir*VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow
    VRFTU(VRFTUNum)%NoCoolHeatOutAirMassFlow = RhoAir*VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
    ! set the node max and min mass flow rates
    ! outside air mixer is optional, check that node num > 0
    IF(OutsideAirNode .GT. 0)THEN
      Node(OutsideAirNode)%MassFlowRateMax = MAX(VRFTU(VRFTUNum)%CoolOutAirMassFlow,VRFTU(VRFTUNum)%HeatOutAirMassFlow)
      Node(OutsideAirNode)%MassFlowRateMin = 0.0d0
      Node(OutsideAirNode)%MassFlowRateMinAvail = 0.0d0
    END IF
    Node(OutNode)%MassFlowRateMax = MAX(VRFTU(VRFTUNum)%MaxCoolAirMassFlow,VRFTU(VRFTUNum)%MaxHeatAirMassFlow)
    Node(OutNode)%MassFlowRateMin = 0.0d0
    Node(OutNode)%MassFlowRateMinAvail = 0.0d0
    Node(InNode)%MassFlowRateMax = MAX(VRFTU(VRFTUNum)%MaxCoolAirMassFlow,VRFTU(VRFTUNum)%MaxHeatAirMassFlow)
    Node(InNode)%MassFlowRateMin = 0.0d0
    Node(InNode)%MassFlowRateMinAvail = 0.0d0
    IF(VRFTU(VRFTUNum)%VRFTUOAMixerRelNodeNum .GT. 0)THEN
      Node(VRFTU(VRFTUNum)%VRFTUOAMixerRelNodeNum)%MassFlowRateMinAvail = 0.0d0
    END IF

    MyEnvrnFlag(VRFTUNum) = .FALSE.

    IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
      rho = GetDensityGlycol(PlantLoop(VRF(VRFCond)%SourceLoopNum)%FluidName, &
                         InitconvTemp, &
                         PlantLoop(VRF(VRFCond)%SourceLoopNum)%FluidIndex, &
                         'InitVRF')
      VRF(VRFCond)%WaterCondenserDesignMassFlow = VRF(VRFCond)%WaterCondVolFlowRate * rho

      CALL InitComponentNodes( 0.d0,VRF(VRFCond)%WaterCondenserDesignMassFlow, &
                                 VRF(VRFCond)%CondenserNodeNum, &
                                 VRF(VRFCond)%CondenserOutletNodeNum, &
                                 VRF(VRFCond)%SourceLoopNum, &
                                 VRF(VRFCond)%SourceLoopSideNum, &
                                 VRF(VRFCond)%SourceBranchNum, &
                                 VRF(VRFCond)%SourceCompNum)
    END IF
!    IF(MyVRFCondFlag(VRFCond))THEN
      VRF(VRFCond)%HRTimer      = 0.d0
      VRF(VRFCond)%ModeChange   = .FALSE.
      VRF(VRFCond)%HRModeChange = .FALSE.
      MyVRFCondFlag(VRFCond)    = .FALSE.
!    END IF
  END IF ! IF (BeginEnvrnFlag .and. MyEnvrnFlag(VRFTUNum)) THEN

  ! reset environment flag for next environment
  IF (.not. BeginEnvrnFlag) THEN
    MyEnvrnFlag(VRFTUNum) = .TRUE.
    MyVRFCondFlag(VRFCond) = .TRUE.
  ENDIF

  ! one-time checks of flow rate vs fan flow rate
  IF(MyVRFFlag(VRFTUNum))THEN
    IF(.NOT. SysSizingCalc)THEN
      IF(VRFTU(VRFTUNum)%ActualFanVolFlowRate /= Autosize)THEN

        IF (VRFTU(VRFTUNum)%MaxCoolAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('... has Supply Air Flow Rate During Cooling Operation > Max Fan Volume Flow Rate, should be <=')
          CALL ShowContinueError('... Supply Air Flow Rate During Cooling Operation = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxCoolAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Max Fan Volume Flow Rate                      = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
          CALL ShowContinueError('...the supply air flow rate during cooling operation will be reduced'// &
                                 ' to match and the simulation continues.')
          VRFTU(VRFTUNum)%MaxCoolAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
        ENDIF

        IF (VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('... has Supply Air Flow Rate When No Cooling is Needed > Max Fan Volume Flow Rate, should be <=')
          CALL ShowContinueError('... Supply Air Flow Rate When No Cooling is Needed = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Max Fan Volume Flow Rate                       = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
          CALL ShowContinueError('...the supply air flow rate when no cooling is needed will be reduced'// &
                                 ' to match and the simulation continues.')
          VRFTU(VRFTUNum)%MaxNoCoolAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
        ENDIF

        IF(VRFTU(VRFTUNum)%CoolOutAirVolFlow .GT. VRFTU(VRFTUNum)%MaxCoolAirVolFlow)THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('...The Outdoor Air Flow Rate During Cooling Operation exceeds the Supply Air'// &
                                 ' Flow Rate During Cooling Operation.')
          CALL ShowContinueError('...Outdoor Air Flow Rate During Cooling Operation = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%CoolOutAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Supply Air Flow Rate During Cooling Operation = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxCoolAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('...the outdoor air flow rate will be reduced to match and the simulation continues.')
          VRFTU(VRFTUNum)%CoolOutAirVolFlow = VRFTU(VRFTUNum)%MaxCoolAirVolFlow
        END IF

        IF (VRFTU(VRFTUNum)%MaxHeatAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('... has Supply Air Flow Rate During Heating Operation > Max Fan Volume Flow Rate, should be <=')
          CALL ShowContinueError('... Supply Air Flow Rate During Heating Operation = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxHeatAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Max Fan Volume Flow Rate                      = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
          CALL ShowContinueError('...the supply air flow rate during cooling operation will be reduced'// &
                                 ' to match and the simulation continues.')
          VRFTU(VRFTUNum)%MaxHeatAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
        ENDIF

        IF (VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('... has Supply Air Flow Rate When No Heating is Needed > Max Fan Volume Flow Rate, should be <=')
          CALL ShowContinueError('... Supply Air Flow Rate When No Heating is Needed = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Max Fan Volume Flow Rate                       = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
          CALL ShowContinueError('...the supply air flow rate when no cooling is needed will be reduced'// &
                                 ' to match and the simulation continues.')
          VRFTU(VRFTUNum)%MaxNoHeatAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
        ENDIF

        IF(VRFTU(VRFTUNum)%HeatOutAirVolFlow .GT. VRFTU(VRFTUNum)%MaxHeatAirVolFlow)THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('...The Outdoor Air Flow Rate During Heating Operation exceeds the Supply Air'// &
                                 ' Flow Rate During Heating Operation.')
          CALL ShowContinueError('...Outdoor Air Flow Rate During Heating Operation = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%HeatOutAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Supply Air Flow Rate During Heating Operation = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%MaxHeatAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('...the outdoor air flow rate will be reduced to match and the simulation continues.')
          VRFTU(VRFTUNum)%HeatOutAirVolFlow = VRFTU(VRFTUNum)%MaxHeatAirVolFlow
        END IF

        IF (VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow > VRFTU(VRFTUNum)%ActualFanVolFlowRate) THEN
          CALL ShowWarningError('InitVRF: VRF Terminal Unit = [' &
             //TRIM(cVRFTUTypes(VRFTU(VRFTUNum)%VRFTUType_Num))//', "'//TRIM(VRFTU(VRFTUNum)%Name)//'"]')
          CALL ShowContinueError('... has a Outdoor Air Flow Rate When No Cooling or Heating is Needed > '// &
                                 'Max Fan Volume Flow Rate, should be <=')
          CALL ShowContinueError('... Outdoor Air Flow Rate When No Cooling or Heating is Needed = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow,4))//' m3/s')
          CALL ShowContinueError('... Max Fan Volume Flow Rate                                   = '// &
                                 TRIM(RoundSigDigits(VRFTU(VRFTUNum)%ActualFanVolFlowRate,4))//' m3/s')
          CALL ShowContinueError('...the outdoor air flow rate when no cooling or heating is needed will be reduced'// &
                                 ' to match and the simulation continues.')
          VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow = VRFTU(VRFTUNum)%ActualFanVolFlowRate
        ENDIF


        IF(VRFTU(VRFTUNum)%ActualFanVolFlowRate .GT. 0.0d0)THEN
          VRFTU(VRFTUNum)%HeatingSpeedRatio = VRFTU(VRFTUNum)%MaxHeatAirVolFlow/VRFTU(VRFTUNum)%ActualFanVolFlowRate
          VRFTU(VRFTUNum)%CoolingSpeedRatio = VRFTU(VRFTUNum)%MaxCoolAirVolFlow/VRFTU(VRFTUNum)%ActualFanVolFlowRate
        END IF

        MyVRFFlag(VRFTUNum) = .FALSE.
      ELSE
        CALL GetFanVolFlow(VRFTU(VRFTUNum)%FanIndex,VRFTU(VRFTUNum)%ActualFanVolFlowRate)
      END IF
    END IF
  END IF ! IF(MyVRFFlag(VRFTUNum))THEN

  ! calculate end time of current time step to determine if max capacity reset is required
  CurrentEndTime = CurrentTime + SysTimeElapsed

  ! Initialize the maximum allowed terminal unit capacity. Total terminal unit capacity must not
  ! exceed the available condenser capacity. This variable is used to limit the terminal units
  ! providing more capacity than allowed. Example: TU loads are 1-ton, 2-ton, 3-ton, and 4-ton connected
  ! to a condenser having only 9-tons available. This variable will be set to 3-tons and the 4-ton
  ! terminal unit will be limited to 3-tons (see SimVRFCondenser where this variable is calculated).
  IF(CurrentEndTime .GT. CurrentEndTimeLast .OR. TimeStepSysLast .GT. TimeStepSys .OR. &
     FirstHVACIteration .AND. MyBeginTimeStepFlag(VRFCond))THEN
    MaxCoolingCapacity(VRFCond) = MaxCap
    MaxHeatingCapacity(VRFCond) = MaxCap
    MyBeginTimeStepFlag(VRFCond) = .FALSE.
  END IF

  IF(.NOT. FirstHVACIteration)MyBeginTimeStepFlag(VRFCond) = .TRUE.

  ! Do the following initializations (every time step).

  TimeStepSysLast = TimeStepSys
  CurrentEndTimeLast = CurrentEndTime

!  TUListNum = VRFTU(VRFTUNum)%TUListIndex

  IF (VRFTU(VRFTUNum)%FanOpModeSchedPtr .GT. 0) THEN
    IF (GetCurrentScheduleValue(VRFTU(VRFTUNum)%FanOpModeSchedPtr) .EQ. 0.0d0) THEN
      VRFTU(VRFTUNum)%OpMode = CycFanCycCoil
    ELSE
      VRFTU(VRFTUNum)%OpMode = ContFanCycCoil
    END IF
  END IF

  ! if condenser is off, all terminal unit coils are off
!!!LKL Discrepancy < 0
  IF (GetCurrentScheduleValue(VRF(VRFCond)%SchedPtr) .EQ. 0.0d0) THEN
    HeatingLoad(VRFCond) = .FALSE.
    CoolingLoad(VRFCond) = .FALSE.
  ELSE

!*** Operating Mode Initialization done at beginning of each iteration ***!
!*** assumes all TU's and Condeser were simulated last iteration ***!
!*** this code is done ONCE each iteration when all TU's IsSimulated flag is FALSE ***!
    ! Determine operating mode prior to simulating any terminal units connected to a VRF condenser
    ! this should happen at the beginning of a time step where all TU's are polled to see what
    ! mode the heat pump condenser will operate in
    IF(.NOT. ANY(TerminalUnitList(TUListIndex)%IsSimulated))THEN
      CALL InitializeOperatingMode(FirstHVACIteration,VRFCond,TUListIndex,OnOffAirFlowRatio)
    END IF  ! IF(.NOT. ANY(TerminalUnitList(TUListNum)%IsSimulated))THEN
!*** End of Operating Mode Initialization done at beginning of each iteration ***!

    ! disable VRF system when outside limits of operation based on OAT
    EnableSystem = .FALSE. ! flag used to switch operating modes when OAT is outside operating limits
    IF(CoolingLoad(VRFCond))THEN
      IF((OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATCooling .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATCooling) .AND. &
          ANY(TerminalUnitList(TUListIndex)%CoolingCoilPresent))THEN
        CoolingLoad(VRFCond) = .FALSE.
        ! test if heating load exists, account for thermostat control type
        SELECT CASE(VRF(VRFCond)%ThermostatPriority)
          CASE(LoadPriority, ZonePriority)
            IF(SumHeatingLoads(VRFCond) .GT. 0.d0)EnableSystem = .TRUE.
          CASE(ThermostatOffsetPriority)
            IF(MinDeltaT(VRFCond) .LT. 0.d0)EnableSystem = .TRUE.
          CASE(ScheduledPriority, MasterThermostatPriority)
            ! can't switch modes if scheduled (i.e., would be switching to unscheduled mode)
            ! or master TSTAT used (i.e., master zone only has a specific load - can't switch)
          CASE DEFAULT
        END SELECT
        IF(EnableSystem)THEN
          IF((OutsideDryBulbTemp .GE. VRF(VRFCond)%MinOATHeating .AND. OutsideDryBulbTemp .LE. VRF(VRFCond)%MaxOATHeating) .AND. &
              ANY(TerminalUnitList(TUListIndex)%HeatingCoilPresent))THEN
            HeatingLoad(VRFCond) = .TRUE.
          ELSE
          IF(ANY(TerminalUnitList(TUListIndex)%CoolingCoilAvailable))THEN
            IF(VRF(VRFCond)%CoolingMaxTempLimitIndex == 0)THEN
              CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
              CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Cooling Mode Limits have '// &
                                   'been exceeded and VRF system is disabled.')
              IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
                CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature           = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
              ELSE
                CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature                 = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
              END IF
              CALL ShowContinueError('... Cooling Minimum Outdoor Unit Inlet Temperature = '// &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MinOATCooling,3)))
              CALL ShowContinueError('... Cooling Maximum Outdoor Unit Inlet Temperature = '//  &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATCooling,3)))
              CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Cooling Mode limits.')
            END IF
            CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//  &
                 TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max cooling temperature limit error continues...',  &
                 VRF(VRFCond)%CoolingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
          END IF
          END IF
        ELSE
          IF(ANY(TerminalUnitList(TUListIndex)%CoolingCoilAvailable))THEN
          IF(VRF(VRFCond)%CoolingMaxTempLimitIndex == 0)THEN
            CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
            CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Cooling Mode Limits have '// &
                                   'been exceeded and VRF system is disabled.')
            IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
              CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature           = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
            ELSE
              CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature                 = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
            END IF
            CALL ShowContinueError('... Cooling Minimum Outdoor Unit Inlet Temperature = '// &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MinOATCooling,3)))
            CALL ShowContinueError('... Cooling Maximum Outdoor Unit Inlet Temperature = '//  &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATCooling,3)))
            CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Cooling Mode limits.')
          END IF
          CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//  &
                 TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max cooling temperature limit error continues...',  &
                 VRF(VRFCond)%CoolingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
        END IF
        END IF
      END IF
    ELSEIF(HeatingLoad(VRFCond))THEN
      IF((OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATHeating .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATHeating) .AND. &
          ANY(TerminalUnitList(TUListIndex)%HeatingCoilPresent))THEN
        HeatingLoad(VRFCond) = .FALSE.
        ! test if heating load exists, account for thermostat control type
        SELECT CASE(VRF(VRFCond)%ThermostatPriority)
          CASE(LoadPriority, ZonePriority)
            IF(SumCoolingLoads(VRFCond) .LT. 0.d0)EnableSystem = .TRUE.
          CASE(ThermostatOffsetPriority)
            IF(MaxDeltaT(VRFCond) .GT. 0.d0)EnableSystem = .TRUE.
          CASE(ScheduledPriority, MasterThermostatPriority)
          CASE DEFAULT
        END SELECT
        IF(EnableSystem)THEN
          IF((OutsideDryBulbTemp .GE. VRF(VRFCond)%MinOATCooling .AND. OutsideDryBulbTemp .LE. VRF(VRFCond)%MaxOATCooling) .AND. &
              ANY(TerminalUnitList(TUListIndex)%CoolingCoilPresent))THEN
            CoolingLoad(VRFCond) = .TRUE.
          ELSE
            IF(ANY(TerminalUnitList(TUListIndex)%HeatingCoilAvailable))THEN
            IF(VRF(VRFCond)%HeatingMaxTempLimitIndex == 0)THEN
              CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
              CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Heating Mode Limits '// &
                                   'have been exceeded and VRF system is disabled.')
              IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
                CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature           = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
              ELSE
                CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature             = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
              ENDIF
              CALL ShowContinueError('... Heating Minimum Outdoor Unit Inlet Temperature = '// &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MinOATHeating,3)))
              CALL ShowContinueError('... Heating Maximum Outdoor Unit Inlet Temperature = '//  &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATHeating,3)))
              CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Heating Mode limits.')
            END IF
            CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//  &
                   TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max heating temperature limit error continues...',  &
                   VRF(VRFCond)%HeatingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
          END IF
          END IF
        ELSE
          IF(ANY(TerminalUnitList(TUListIndex)%HeatingCoilAvailable))THEN
          IF(VRF(VRFCond)%HeatingMaxTempLimitIndex == 0)THEN
            CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
            CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Operating Temperature in Heating Mode Limits '// &
                                   'have been exceeded and VRF system is disabled.')
            IF(VRF(VRFCond)%CondenserType == WaterCooled) THEN
              CALL ShowContinueError('... Outdoor Unit Inlet Water Temperature           = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
            ELSE
              CALL ShowContinueError('... Outdoor Unit Inlet Air Temperature             = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
            END IF
            CALL ShowContinueError('... Heating Minimum Outdoor Unit Inlet Temperature = '// &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MinOATHeating,3)))
            CALL ShowContinueError('... Heating Maximum Outdoor Unit Inlet Temperature = '//  &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATHeating,3)))
            CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Heating Mode limits.')
          END IF
          CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//  &
                   TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Pump min/max heating temperature limit error continues...',  &
                   VRF(VRFCond)%HeatingMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
        END IF
        END IF
      END IF
    END IF

  END IF ! IF (GetCurrentScheduleValue(VRF(VRFCond)%SchedPtr) .EQ. 0.0) THEN

! initialize terminal unit flow rate
  IF(HeatingLoad(VRFCond) .OR. &
    (VRF(VRFCond)%HeatRecoveryUsed .AND. TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList)))THEN
    IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
      Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
      Node(OutsideAirNode)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
    ELSE
      Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
    END IF
  ELSE IF(CoolingLoad(VRFCond) .OR. &
         (VRF(VRFCond)%HeatRecoveryUsed .AND. TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList)))THEN
    IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
      Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
      Node(OutsideAirNode)%MassFlowRate = VRFTU(VRFTUNum)%CoolOutAirMassFlow
    ELSE
      Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
    END IF
  ELSE
    IF(LastModeCooling(VRFCond))THEN
      IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
        Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
        Node(OutsideAirNode)%MassFlowRate  = VRFTU(VRFTUNum)%NoCoolHeatOutAirMassFlow
      ELSE
        Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
      END IF
    ELSEIF(LastModeHeating(VRFCond))THEN
      IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
        Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
        Node(OutsideAirNode)%MassFlowRate  = VRFTU(VRFTUNum)%NoCoolHeatOutAirMassFlow
      ELSE
        Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
      END IF
    END IF
  END IF

  IF(VRFTU(VRFTUNum)%OAMixerUsed)CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)

  OnOffAirFlowRatio = 1.0d0

  ! these flags are used in Subroutine CalcVRF to turn on the correct coil (heating or cooling)
  ! valid operating modes
  ! Heat Pump (heat recovery flags are set to FALSE):
  ! CoolingLoad(VRFCond) - TU can only operate in this mode if heat recovery is not used and there is a cooling load
  ! HeatingLoad(VRFCond) - TU can only operate in this mode if heat recovery is not used and there is a heating load
  ! Heat Recovery (heat pump flags are set same as for Heat Pump operation):
  ! TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) - TU will operate in this mode if heat recovery is used
  ! TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) - TU will operate in this mode if heat recovery is used

    QZnReq = ZoneSysEnergyDemand(VRFTU(VRFTUNum)%ZoneNum)%RemainingOutputRequired
    IF(ABS(QZnReq) .LT. SmallLoad) QZnReq = 0.d0
    LoadToCoolingSP = ZoneSysEnergyDemand(VRFTU(VRFTUNum)%ZoneNum)%RemainingOutputReqToCoolSP
    ! set initial terminal unit operating mode for heat recovery
    ! operating mode for non-heat recovery set above using CoolingLoad(VRFCond) or HeatingLoad(VRFCond) variables
    ! first turn off terminal unit
    TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
    TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
    ! then set according to LoadToXXXXingSP variables
    IF(LoadToCoolingSP .LT. -1.d0*SmallLoad)THEN
      TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
      TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
    END IF
    LoadToHeatingSP = ZoneSysEnergyDemand(VRFTU(VRFTUNum)%ZoneNum)%RemainingOutputReqToHeatSP
    IF(LoadToHeatingSP .GT. SmallLoad)THEN
      TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
      TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
    END IF
    IF(LoadToCoolingSP > 0.d0 .AND. LoadToHeatingSP < 0.d0)QZnReq=0.d0

    ! next check for overshoot when constant fan mode is used
    ! check operating load to see if OA will overshoot setpoint temperature when constant fan mode is used
    IF(VRFTU(VRFTUNum)%OpMode == ContFanCycCoil)THEN
      CALL SetCompFlowRate(VRFTUNum, VRFCond, .TRUE.)
      CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
      ! If the Terminal Unit has a net cooling capacity (TempOutput < 0) and
      ! the zone temp is above the Tstat heating setpoint (QToHeatSetPt < 0)
      ! see if the terminal unit operation will exceed the setpoint
      !
      ! 4 tests here to cover all possibilities:
      ! IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .LT. 0.0d0)THEN
      ! ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .GT. 0.0d0)THEN
      ! ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .LT. 0.0d0)THEN
      ! ELSE IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .GT. 0.0d0)THEN
      ! END IF
      ! could compress these to 2 complex IF's but logic inside each would get more complex
      !
      IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .LT. 0.0d0)THEN
        ! If the net cooling capacity overshoots the heating setpoint count as heating load
        IF(TempOutput < LoadToHeatingSP)THEN
          ! Don't count as heating load unless mode is allowed. Also check for floating zone.
          IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleCoolingSetPoint .AND. &
            TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
            IF(.NOT. LastModeHeating(VRFCond))THEN
              ! system last operated in cooling mode, change air flows and repeat coil off capacity test
              IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
                Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
                Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
                CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
              ELSE
                Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
              END IF
              CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
              ! if zone temp will overshoot, pass the LoadToHeatingSP as the load to meet
              IF(TempOutput < LoadToHeatingSP)THEN
                QZnReq = LoadToHeatingSP
                TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
                TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
              END IF
            ELSE
              ! last mode was heating, zone temp will overshoot heating setpoint, reset QznReq to LoadtoHeatingSP
              QZnReq = LoadToHeatingSP
              TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
              TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
            END IF
          END IF
        ELSE IF(TempOutput > LoadToCoolingSP .AND. LoadToCoolingSP < 0.d0)THEN
!       If the net cooling capacity does not meet the zone cooling load enable cooling
          QZnReq = LoadToCoolingSP
          TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
          TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
        ELSE IF(TempOutput < LoadToCoolingSP .AND. LoadToCoolingSP < 0.d0)THEN
!       If the net cooling capacity meets the zone cooling load but does not overshoot heating setpoint
          QZnReq = 0.d0
          TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
          TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
        END IF
!     If the terminal unit has a net heating capacity and the zone temp is below the Tstat cooling setpoint
!     see if the terminal unit operation will exceed the setpoint
      ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .GT. 0.0d0)THEN
!       If the net heating capacity overshoots the cooling setpoint count as cooling load
        IF(TempOutput > LoadToCoolingSP)THEN
!         Don't count as cooling load unless mode is allowed. Also check for floating zone.
          IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleHeatingSetPoint .AND. &
             TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
            IF(.NOT. LastModeCooling(VRFCond))THEN
              IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
                Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
                Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%CoolOutAirMassFlow
                CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
              ELSE
                Node(VRFTU(VRFTUNum)%VRFTUInletNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
              END IF
              CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
              ! if zone temp will overshoot, pass the LoadToCoolingSP as the load to meet
              IF(TempOutput > LoadToCoolingSP)THEN
                QZnReq = LoadToCoolingSP
                TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
                TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
              END IF
            ELSE
              QZnReq = LoadToCoolingSP
              TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
              TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
            END IF
          END IF
        ELSE IF(TempOutput .LT. LoadToHeatingSP)THEN
!         Don't count as heating load unless mode is allowed. Also check for floating zone.
          IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleCoolingSetPoint .AND. &
             TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
            IF(.NOT. LastModeHeating(VRFCond))THEN
              IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
                Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
                Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
                CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
              ELSE
                Node(VRFTU(VRFTUNum)%VRFTUInletNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
              END IF
              CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
              ! if zone temp will overshoot, pass the LoadToHeatingSP as the load to meet
              IF(TempOutput < LoadToHeatingSP)THEN
                QZnReq = LoadToHeatingSP
                TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
                TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
              END IF
            ELSE
              QZnReq = LoadToHeatingSP
              TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
              TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
            END IF
          END IF
        ELSE IF(TempOutput > LoadToHeatingSP .AND. TempOutput < LoadToCoolingSP)THEN
!         If the net capacity does not overshoot either setpoint
          QZnReq = 0.d0
          TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
          TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
        ELSE
!         If the net heating capacity meets the zone heating load but does not overshoot cooling setpoint
          QZnReq = 0.d0
          TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
          TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
        END IF
!     If the terminal unit has a net heating capacity and the zone temp is above the Tstat cooling setpoint
!     see if the terminal unit operation will exceed the setpoint
      ELSE IF(TempOutput .GT. 0.0d0 .AND. LoadToCoolingSP .LT. 0.0d0)THEN
!       If the net heating capacity overshoots the cooling setpoint count as cooling load
!       Don't count as cooling load unless mode is allowed. Also check for floating zone.
        IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleHeatingSetPoint .AND. &
           TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
          IF(.NOT. LastModeCooling(VRFCond))THEN
            IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
              Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
              Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%CoolOutAirMassFlow
              CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
            ELSE
              Node(VRFTU(VRFTUNum)%VRFTUInletNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
            END IF
            CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
            ! if zone temp will overshoot, pass the LoadToCoolingSP as the load to meet
            IF(TempOutput > LoadToCoolingSP)THEN
              QZnReq = LoadToCoolingSP
              TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
              TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
            END IF
          ! last mode was cooling, zone temp will overshoot cooling setpoint, reset QznReq to LoadtoCoolingSP
          ELSE
            QZnReq = LoadToCoolingSP
            TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
            TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
          END IF
        END IF
      ! If the Terminal Unit has a net cooling capacity (TempOutput < 0) and
      ! the zone temp is below the Tstat heating setpoint (QToHeatSetPt > 0)
      ! see if the terminal unit operation will exceed the setpoint
      ELSE IF(TempOutput < 0.0d0 .AND. LoadToHeatingSP .GT. 0.0d0)THEN
        ! Don't count as heating load unless mode is allowed. Also check for floating zone.
        IF(TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. SingleCoolingSetPoint .AND. &
          TempControlType(VRFTU(VRFTUNum)%ZoneNum) .NE. 0)THEN
          IF(.NOT. LastModeHeating(VRFCond))THEN
            ! system last operated in cooling mode, change air flows and repeat coil off capacity test
            IF(VRFTU(VRFTUNum)%OAMixerUsed)THEN
              Node(VRFTU(VRFTUNum)%VRFTUOAMixerRetNodeNum)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
              Node(VRFTU(VRFTUNum)%VRFTUOAMixerOANodeNum)%MassFlowRate = VRFTU(VRFTUNum)%HeatOutAirMassFlow
              CALL SimOAMixer(VRFTU(VRFTUNum)%OAMixerName,FirstHVACIteration,VRFTU(VRFTUNum)%OAMixerIndex)
            ELSE
              Node(InNode)%MassFlowRate = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
            END IF
            CALL CalcVRF(VRFTUNum,FirstHVACIteration,0.0d0,TempOutput,OnOffAirFlowRatio)
            ! if zone temp will overshoot, pass the LoadToHeatingSP as the load to meet
            IF(TempOutput < LoadToHeatingSP)THEN
              QZnReq = LoadToHeatingSP
              TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
              TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
            END IF
          ELSE
            ! last mode was heating, zone temp will overshoot heating setpoint, reset QznReq to LoadtoHeatingSP
            QZnReq = LoadToHeatingSP
            TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
            TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
          END IF
        END IF
      END IF
    END IF ! IF(VRFTU(VRFTUNum)%OpMode == ContFanCycCoil)THEN

  IF(VRF(VRFCond)%HeatRecoveryUsed)THEN
   IF(OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATHeatRecovery .OR. &
      OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATHeatRecovery)THEN
      IF(ANY(TerminalUnitList(TUListIndex)%HRCoolRequest) .OR. &
        ANY(TerminalUnitList(TUListIndex)%HRHeatRequest))THEN
          IF(VRF(VRFCond)%HRMaxTempLimitIndex == 0)THEN
            CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
            CALL ShowContinueError('...InitVRF: VRF Heat Pump Min/Max Outdoor Temperature in Heat Recovery Mode Limits '// &
                                   'have been exceeded and VRF heat recovery is disabled.')
            CALL ShowContinueError('... Outdoor Dry-Bulb Temperature                       = '// &
                                   TRIM(TrimSigDigits(OutsideDryBulbTemp,3)))
            CALL ShowContinueError('... Heat Recovery Minimum Outdoor Dry-Bulb Temperature = '// &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MinOATHeatRecovery,3)))
            CALL ShowContinueError('... Heat Recovery Maximum Outdoor Dry-Bulb Temperature = '//  &
                                   TRIM(TrimSigDigits(VRF(VRFCond)%MaxOATHeatRecovery,3)))
            CALL ShowContinueErrorTimeStamp('... Check VRF Heat Pump Min/Max Outdoor Temperature in Heat Recovery Mode limits.')
            CALL ShowContinueError('...the system will operate in heat pump mode when applicable.')
          END IF
          CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//  &
                 TRIM(VRF(VRFCond)%Name)//'" -- Exceeded VRF Heat Recovery min/max outdoor temperature limit error continues...', &
                 VRF(VRFCond)%HRMaxTempLimitIndex,OutsideDryBulbTemp,OutsideDryBulbTemp)
      END IF
      ! Allow heat pump mode to operate if within limits
      IF(OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATCooling .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATCooling)THEN
        ! Disable cooling mode only, heating model will still be allowed
        TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
      END IF
      IF(OutsideDryBulbTemp .LT. VRF(VRFCond)%MinOATHeating .OR. OutsideDryBulbTemp .GT. VRF(VRFCond)%MaxOATHeating)THEN
        ! Disable heating mode only, cooling model will still be allowed
        TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
      END IF
    END IF
  ELSE
    TerminalUnitList(TUListIndex)%HRHeatRequest = .FALSE.
    TerminalUnitList(TUListIndex)%HRCoolRequest = .FALSE.
  END IF

  ! Override operating mode when using EMS
  ! this logic seems suspect, uses a "just run it on" mentality. Nee to test using EMS.
  IF (VRF(VRFCond)%EMSOverrideHPOperatingMode) THEN
    IF(VRF(VRFCond)%EMSValueForHPOperatingMode == 0.d0)THEN  ! Off
      HeatingLoad(VRFCond) = .FALSE.
      CoolingLoad(VRFCond) = .FALSE.
      TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
      TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
    ELSE IF(VRF(VRFCond)%EMSValueForHPOperatingMode == 1.d0)THEN ! Cooling
      HeatingLoad(VRFCond) = .FALSE.
      CoolingLoad(VRFCond) = .TRUE.
      QZnReq = LoadToCoolingSP
      IF(VRF(VRFCond)%HeatRecoveryUsed)THEN
        TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .FALSE.
        TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .TRUE.
      END IF
    ELSE IF(VRF(VRFCond)%EMSValueForHPOperatingMode == 2.d0)THEN ! Heating
      HeatingLoad(VRFCond) = .TRUE.
      CoolingLoad(VRFCond) = .FALSE.
      QZnReq = LoadToHeatingSP
      IF(VRF(VRFCond)%HeatRecoveryUsed)THEN
        TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList) = .TRUE.
        TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList) = .FALSE.
      END IF
    ELSE
      IF(VRF(VRFCond)%HPOperatingModeErrorIndex == 0)THEN
        CALL ShowWarningMessage(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//TRIM(VRF(VRFCond)%Name)//'".')
        CALL ShowContinueError('...InitVRF: Illegal HP operating mode = '// &
                               TRIM(TrimSigDigits(VRF(VRFCond)%EMSValueForHPOperatingMode,0)))
        CALL ShowContinueError('...InitVRF: VRF HP operating mode will not be controlled by EMS.')

      END IF
      CALL ShowRecurringWarningErrorAtEnd(TRIM(cVRFTypes(VRF(VRFCond)%VRFSystemTypeNum))//' "'//  &
           TRIM(VRF(VRFCond)%Name)//'" -- Illegal HP operating mode error continues...',  &
           VRF(VRFCond)%HPOperatingModeErrorIndex,VRF(VRFCond)%EMSValueForHPOperatingMode, &
            VRF(VRFCond)%EMSValueForHPOperatingMode)
    END IF
  ENDIF

  ! set the TU flow rate. Check for heat recovery operation first, these will be FALSE if HR is not used.
  IF(TerminalUnitList(TUListIndex)%HRCoolRequest(IndexToTUInTUList))THEN
    CompOnMassFlow = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
    CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
    OACompOnMassFlow = VRFTU(VRFTUNum)%CoolOutAirMassFlow
    OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
  ELSE IF(TerminalUnitList(TUListIndex)%HRHeatRequest(IndexToTUInTUList))THEN
    CompOnMassFlow = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
    CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
    OACompOnMassFlow = VRFTU(VRFTUNum)%HeatOutAirMassFlow
    OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
  ELSE IF(CoolingLoad(VRFCond) .and. QZnReq /= 0.d0)THEN
    CompOnMassFlow = VRFTU(VRFTUNum)%MaxCoolAirMassFlow
    CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
    OACompOnMassFlow = VRFTU(VRFTUNum)%CoolOutAirMassFlow
    OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
  ELSE IF(HeatingLoad(VRFCond) .and. QZnReq /= 0.d0)THEN
    CompOnMassFlow = VRFTU(VRFTUNum)%MaxHeatAirMassFlow
    CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
    OACompOnMassFlow = VRFTU(VRFTUNum)%HeatOutAirMassFlow
    OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
  ELSE
    IF(LastModeCooling(VRFCond))THEN
      CompOnMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
      CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoCoolAirMassFlow
      OACompOnMassFlow = VRFTU(VRFTUNum)%CoolOutAirMassFlow
    END IF
    IF(LastModeHeating(VRFCond))THEN
      CompOnMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
      CompOffMassFlow = VRFTU(VRFTUNum)%MaxNoHeatAirMassFlow
      OACompOnMassFlow = VRFTU(VRFTUNum)%HeatOutAirMassFlow
    END IF
    OACompOffMassFlow = VRFTU(VRFTUNum)%NoCoolHeatOutAirVolFlow
  END IF

  IF(VRFTU(VRFTUNum)%OpMode .EQ. CycFanCycCoil)THEN
    CompOffMassFlow = 0.d0
    OACompOffMassFlow = 0.d0
  END IF

  CALL SetAverageAirFlow(VRFTUNum, 0.d0, OnOffAirFlowRatio)

  RETURN

END SUBROUTINE InitVRF


AbortEnergyPlus AbsoluteAirMass ActivateDemandManagers ActivateEMSControls AddBlankKeys addChargesToOperand AddCompSizeTableEntry AddEndUseSubcategory AddError addFootNoteSubTable AddInstruction AddMeter addMonthlyCharge AddMonthlyFieldSetInput AddMonthlyReport AddNeighborInformation AddObjectDefandParse addOperand AddRecordFromSection AddRecordToOutputVariableStructure AddSectionDef AddShadowRelateTableEntry AddSQLiteComponentSizingRecord AddSQLiteComponentSizingRecord AddSQLiteSystemSizingRecord AddSQLiteSystemSizingRecord AddSQLiteZoneSizingRecord AddSQLiteZoneSizingRecord AddTOCEntry AddTOCZoneLoadComponentTable AddToOutputVariableList AddVariablesForMonthlyReport AddVariableSlatBlind AddWindow AdjustAirSetpointsforOpTempCntrl AdjustCBF AdjustCBF AdjustChangeInLoadByEMSControls AdjustChangeInLoadByHowServed AdjustChangeInLoadForLastStageUpperRangeLimit AdjustCoolingSetPointforTempAndHumidityControl adjusthhat AdjustPumpFlowRequestByEMSControls AdjustReportingHourAndMinutes AdjustVBGap AdvanceRootFinder AFECFR AFECOI AFECPD AFECPF AFEDMP AFEDOP AFEDWC AFEELR AFEEXF AFEFAN AFEHEX AFEHOP AFEPLR AFESCR AFESEL AFESOP AFETMU AirflowNetworkVentingControl AirMass AIRMOV AllocateAirflowNetworkData AllocateAirHeatBalArrays AllocateAndInitData AllocateAndSetUpVentReports AllocateCFSStateHourlyData AllocateForCFSRefPointsGeometry AllocateForCFSRefPointsState AllocateHeatBalArrays AllocateLoadComponentArrays AllocateModuleArrays AllocateModuleArrays AllocateSurfaceHeatBalArrays AllocateWeatherData angle_2dvector AnisoSkyViewFactors AnyPlantLoopSidesNeedSim AnyPlantSplitterMixerLacksContinuity AreaPolygon ArgCheck array_to_vector ASHRAETauModel ASHWAT_OffNormalProperties ASHWAT_Solar ASHWAT_Thermal ASSIGNMENT (=) AssignNodeNumber AssignReportNumber AssignResourceTypeNum AssignReverseConstructionNumber AssignVariablePt AttachCustomMeters AttachMeters AuditBranches AUTOTDMA BaseThermalPropertySet_Diffusivity BeginEnvrnInitializeRuntimeLanguage BetweenDates BetweenGlassForcedFlow BetweenGlassShadeForcedFlow BetweenGlassShadeNaturalFlow BisectionMethod BlindBeamBeamTrans BlindOpticsBeam BlindOpticsDiffuse BoreholeResistance BoundValueToNodeMinMaxAvail BoundValueToWithinTwoValues BracketRoot BranchPressureDrop BrentMethod BuildGap BuildKeyVarList Calc4PipeFanCoil Calc_EN673 Calc_ISO15099 CalcActiveTranspiredCollector CalcAggregateLoad CalcAirflowNetworkAirBalance CalcAirflowNetworkCO2Balance CalcAirflowNetworkGCBalance CalcAirflowNetworkHeatBalance CalcAirflowNetworkMoisBalance CalcAirFlowSimple CalcAirLoopSplitter CalcAirMixer CalcAirToAirGenericHeatExch CalcAirToAirPlateHeatExch CalcAirZoneReturnPlenum CalcAirZoneSupplyPlenum CalcAlamdariHammondStableHorizontal CalcAlamdariHammondUnstableHorizontal CalcAlamdariHammondVerticalWall CalcAngleFactorMRT CalcApproximateViewFactors CalcASHRAEDetailedIntConvCoeff CalcASHRAESimpExtConvectCoeff CalcASHRAESimpleIntConvCoeff CalcASHRAEVerticalWall CalcATMixer CalcAwbiHattonHeatedFloor CalcAwbiHattonHeatedWall CalcBasinHeaterPower CalcBasinHeaterPowerForMultiModeDXCoil CalcBeamSolarOnWinRevealSurface CalcBeamSolDiffuseReflFactors CalcBeamSolSpecularReflFactors CalcBeausoleilMorrisonMixedAssistedWall CalcBeausoleilMorrisonMixedOpposingWall CalcBeausoleilMorrisonMixedStableCeiling CalcBeausoleilMorrisonMixedStableFloor CalcBeausoleilMorrisonMixedUnstableCeiling CalcBeausoleilMorrisonMixedUnstableFloor CalcBLASTAbsorberModel CalcBlockenWindward CalcBoilerModel CalcBoilerModel CalcBottomFluxCoefficents CalcBottomSurfTemp CalcBuriedPipeSoil CalcCBF CalcCBF CalcCBVAV CalcCeilingDiffuserInletCorr CalcCeilingDiffuserIntConvCoeff CalcChillerHeaterModel CalcChillerIPLV CalcChillerModel CalcClearRoof CalcCoilUAbyEffectNTU CalcColdestSetPoint CalcComplexWindowOverlap CalcComplexWindowThermal CalcCompSuctionTempResidual CalcCondEntSetPoint CalcConnectionsDrainTemp CalcConnectionsFlowRates CalcConnectionsHeatRecovery CalcConstCOPChillerModel CalcConvCoeffAbsPlateAndWater CalcConvCoeffBetweenPlates CalcCoolBeam CalcCoolTower CalcCoordinateTransformation CalcCoPlanarNess CalcCostEstimate CalcCTGeneratorModel CalcDayltgCoefficients CalcDayltgCoeffsMapPoints CalcDayltgCoeffsRefMapPoints CalcDayltgCoeffsRefPoints CalcDesiccantBalancedHeatExch CalcDesignSpecificationOutdoorAir CalcDesuperheaterHeatingCoil CalcDesuperheaterWaterHeater CalcDetailedHcInForDVModel CalcDetailedSystem CalcDetailedTransSystem CalcDetailFlatFinCoolingCoil CalcDetIceStorLMTDstar CalcDiffTSysAvailMgr CalcDirectAir CalcDirectEvapCooler CalcDirectResearchSpecialEvapCooler CalcDoe2DXCoil CalcDOE2Leeward CalcDOE2Windward CalcDryFinEffCoef CalcDryIndirectEvapCooler CalcDuct CalcDXCoilStandardRating CalcDXHeatingCoil CalcEarthTube CalcEcoRoof CalcEffectiveness CalcEffectiveSHR CalcEffectiveSHR CalcEffectiveSHR CalcEffectiveSHR CalcElecSteamHumidifier CalcElectricBaseboard CalcElectricChillerHeatRecovery CalcElectricChillerModel CalcElectricEIRChillerModel CalcElectricHeatingCoil CalcEmmelRoof CalcEmmelVertical CalcEngineChillerHeatRec CalcEngineDrivenChillerModel CalcEQLOpticalProperty CalcEQLWindowOpticalProperty CalcEQLWindowSHGCAndTransNormal CalcEQLWindowStandardRatings CalcEQLWindowUvalue CalcEquipmentDrainTemp CalcEquipmentFlowRates CalcExhaustAbsorberChillerModel CalcExhaustAbsorberHeaterModel CalcExteriorVentedCavity CalcFisherPedersenCeilDiffuserCeiling CalcFisherPedersenCeilDiffuserFloor CalcFisherPedersenCeilDiffuserWalls CalcFluidHeatExchanger CalcFohannoPolidoriVerticalWall CalcFollowOATempSetPoint CalcFollowSysNodeTempSetPoint CalcFourPipeIndUnit CalcFrameDividerShadow CalcFuelCellAuxHeater CalcFuelCellGeneratorModel CalcFuelCellGenHeatRecovery CalcFurnaceOutput CalcFurnaceResidual CalcGasAbsorberChillerModel CalcGasAbsorberHeaterModel CalcGasCooler CalcGasHeatingCoil CalcGenericDesiccantDehumidifier CalcGoldsteinNovoselacCeilingDiffuserFloor CalcGoldsteinNovoselacCeilingDiffuserWall CalcGoldsteinNovoselacCeilingDiffuserWindow CalcGroundTempSetPoint CalcGroundwaterWell CalcGshpModel CalcGshpModel CalcGTChillerModel CalcHeatBalanceAir CalcHeatBalanceInsideSurf CalcHeatBalanceInsideSurf CalcHeatBalanceOutsideSurf CalcHeatBalanceOutsideSurf CalcHeatBalFiniteDiff CalcHeatBalHAMT CalcHeatPumpWaterHeater CalcHeatTransCoeffAndCoverTemp CalcHfExteriorSparrow CalcHighTempRadiantSystem CalcHighTempRadiantSystemSP CalcHiTurnOffSysAvailMgr CalcHiTurnOnSysAvailMgr CalcHnASHRAETARPExterior CalcHPCoolingSimple CalcHPHeatingSimple CalcHPWHDXCoil CalcHWBaseboard CalcHXAssistedCoolingCoil CalcHXEffectTerm CalcHybridVentSysAvailMgr CalcIBesselFunc CalcICEngineGeneratorModel CalcICEngineGenHeatRecovery CalcIceStorageCapacity CalcIceStorageCharge CalcIceStorageDischarge CalcIceStorageDormant CalcICSSolarCollector CalcIdealCondEntSetPoint CalcIfSetpointMet CalcIndirectAbsorberModel CalcIndirectResearchSpecialEvapCooler CalcInteriorRadExchange CalcInteriorSolarDistribution CalcInteriorSolarOverlaps CalcInteriorWinTransDifSolInitialDistribution CalcISO15099WindowIntConvCoeff CalcKaradagChilledCeiling CalcKBesselFunc CalcKhalifaEq3WallAwayFromHeat CalcKhalifaEq4CeilingAwayFromHeat CalcKhalifaEq5WallsNearHeat CalcKhalifaEq6NonHeatedWalls CalcKhalifaEq7Ceiling CalcLoadCenterThermalLoad CalcLoTurnOffSysAvailMgr CalcLoTurnOnSysAvailMgr CalcLowTempCFloRadiantSystem CalcLowTempCFloRadSysComps CalcLowTempElecRadiantSystem CalcLowTempHydrRadiantSystem CalcLowTempHydrRadSysComps CalcMatrixInverse CalcMcAdams CalcMerkelVariableSpeedTower CalcMicroCHPNoNormalizeGeneratorModel CalcMinIntWinSolidAngs CalcMitchell CalcMixedAirSetPoint CalcMoistureBalanceEMPD CalcMoreNodeInfo CalcMoWITTLeeward CalcMoWITTWindward CalcMSHeatPump CalcMTGeneratorModel CalcMultiSpeedDXCoil CalcMultiSpeedDXCoilCooling CalcMultiSpeedDXCoilHeating CalcMultiStageElectricHeatingCoil CalcMultiStageGasHeatingCoil CalcMultiZoneAverageCoolingSetPoint CalcMultiZoneAverageHeatingSetPoint CalcMultiZoneAverageMaxHumSetPoint CalcMultiZoneAverageMinHumSetPoint CalcMultiZoneMaxHumSetPoint CalcMultiZoneMinHumSetPoint CalcMundtModel CalcNCycSysAvailMgr CalcNewZoneHeatCoolFlowRates CalcNewZoneHeatOnlyFlowRates CalcNodeMassFlows CalcNominalWindowCond CalcNonDXHeatingCoils CalcNonDXHeatingCoils CalcNonDXHeatingCoils CalcNonDXHeatingCoils CalcNusselt CalcNusseltJurges CalcNVentSysAvailMgr CalcOAController CalcOAMassFlow CalcOAMassFlow CalcOAMixer CalcOAOnlyMassFlow CalcOAPretreatSetPoint CalcOAUnitCoilComps CalcObstrMultiplier CalcOptStartSysAvailMgr CalcOtherSideDemand CalcOutdoorAirUnit CalcOutsideAirSetPoint CalcOutsideSurfTemp CalcParallelPIU CalcPassiveExteriorBaffleGap CalcPassiveSystem CalcPassiveTranspiredCollector CalcPerSolarBeam CalcPipeHeatTransCoef CalcPipesHeatTransfer CalcPipeTransBeam CalcPlantValves CalcPollution CalcPolyhedronVolume CalcPolynomCoef CalcPondGroundHeatExchanger CalcPredictedHumidityRatio CalcPredictedSystemLoad CalcPTUnit CalcPumps CalcPurchAirLoads CalcPurchAirMinOAMassFlow CalcPurchAirMixedAir CalcPVTcollectors CalcQiceChargeMaxByChiller CalcQiceChargeMaxByITS CalcQiceDischageMax CalcRABFlowSetPoint CalcRackSystem CalcRadSysHXEffectTerm CalcRadTemp CalcRainCollector CalcReformEIRChillerModel CalcResearchSpecialPartLoad CalcReturnAirPath CalcRfFlrCoordinateTransformation CalcSandiaPV CalcSatVapPressFromTemp CalcSchedOffSysAvailMgr CalcSchedOnSysAvailMgr CalcSchedSysAvailMgr CalcScheduledDualSetPoint CalcScheduledSetPoint CalcScreenTransmittance CalcScriptF CalcSeriesPIU CalcSetpointTempTarget CalcSHRUserDefinedCurves CalcSimpleController CalcSimpleHeatingCoil CalcSimplePV CalcSingleSpeedEvapFluidCooler CalcSingleSpeedTower CalcSingZoneClSetPoint CalcSingZoneHtSetPoint CalcSingZoneMaxHumSetPoint CalcSingZoneMinHumSetPoint CalcSingZoneRhSetPoint CalcSkySolDiffuseReflFactors CalcSolarCollector CalcSolarFlux CalcSolidDesiccantDehumidifier CalcSourceFlux CalcSourceTempCoefficents CalcSparrowLeeward CalcSparrowWindward CalcSpecialDayTypes CalcStandAloneERV CalcStandardRatings CalcStaticProperties CalcSteamAirCoil CalcSteamBaseboard CalcSurfaceCentroid CalcSurfaceGroundHeatExchanger CalcSystemEnergyUse CalcSZOneStageCoolingSetPt CalcSZOneStageHeatingSetPt CalcTankTemp CalcTDDTransSolAniso CalcTDDTransSolHorizon CalcTDDTransSolIso CalcTempDistModel CalcTempIntegral CalcTESCoilChargeOnlyMode CalcTESCoilCoolingAndChargeMode CalcTESCoilCoolingAndDischargeMode CalcTESCoilCoolingOnlyMode CalcTESCoilDischargeOnlyMode CalcTESCoilOffMode CalcTESIceStorageTank CalcTESWaterStorageTank CalcThermalChimney CalcThermalComfortAdaptiveASH55 CalcThermalComfortAdaptiveCEN15251 CalcThermalComfortFanger CalcThermalComfortKSU CalcThermalComfortPierce CalcThermalComfortSimpleASH55 CalcTimeNeeded CalcTopFluxCoefficents CalcTopSurfTemp CalcTotalFLux CalcTotCapSHR CalcTotCapSHR_VSWSHP CalcTransAbsorProduct CalcTransRefAbsOfCover CalcTRNSYSPV CalcTrombeWallIntConvCoeff CalcTwoSpeedDXCoilIEERResidual CalcTwoSpeedDXCoilStandardRating CalcTwoSpeedEvapFluidCooler CalcTwoSpeedTower CalcUAIce CalcUCSDCV CalcUCSDDV CalcUCSDUE CalcUCSDUI CalculateAirChillerSets CalculateBasisLength CalculateCase CalculateCoil CalculateCompressors CalculateCondensers CalculateCTFs CalculateDailySolarCoeffs CalculateDayOfWeek CalculateEpsFromNTUandZ CalculateExponentialMatrix CalculateFuncResults CalculateGammas CalculateInverseMatrix CalculateMoodyFrictionFactor CalculateNTUfromEpsAndZ CalculatePollution CalculateSecondary CalculateSubcoolers CalculateSunDirectionCosines CalculateTransCompressors CalculateWalkIn CalculateWaterUseage CalculateWaterUseage CalculateWindowBeamProperties CalculateZoneMRT CalculateZoneVolume CalcUnitaryCoolingSystem CalcUnitaryHeatingSystem CalcUnitarySuppHeatingSystem CalcUnitarySuppSystemtoSP CalcUnitarySystemLoadResidual CalcUnitarySystemToLoad CalcUnitHeater CalcUnitHeaterComponents CalcUnitVentilator CalcUnitVentilatorComponents CalcUnmetPlantDemand CalcUpdateHeatRecovery CalcUpdateHeatRecovery CalcUserDefinedInsideHcModel CalcUserDefinedOutsideHcModel CalcVariableSpeedTower CalcVarSpeedCoilCooling CalcVarSpeedCoilHeating CalcVarSpeedHeatPump CalcVarSpeedHeatPump CalcVAVVS CalcVentilatedSlab CalcVentilatedSlabComps CalcVentilatedSlabRadComps CalcVentSlabHXEffectTerm CalcVerticalGroundHeatExchanger CalcViewFactorToShelf CalcVRF CalcVRFCondenser CalcVRFCoolingCoil CalcVSTowerApproach CalcWallCoordinateTransformation CalcWaltonStableHorizontalOrTilt CalcWaltonUnstableHorizontalOrTilt CalcWarmestSetPoint CalcWarmestSetPointTempFlow CalcWaterMainsTemp CalcWaterSource CalcWaterStorageTank CalcWaterThermalTankMixed CalcWaterThermalTankStratified CalcWaterThermalTankZoneGains CalcWaterToAirHeatpump CalcWatertoAirHPCooling CalcWatertoAirHPHeating CalcWaterToAirResidual CalcWatertoWaterHPCooling CalcWatertoWaterHPHeating CalcWaterUseZoneGains CalcWetIndirectEvapCooler CalcWindowACOutput CalcWindowBlindProperties CalcWindowHeatBalance CalcWindowProfileAngles CalcWindowScreenProperties CalcWindowStaticProperties CalcWindPressure CalcWindPressureCoeffs CalcWindTurbine CalcWinFrameAndDividerTemps CalcWinTransDifSolInitialDistribution CalcWrapperModel CalcZoneAirComfortSetpoints CalcZoneAirTempSetpoints CalcZoneComponentLoadSums CalcZoneDehumidifier CalcZoneEvaporativeCoolerUnit CalcZoneLeavingConditions CalcZoneMassBalance CalcZonePipesHeatGain CalcZoneSums CartesianPipeCellInformation_ctor CellType_IsFieldCell CFSHasControlledShade CFSNGlz CFSRefPointPosFactor CFSRefPointSolidAngle CFSShadeAndBeamInitialization CFSUFactor cGetCoilAirOutletNode cGetCoilSteamInletNode cGetCoilSteamOutletNode CharPreDefTableEntry CheckActuatorNode CheckAndAddAirNodeNumber CheckAndFixCFSLayer CheckAndReadCustomSprectrumData CheckAndReadFaults CheckAndSetConstructionProperties CheckBracketRoundOff CheckBranchForOASys CheckCachedIPErrors CheckCFSStates CheckCoilWaterInletNode CheckControllerListOrder CheckControllerLists CheckConvexity CheckCostEstimateInput CheckCreatedZoneItemName CheckCurveLimitsForIPLV CheckCurveLimitsForStandardRatings CheckDayScheduleValueMinMax CheckDXCoolingCoilInOASysExists CheckFDSurfaceTempLimits CheckFFSchedule CheckFluidPropertyName CheckForActualFileName CheckForBalancedFlow CheckForControllerWaterCoil CheckForGeometricTransform CheckForGeometricTransform CheckForMisMatchedEnvironmentSpecifications CheckForOutOfRangeTempResult CheckForOutOfRangeTemps CheckForRequestedReporting CheckForRunawayPlantTemps CheckForSensorAndSetpointNode CheckGasCoefs CheckHeatingCoilSchedule CheckHXAssistedCoolingCoilSchedule CheckIFAnyEMS CheckIFAnyIdealCondEntSetPoint CheckIfAnyPlant CheckIfNodeSetpointManagedByEMS CheckIncrementRoundOff CheckInternalConsistency CheckLightsReplaceableMinMaxForZone CheckLocationValidity CheckLoopExitNode CheckLowerUpperBracket CheckMarkedNodes CheckMaxActiveController CheckMaxConstraint CheckMicroCHPThermalBalance CheckMinActiveController CheckMinConstraint checkMinimumMonthlyCharge CheckMinMaxCurveBoundaries CheckMinMaxRange CheckModelBoundOutput_HumRat CheckModelBoundOutput_Temp CheckModelBounds CheckModelBoundsHumRatEq CheckModelBoundsRH_HumRatEq CheckModelBoundsRH_TempEq CheckModelBoundsTempEq CheckNodeConnections CheckNodeSetPoint CheckNonSingularity CheckOAControllerName CheckOutAirNodeNumber CheckPlantConvergence CheckPlantMixerSplitterConsistency CheckPlantOnAbort CheckPollutionMeterReporting CheckRefrigerationInput CheckReportVariable CheckRootFinderCandidate CheckRootFinderConvergence CheckScheduledSurfaceGains CheckScheduleValue CheckScheduleValueMinMax Checksetpoints CheckSimpleController CheckSlope CheckSteamCoilSchedule CheckSubSurfaceMiscellaneous CheckSysSizing CheckSystemBranchFlow CheckTDDsAndLightShelvesInDaylitZones CheckThisAirSystemForSizing CheckThisZoneForSizing CheckThreading CheckUniqueNodes CheckUnitarySysCoilInOASysExists CheckUsedConstructions CheckValidSimulationObjects CheckWarmupConvergence CheckWaterCoilSchedule CheckWeatherFileValidity CheckWindowShadingControlFrameDivider CheckZoneEquipmentList CheckZoneSizing CHKBKS CHKGSS CHKSBS CLIP CLIPPOLY CloseDFSFile CloseMiscOpenFiles CloseMoistureBalanceEMPD CloseOutOpenFiles CloseOutputFiles CloseOutputTabularFile CloseReportIllumMaps CloseSocket CloseWeatherFile CoilAreaFracIter CoilCompletelyDry CoilCompletelyWet CoilOutletStreamCondition CoilPartWetPartDry COMMAND_ARGUMENT_COUNT CompactObjectsCheck CompareTwoVectors ComplexFenestrationLuminances ComputeDelayedComponents ComputeDifSolExcZonesWIZWindows ComputeIntSolarAbsorpFactors ComputeIntSWAbsorpFactors ComputeIntThermalAbsorpFactors ComputeLifeCycleCostAndReport ComputeLoadComponentDecayCurve ComputeNominalUwithConvCoeffs ComputePresentValue ComputeTariff ComputeTaxAndDepreciation ComputeWinShadeAbsorpFactors CondOutTempResidual ConstructBasis ControlCBVAVOutput ControlCompOutput ControlCompOutput ControlCoolBeam ControlCoolingSystem ControlCycWindACOutput ControlDesiccantDehumidifier ControlDXHeatingSystem ControlDXSystem ControlFluidHeatExchanger ControlHeatingSystem ControlHumidifier ControlMSHPOutput ControlPTUnitOutput ControlPVTcollector ControlReformEIRChillerModel ControlSuppHeatSystem ControlUnitarySystemOutput ControlUnitarySystemtoLoad ControlUnitarySystemtoSP ControlVRF ControlVSEvapUnitToMeetLoad ControlVSHPOutput ControlVSHPOutput ConvectionFactor ConvertCasetoLower ConvertCasetoUpper ConvertIP ConvertIPdelta ConvertToElementTag ConvertToEscaped CoolBeamResidual CoolingCoil CoolWaterHumRatResidual CoolWaterTempResidual CoolWatertoAirHPHumRatResidual CoolWatertoAirHPTempResidual CorrectZoneAirTemp CorrectZoneContaminants CorrectZoneHumRat CostInfoOut CPCW CPHW CreateBoundaryList CreateBoundaryListCount CreateCategoryNativeVariables CreateCellArray CreateCurrentDateTimeString CreateDefaultComputation CreateEnergyReportStructure CreateFCfactorConstructions CreateHVACStepFullString CreateHVACTimeIntervalString CreateHVACTimeString CreateNewellAreaVector CreateNewellSurfaceNormalVector CreatePartitionCenterList CreatePartitionRegionList CreatePredefinedMonthlyReports CreateRegionList CreateRegionListCount CreateShadedWindowConstruction CreateSQLiteConstructionsTable CreateSQLiteConstructionsTable CreateSQLiteDatabase CreateSQLiteDatabase CreateSQLiteDaylightMap CreateSQLiteDaylightMap CreateSQLiteDaylightMapTitle CreateSQLiteDaylightMapTitle CreateSQLiteEnvironmentPeriodRecord CreateSQLiteEnvironmentPeriodRecord CreateSQLiteErrorRecord CreateSQLiteErrorRecord CreateSQLiteInfiltrationTable CreateSQLiteInfiltrationTable CreateSQLiteMaterialsTable CreateSQLiteMaterialsTable CreateSQLiteMeterDictionaryRecord CreateSQLiteMeterDictionaryRecord CreateSQLiteMeterRecord CreateSQLiteMeterRecord CreateSQLiteNominalBaseboardHeatTable CreateSQLiteNominalBaseboardHeatTable CreateSQLiteNominalElectricEquipmentTable CreateSQLiteNominalElectricEquipmentTable CreateSQLiteNominalGasEquipmentTable CreateSQLiteNominalGasEquipmentTable CreateSQLiteNominalHotWaterEquipmentTable CreateSQLiteNominalHotWaterEquipmentTable CreateSQLiteNominalLightingTable CreateSQLiteNominalLightingTable CreateSQLiteNominalOtherEquipmentTable CreateSQLiteNominalOtherEquipmentTable CreateSQLiteNominalPeopleTable CreateSQLiteNominalPeopleTable CreateSQLiteNominalSteamEquipmentTable CreateSQLiteNominalSteamEquipmentTable CreateSQLiteReportVariableDataRecord CreateSQLiteReportVariableDataRecord CreateSQLiteReportVariableDictionaryRecord CreateSQLiteReportVariableDictionaryRecord CreateSQLiteRoomAirModelTable CreateSQLiteRoomAirModelTable CreateSQLiteSchedulesTable CreateSQLiteSimulationsRecord CreateSQLiteSimulationsRecord CreateSQLiteStringTableRecord CreateSQLiteSurfacesTable CreateSQLiteSurfacesTable CreateSQLiteTabularDataRecords CreateSQLiteTabularDataRecords CreateSQLiteTimeIndexRecord CreateSQLiteTimeIndexRecord CreateSQLiteVentilationTable CreateSQLiteVentilationTable CreateSQLiteZoneGroupTable CreateSQLiteZoneGroupTable CreateSQLiteZoneListTable CreateSQLiteZoneListTable CreateSQLiteZoneTable CreateSQLiteZoneTable CreateStormWindowConstructions CreateSysTimeIntervalString CreateTCConstructions CreateTimeIntervalString CreateTimeString CreatExtBooundCondName CreateZoneExtendedOutput CreateZoneExtendedOutput CrossProduct CrossProduct cSurfaceClass CTRANS CurveValue DateToString DateToStringWithMonth DaylghtAltAndAzimuth DayltgAveInteriorReflectance DayltgClosestObstruction DayltgCrossProduct DayltgCurrentExtHorizIllum DayltgDirectIllumComplexFenestration DayltgDirectSunDiskComplexFenestration DayltgElecLightingControl DayltgExtHorizIllum DayltgGlare DayltgGlarePositionFactor DayltgGlareWithIntWins DayltgHitBetWinObstruction DayltgHitInteriorObstruction DayltgHitObstruction DayltgInteriorIllum DayltgInteriorMapIllum DayltgInteriorTDDIllum DayltgInterReflectedIllum DayltgInterReflectedIllumComplexFenestration DayltgInterReflIllFrIntWins DayltgLuminousEfficacy DayltgPierceSurface DayltgSetupAdjZoneListsAndPointers DayltgSkyLuminance DayltgSurfaceLumFromSun dCheckScheduleValueMinMax1 dCheckScheduleValueMinMax2 DeallocateLoadComponentArrays DebugRootFinder DecodeHHMMField DecodeMonDayHrMin DeflectionTemperatures DeflectionWidths DegradF DElightDaylightCoefficients DElightDaylightCoefficients DElightElecLtgCtrl DElightElecLtgCtrl DElightFreeMemory DElightFreeMemory DElightInputGenerator DElightInputGenerator DElightOutputGenerator DElightOutputGenerator DensityCFSFillGas Depth DERIV DetailsForSurfaces DetectOscillatingZoneTemp DetermineAzimuthAndTilt DetermineBranchFlowRequest DetermineBuildingFloorArea DetermineDateTokens DetermineFrequency DetermineIndexGroupFromMeterGroup DetermineIndexGroupKeyFromMeterName DetermineMaxBackSurfaces DetermineMeterIPUnits DetermineMinuteForReporting DeterminePolygonOverlap DetermineShadowingCombinations DetermineSunUpDown DevelopMesh DiffuseAverage DiffuseAverageProfAngGnd DiffuseAverageProfAngSky DisplayMaterialRoughness DisplayNumberandString DisplaySimDaysProgress DisplayString distance DistributeBBElecRadGains DistributeBBRadGains DistributeBBSteamRadGains DistributeHTRadGains DistributePlantLoad DistributePressureOnBranch DistributeTDDAbsorbedSolar DistributeUserDefinedPlantLoad DL_RES_r2 DLAG DOE2DXCoilHumRatResidual DOE2DXCoilHumRatResidual DOE2DXCoilResidual DOE2DXCoilResidual DOE2DXCoilResidual DoEndOfIterationOperations DomainRectangle_Contains DOMakeUPPERCase DoOneTimeInitializations DOSameString DoShadeControl DoStartOfTimeStepInitializations DownInterpolate4HistoryValues DumpAirLoopStatistics DumpCurrentLineBuffer DUMPVD DUMPVR DXCoilCyclingHumRatResidual DXCoilCyclingHumRatResidual DXCoilCyclingResidual DXCoilCyclingResidual DXCoilVarSpeedHumRatResidual DXCoilVarSpeedHumRatResidual DXCoilVarSpeedResidual DXCoilVarSpeedResidual DXFOut DXFOutLines DXFOutWireFrame DXHeatingCoilResidual DXHeatingCoilResidual DXHeatingCoilResidual DynamicClothingModel DynamicExtConvSurfaceClassification DynamicIntConvSurfaceClassification EchoOutActuatorKeyChoices EchoOutInternalVariableChoices EffectiveEPSLB EffectiveEPSLF EIRChillerHeatRecovery EN673ISO10292 EncodeMonDayHrMin EndEnergyPlus EndUniqueNodeCheck EnthalpyResidual epElapsedTime epGetTimeUsed epGetTimeUsedperCall epStartTime epStopTime epSummaryTimes eptime EQLWindowInsideEffectiveEmiss EQLWindowOutsideEffectiveEmiss EQLWindowSurfaceHeatBalance EquationsSolver ERF EstimateHEXSurfaceArea EvalInsideMovableInsulation EvalOutsideMovableInsulation EvaluateAdiabaticSurfaceTemperature EvaluateBasementCellTemperature EvaluateCellNeighborDirections evaluateChargeBlock evaluateChargeSimple EvaluateExpression EvaluateExtHcModels EvaluateFarfieldBoundaryTemperature EvaluateFarfieldCharacteristics EvaluateFieldCellTemperature EvaluateGroundSurfaceTemperature EvaluateIntHcModels EvaluateLoopSetPointLoad EvaluateNeighborCharacteristics evaluateQualify evaluateRatchet EvaluateSoilRhoCp EvaluateStack EvolveParaUCSDCV ExitCalcController ExpandComplexState ExpressAsCashFlows ExtendObjectDefinition ExteriorBCEqns ExternalInterfaceExchangeVariables ExternalInterfaceInitializeErlVariable ExternalInterfaceSetErlVariable ExternalInterfaceSetSchedule ExtOrIntShadeNaturalFlow Fabric_EstimateDiffuseProps FACSKY FalsePositionMethod FEQX FI FigureACAncillaries FigureAirEnthalpy FigureAirHeatCap FigureAuxilHeatGasHeatCap FigureBeamSolDiffuseReflFactors FigureBeamSolSpecularReflFactors FigureConstGradPattern FigureDayltgCoeffsAtPointsForSunPosition FigureDayltgCoeffsAtPointsForWindowElements FigureDayltgCoeffsAtPointsSetupForWindow FigureElectricalStorageZoneGains FigureFuelCellZoneGains FigureFuelEnthalpy FigureFuelHeatCap FigureGaseousWaterEnthalpy FigureHeightPattern FigureHXleavingGasHeatCap FigureInverterZoneGains FigureLHVofFuel FigureLiquidWaterEnthalpy FigureLiquidWaterHeatCap FigureMapPointDayltgFactorsToAddIllums FigureMicroCHPZoneGains FigureNDheightInZone FigurePowerConditioningLosses FigureProductGasesEnthalpy FigureProductGasHeatCap FigureRefPointDayltgFactorsToAddIllums FigureRefrigerationZoneGains FigureSolarBeamAtTimestep FigureSunCosines FigureSurfMapPattern FigureTDDZoneGains FigureTransformerZoneGains FigureTransientConstraints FigureTwoGradInterpPattern FILJAC FillBasisElement FillDefaultsSWP FillRemainingPredefinedEntries FillWeatherPredefinedEntries film filmg filmi filmPillar FILSKY FinalizeCFS FinalizeCFSLAYER FinalRateCoils FindAirLoopBranchConnection FindAirPlantCondenserLoopFromBranchList FindAllNumbersinList FindArrayIndex FindCompSPInput FindCompSPLoad FindCondenserLoopBranchConnection FindControlledZoneIndexFromSystemNodeNumberForZone FindDeltaTempRangeInput FindDemandSideMatch FindEMSVariable FindFirstLastPtr FindFirstRecord FindGlycol FindHXDemandSideLoopFlow FindInBasis FindItem FindIteminList FindIteminSortedList FindItemInVariableList FindLoopSideInCallingOrder FindNextRecord FindNonSpace FindNumberinList FindOAMixerMatchForOASystem FindPlantLoopBranchConnection FindRangeBasedOrUncontrolledInput FindRangeVariable FindRefrigerant FindRootSimpleController FindStratifiedTankSensedTemp FindTariffIndex FindTDDPipe FindUnitNumber FinishDebugOutputFiles FixViewFactors FluidCellInformation_ctor FM_BEAM FM_DIFF FM_F FNU forcedventilation FourPipeInductionUnitHasMixer FourPipeIUCoolingResidual FourPipeIUHeatingResidual FRA FrostControl FrostControlSetPointLimit FrostControlSetPointLimit FuelCellProductGasEnthResidual FUN FuncDetermineCoolantWaterExitTemp FuncDetermineCWMdotForInternalFlowControl FuncDetermineEngineTemp FV GasElecHeatingCoilResidual GASSES90 GassesLow GatherBEPSResultsForTimestep GatherBinResultsForTimestep GatherComponentLoadsHVAC GatherComponentLoadsIntGain GatherComponentLoadsSurfAbsFact GatherComponentLoadsSurface GatherForEconomics GatherForPredefinedReport GatherHeatGainReport GatherMonthlyResultsForTimestep GatherPeakDemandForTimestep GatherSourceEnergyEndUseResultsForTimestep GaussElimination generate_ears GenerateDElightDaylightCoefficients GenerateDElightDaylightCoefficients GeneratorPowerOutput GenericCrack GenOutputVariablesAuditReport Get2DMatrix Get2DMatrixDimensions GET_COMMAND GET_COMMAND_ARGUMENT Get_Environment_Variable GetActualDXCoilIndex GetAirBranchIndex GetAirFlowFlag GetAirflowNetworkInput GetAirHeatBalanceInput GetAirLoopAvailabilityManager GetAirModelDatas GetAirNodeData GetAirPathData GetAngleFactorList GetATMixer GetATMixerOutNode GetATMixerPriNode GetATMixers GetATMixerSecNode GetAttShdSurfaceData GetAverageTempByType GetBaseboardInput GetBaseboardInput GetBasementFloorHeatFlux GetBasementWallHeatFlux GetBLASTAbsorberInput GetBoilerInput GetBoilerInput GetBranchData GetBranchFanTypeName GetBranchFlow GetBranchInput GetBranchList GetBranchListInput GetBuildingData GetCBVAV GetCellWidths GetCellWidthsCount GetChildrenData GetChillerheaterInput GetCoilAirFlowRate GetCoilAirFlowRateVariableSpeed GetCoilAirInletNode GetCoilAirOutletNode GetCoilAvailScheduleIndex GetCoilCapacity GetCoilCapacity GetCoilCapacity GetCoilCapacity GetCoilCapacity GetCoilCapacity GetCoilCapacityByIndexType GetCoilCapacityVariableSpeed GetCoilCondenserInletNode GetCoilControlNodeNum GetCoilGroupTypeNum GetCoilIndex GetCoilIndex GetCoilIndex GetCoilIndexVariableSpeed GetCoilInletNode GetCoilInletNode GetCoilInletNode GetCoilInletNode GetCoilInletNode GetCoilInletNode GetCoilInletNodeVariableSpeed GetCoilMaxSteamFlowRate GetCoilMaxWaterFlowRate GetCoilMaxWaterFlowRate GetCoilMaxWaterFlowRate GetCoilObjectTypeNum GetCoilOutletNode GetCoilOutletNode GetCoilOutletNode GetCoilOutletNode GetCoilOutletNode GetCoilOutletNode GetCoilOutletNodeVariableSpeed GetCoilSteamInletNode GetCoilSteamOutletNode GetCoilTypeNum GetCoilWaterInletNode GetCoilWaterInletNode GetCoilWaterOutletNode GetColumnUsingTabs GetComfortSetpoints GetComponentData GetCondFDInput GetConductivityGlycol GetConnectorList GetConnectorListInput GetConstCOPChillerInput GetConstructData GetControlledZoneIndex GetControllerActuatorNodeNum GetControllerInput GetCoolBeams GetCoolingCoilTypeNameAndIndex GetCooltower GetCostEstimateInput GetCrossVentData GetCTGeneratorInput GetCTGeneratorResults GetCurrentHVACTime GetCurrentMeterValue GetCurrentScheduleValue GetCurveCheck GetCurveIndex GetCurveInput GetCurveMinMaxValues GetCurveName GetCurveObjectTypeNum GetCurveType GetCustomMeterInput GetDaylightingParametersDetaild GetDaylightingParametersInput GetDayScheduleIndex GetDemandManagerInput GetDemandManagerListInput GetDensityGlycol GetDesiccantDehumidifierInput GetDesignDayData GetDesignLightingLevelForZone GetDetShdSurfaceData GetDirectAirInput GetDisplacementVentData GetDSTData GetDualDuctInput GetDualDuctOutdoorAirRecircUse GetDuctInput GetDXCoilAirFlow GetDXCoilAvailSchPtr GetDXCoilBypassedFlowFrac GetDXCoilCapFTCurveIndex GetDXCoilIndex GetDXCoilNumberOfSpeeds GetDXCoils GetDXCoolingSystemInput GetDXHeatPumpSystemInput GetEarthTube GetElecReformEIRChillerInput GetElectricBaseboardInput GetElectricChillerInput GetElectricEIRChillerInput GetEMSInput GetEngineDrivenChillerInput GetEnvironmentalImpactFactorInfo GetEvapFluidCoolerInput GetEvapInput GetExhaustAbsorberInput GetExhaustAirInletNode GetExteriorEnergyUseInput GetExtVentedCavityIndex GetExtVentedCavityIndex GetExtVentedCavityTsColl GetExtVentedCavityTsColl GetFanAvailSchPtr GetFanCoilIndex GetFanCoilInletAirNode GetFanCoilMixedAirNode GetFanCoilOutAirNode GetFanCoilReturnAirNode GetFanCoilUnits GetFanCoilZoneInletAirNode GetFanDesignVolumeFlowRate GetFanIndex GetFanIndexForTwoSpeedCoil GetFanInletNode GetFanInput GetFanOutletNode GetFanPower GetFanSpeedRatioCurveIndex GetFanType GetFanVolFlow GetFarfieldTemp GetFirstBranchInletNodeName GetFluidCoolerInput GetFluidDensityTemperatureLimits GetFluidHeatExchangerInput GetFluidPropertiesData GetFluidSpecificHeatTemperatureLimits GetFrameAndDividerData GetFuelCellGeneratorInput GetFuelCellGeneratorResults GetFuelFactorInfo GetFurnaceInput GetGasAbsorberInput GetGeneratorFuelSupplyInput GetGeometryParameters GetGlycolNameByIndex GetGroundheatExchangerInput GetGroundReflectances GetGroundTemps GetGshpInput GetGshpInput GetGTChillerInput GetHeatBalanceInput GetHeatBalHAMTInput GetHeatExchangerObjectTypeNum GetHeatingCoilIndex GetHeatingCoilInput GetHeatingCoilNumberOfStages GetHeatingCoilPLFCurveIndex GetHeatingCoilTypeNum GetHeatReclaimSourceIndex GetHeatRecoveryInput GetHighTempRadiantSystem GetHPCoolingCoilIndex GetHTSubSurfaceData GetHTSurfaceData GetHTSurfExtVentedCavityData GetHumidifierInput GetHVACSingleDuctSysIndex GetHWBaseboardInput GetHXAssistedCoolingCoilInput GetHXCoilAirFlowRate GetHXCoilType GetHXCoilTypeAndName GetHXDXCoilIndex GetHXDXCoilName GetHybridVentilationControlStatus GetHybridVentilationInputs GetICEGeneratorResults GetICEngineGeneratorInput GetIceStorageInput GetIDFRecordsStats GetIndirectAbsorberInput GetIndUnits GetInputEconomicsChargeBlock GetInputEconomicsChargeSimple GetInputEconomicsComputation GetInputEconomicsCurrencyType GetInputEconomicsQualify GetInputEconomicsRatchet GetInputEconomicsTariff GetInputEconomicsVariable GetInputForLifeCycleCost GetInputFuelAndPollutionFactors GetInputLifeCycleCostNonrecurringCost GetInputLifeCycleCostParameters GetInputLifeCycleCostRecurringCosts GetInputLifeCycleCostUseAdjustment GetInputLifeCycleCostUsePriceEscalation GetInputTabularMonthly GetInputTabularPredefined GetInputTabularStyle GetInputTabularTimeBins GetInputViewFactors GetInputViewFactorsbyName GetInputZoneEvaporativeCoolerUnit GetInstantMeterValue GetInternalBranchData GetInternalHeatGainsInput GetInternalVariableValue GetInternalVariableValue GetInternalVariableValueExternalInterface GetInternalVariableValueExternalInterface GetInterpolatedSatProp GetInterpValue GetIntMassSurfaceData GetLastBranchOutletNodeName GetLastWord GetLightWellData GetListOfObjectsInIDD GetListofSectionsinInput GetLocationInfo GetLoopMixer GetLoopSidePumpIndex GetLoopSplitter GetLowTempRadiantSystem GetMaterialData GetMatrixInput getMaxAndSum GetMeteredVariables GetMeterIndex GetMeterResourceType GetMicroCHPGeneratorInput GetMicroCHPGeneratorResults GetMinOATCompressor GetMixerInput GetMixerInput GetMoistureBalanceEMPDInput GetMonthlyCostForResource GetMovableInsulationData GetMSHeatPumpInput GetMTGeneratorExhaustNode GetMTGeneratorInput GetMTGeneratorResults GetMundtData GetNewUnitNumber GetNextEnvironment GetNodeConnectionType GetNodeList GetNodeListsInput GetNodeNums GetNTUforCrossFlowBothUnmixed GetNumberOfSchedules GetNumberOfSurfaceLists GetNumberOfSurfListVentSlab GetNumChildren GetNumMeteredVariables GetNumOAControllers GetNumOAMixers GetNumOASystems GetNumObjectsFound GetNumObjectsInIDD GetNumRangeCheckErrorsFound GetNumSectionsFound GetNumSectionsinInput GetNumSegmentsForHorizontalTrenches GetNumSplitterMixerInConntrList GetOACompListNumber GetOACompName GetOACompType GetOACompTypeNum GetOAControllerInputs GetOAMixerIndex GetOAMixerInletNodeNumber GetOAMixerInputs GetOAMixerMixedNodeNumber GetOAMixerNodeNumbers GetOAMixerReliefNodeNumber GetOAMixerReturnNodeNumber GetOARequirements GetOASysControllerListIndex GetOASysNumCoolingCoils GetOASysNumHeatingCoils GetOASysNumSimpControllers GetOASystemNumber GetObjectDefInIDD GetObjectDefMaxArgs GetObjectItem GetObjectItemfromFile GetObjectItemNum GetOnlySingleNode GetOperationSchemeInput GetOSCData GetOSCMData GetOutAirNodesInput GetOutdoorAirUnitInputs GetOutdoorAirUnitOutAirNode GetOutdoorAirUnitReturnAirNode GetOutdoorAirUnitZoneInletNode GetOutsideAirSysInputs GetOutsideEnergySourcesInput GetParentData GetPipeInput GetPipesHeatTransfer GetPipingSystemsInput GetPIUs GetPlantAvailabilityManager GetPlantInput GetPlantLoopData GetPlantOperationInput GetPlantProfileInput GetPlantSizingInput GetPlantValvesInput GetPollutionFactorInput GetPondGroundHeatExchanger GetPowerManagerInput GetPressureCurveTypeAndIndex GetPressureSystemInput GetPreviousHVACTime GetProjectControlData GetProjectData GetPTUnit GetPTUnitMixedAirNode GetPTUnitOutAirNode GetPTUnitReturnAirNode GetPTUnitZoneInletAirNode GetPumpInput GetPurchasedAir GetPurchasedAirMixedAirHumRat GetPurchasedAirMixedAirTemp GetPurchasedAirOutAirMassFlow GetPurchasedAirReturnAirNode GetPurchasedAirZoneInletAirNode GetPVGeneratorResults GetPVInput GetPVTcollectorsInput GetPVTThermalPowerProduction GetQualityRefrig GetRecordLocations GetRectDetShdSurfaceData GetRectSubSurfaces GetRectSurfaces GetRefrigeratedRackIndex GetRefrigerationInput GetReportVariableInput GetRequiredMassFlowRate GetResidCrossFlowBothUnmixed GetResourceTypeChar GetReturnAirNodeForZone GetReturnAirPathInput GetRoomAirModelParameters GetRunPeriodData GetRunPeriodDesignData GetRuntimeLanguageUserInput GetSatDensityRefrig GetSatEnthalpyRefrig GetSatPressureRefrig GetSatSpecificHeatRefrig GetSatTemperatureRefrig GetScheduledSurfaceGains GetScheduleIndex GetScheduleMaxValue GetScheduleMinValue GetScheduleName GetScheduleType GetScheduleValuesForDay GetSecondaryInletNode GetSecondaryOutletNode GetSetPointManagerInputs GetShadingSurfReflectanceData GetShadowingInput GetShelfInput GetSimpleAirModelInputs GetSimpleShdSurfaceData GetSimpleWatertoAirHPInput GetSingleDayScheduleValues GetSiteAtmosphereData GetSizingParams GetSnowGroundRefModifiers GetSolarCollectorInput GetSpecialDayPeriodData GetSpecificHeatGlycol getSpecificUnitDivider getSpecificUnitIndex getSpecificUnitMultiplier GetSplitterInput GetSplitterInput GetSplitterNodeNumbers GetSplitterOutletNumber GetStandAloneERV GetStandAloneERVNodes GetStandAloneERVOutAirNode GetStandAloneERVReturnAirNode GetStandAloneERVZoneInletAirNode GetStandardMeterResourceType GetSteamBaseboardInput GetSteamCoilAvailScheduleIndex GetSteamCoilControlNodeNum GetSteamCoilIndex GetSteamCoilInput GetSTM GetStormWindowData GetSupHeatDensityRefrig GetSupHeatEnthalpyRefrig GetSupHeatPressureRefrig GetSupplyAirFlowRate GetSupplyAirFlowRate GetSupplyAirInletNode GetSupplyInletNode GetSupplyOutletNode GetSurfaceCountForOSCM GetSurfaceData GetSurfaceGroundHeatExchanger GetSurfaceHeatTransferAlgorithmOverrides GetSurfaceIndecesForOSCM GetSurfaceListsInputs GetSurfHBDataForMundtModel GetSurfHBDataForTempDistModel GetSysAvailManagerInputs GetSysAvailManagerListInputs GetSysInput GetSystemNodeNumberForZone GetSystemSizingInput GetTDDInput GetTESCoilIndex GetTESCoilInput GetThermalChimney GetTowerInput GetTranspiredCollectorIndex GetTranspiredCollectorInput GetTypeOfCoil GetUFADZoneData GetUnitarySystemDXCoolingCoilIndex GetUnitarySystemInput GetUnitarySystemOAHeatCoolCoil GetUnitConversion GetUnitHeaterInput GetUnitsString GetUnitSubString GetUnitVentilatorInput GetUnitVentilatorMixedAirNode GetUnitVentilatorOutAirNode GetUnitVentilatorReturnAirNode GetUnitVentilatorZoneInletAirNode GetUserConvectionCoefficients GetUserDefinedComponents GetUserDefinedOpSchemeInput GetUserDefinedPatternData GetUTSCTsColl GetVariableKeyCountandType GetVariableKeyCountandType GetVariableKeys GetVariableKeys GetVariableTypeAndIndex GetVariableUnitsString GetVarSpeedCoilInput GetVentilatedSlabInput GetVertices GetViscosityGlycol GetVRFInput GetVSCoilCondenserInletNode GetVSCoilMinOATCompressor GetVSCoilNumOfSpeeds GetWaterCoilAvailScheduleIndex GetWaterCoilCapacity GetWaterCoilIndex GetWaterCoilInput GetWaterMainsTemperatures GetWaterManagerInput GetWaterSource GetWaterThermalTankInput GetWatertoAirHPInput GetWatertoWaterHPInput GetWaterUseInput GetWeatherProperties GetWeatherStation GetWindowAC GetWindowACMixedAirNode GetWindowACOutAirNode GetWindowACReturnAirNode GetWindowACZoneInletAirNode GetWindowGapAirflowControlData GetWindowGlassSpectralData GetWindowShadingControlData GetWindTurbineInput GetWrapperInput GetWTGeneratorResults GetZoneAirDistribution GetZoneAirLoopEquipment GetZoneAirSetpoints GetZoneAndZoneListNames GetZoneContaminanInputs GetZoneContaminanSetpoints GetZoneData GetZoneDehumidifierInput GetZoneDehumidifierNodeNumber GetZoneEqAvailabilityManager GetZoneEquipment GetZoneEquipmentData GetZoneEquipmentData1 GetZoneInfilAirChangeRate GetZoneLoads GetZonePlenumInput GetZoneSizingInput GLtoAMB GoAhead guess HasFractionalScheduleValue hatter HCInWindowStandardRatings HConvGap HcUCSDCV HcUCSDDV HcUCSDUF HeatingCoilVarSpeedCycResidual HeatingCoilVarSpeedResidual HeatPumpRunFrac HeatPumpRunFrac HeatPumpRunFrac HeatWatertoAirHPTempResidual Height HEMINT HIC_ASHRAE HotWaterCoilResidual HotWaterCoilResidual HotWaterCoilResidual HotWaterCoilResidual HotWaterCoilResidual HotWaterHeatingCoilResidual HRadPar HTRANS HTRANS0 HTRANS1 HWBaseboardUAResidual HXAssistDXCoilResidual HXAssistedCoolCoilHRResidual HXAssistedCoolCoilHRResidual HXAssistedCoolCoilTempResidual HXAssistedCoolCoilTempResidual HXDemandSideLoopFlowResidual HybridVentilationControl IAM iCheckScheduleValue ICSCollectorAnalyticalSoluton iGetCoilAirOutletNode iGetCoilSteamInletNode iGetCoilSteamOutletNode INCLOS incrementEconVar IncrementInstMeterCache incrementSteps incrementTableEntry InitAirflowNetwork InitAirflowNetworkData InitAirHeatBalance InitAirLoops InitAirLoopSplitter InitAirMixer InitAirTerminalUserDefined InitAirZoneReturnPlenum InitAirZoneSupplyPlenum InitATMixer InitBaseboard InitBaseboard InitBLASTAbsorberModel InitBoiler InitBoiler InitBoreholeHXSimVars InitBSDFWindows InitCBVAV InitCoilUserDefined InitComplexWindows InitComponentNodes InitConductionTransferFunctions InitConnections InitConstCOPChiller InitController InitCoolBeam InitCTGenerators InitCurveReporting InitDaylightingDevices InitDemandManagers InitDesiccantDehumidifier InitDetailedIceStorage InitDirectAir InitDualDuct InitDuct InitDXCoil InitDXCoolingSystem InitDXHeatPumpSystem InitElecReformEIRChiller InitElectricBaseboard InitElectricChiller InitElectricEIRChiller InitEMS InitEMSControlledConstructions InitEMSControlledSurfaceProperties InitEnergyReports InitEngineDrivenChiller InitEquivalentLayerWindowCalculations InitEvapCooler InitEvapFluidCooler InitExhaustAbsorber InitExteriorConvectionCoeff InitFan InitFanCoilUnits InitFluidCooler InitFluidHeatExchanger InitFuelCellGenerators InitFurnace InitGasAbsorber InitGlassOpticalCalculations InitGshp InitGshp InitGTChiller InitHeatBalance InitHeatBalFiniteDiff InitHeatBalHAMT InitHeatingCoil InitHeatRecovery InitHighTempRadiantSystem InitHumidifier InitHWBaseboard InitHXAssistedCoolingCoil InitHybridVentSysAvailMgr InitialInitHeatBalFiniteDiff InitializeCFSDaylighting InitializeCFSStateData InitializeComponentSizingTable InitializeConstructionsTables InitializeDaylightMapTables InitializeEnvironmentPeriodsTable InitializeErrorsTable InitializeGlycolTempLimits InitializeHeatTransferPipes InitializeIndexes InitializeIndexes InitializeLoops InitializeMaterialsTable InitializeMeters initializeMonetaryUnit InitializeNominalBaseboardHeatTable InitializeNominalElectricEquipmentTable InitializeNominalGasEquipmentTable InitializeNominalHotWaterEquipmentTable InitializeNominalInfiltrationTable InitializeNominalLightingTable InitializeNominalOtherEquipmentTable InitializeNominalPeopleTable InitializeNominalSteamEquipmentTable InitializeNominalVentilationTable InitializeOperatingMode InitializeOutput InitializePipes InitializePredefinedMonthlyTitles InitializePsychRoutines InitializePumps InitializeRefrigerantLimits InitializeReportMeterDataDictionaryTable InitializeReportMeterDataTables InitializeReportVariableDataDictionaryTable InitializeReportVariableDataTables InitializeRoomAirModelTable InitializeRootFinder InitializeRuntimeLanguage InitializeSchedulesTable InitializeSimulationsTable InitializeSQLiteTables InitializeSurfacesTable InitializeSystemSizingTable InitializeTabularDataTable InitializeTabularDataTable InitializeTabularDataView InitializeTabularDataView InitializeTabularMonthly InitializeTimeIndicesTable InitializeViews InitializeWeather InitializeZoneGroupTable InitializeZoneInfoTable InitializeZoneListTable InitializeZoneSizingTable InitICEngineGenerators InitIndirectAbsorpChiller InitIndUnit InitInteriorConvectionCoeffs InitInteriorRadExchange InitInternalHeatGains InitIntSolarDistribution InitLoadBasedControl InitLoadDistribution InitLowTempRadiantSystem InitMicroCHPNoNormalizeGenerators InitMoistureBalanceEMPD InitMSHeatPump InitMTGenerators InitMundtModel InitOAController InitOAMixer InitOneTimePlantSizingInfo InitOutAirNodes InitOutdoorAirUnit InitOutsideAirSys InitPipesHeatTransfer InitPipingSystems InitPIU InitPlantProfile InitPlantUserComponent InitPlantValves InitPollutionMeterReporting InitPondGroundHeatExchanger InitPressureDrop InitPTUnit InitPurchasedAir InitPVTcollectors InitRefrigeration InitRefrigerationPlantConnections InitReturnAirPath InitSecretObjects InitSetPointManagers InitSimpleIceStorage InitSimpleMixingConvectiveHeatGains InitSimpleWatertoAirHP InitSimVars InitSimVars InitSimVars InitSimVars InitSolarCalculations InitSolarCollector InitSolarHeatGains InitSolReflRecSurf InitStandAloneERV InitSteamBaseboard InitSteamCoil InitSurfaceGroundHeatExchanger InitSurfaceHeatBalance InitSys InitSysAvailManagers InitSystemOutputRequired InitTempDistModel InitTESCoil InitThermalAndFluxHistories InitThermalComfort InitTower InitTranspiredCollector InitTRNSYSPV InitUCSDCV InitUCSDDV InitUCSDUF InitUniqueNodeCheck InitUnitarySystems InitUnitHeater InitUnitVentilator InitVarSpeedCoil InitVentilatedSlab InitVRF InitWaterCoil InitWaterSource InitWaterThermalTank InitWatertoAirHP InitWatertoWaterHP InitWindowAC InitWindTurbine InitWrapper InitZoneAirLoopEquipment InitZoneAirSetpoints InitZoneAirUserDefined InitZoneContSetpoints InitZoneDehumidifier InitZoneEquipment InitZoneEvaporativeCoolerUnit InPolygon InsertCurrencySymbol int_times_vector INTCPT Integer_IsInRange IntegerIsWithinTwoValues IntegerToString InterConnectTwoPlantLoopSides InteriorBCEqns InteriorNodeEqns InternalRangeCheck InternalSetupTankDemandComponent InternalSetupTankSupplyComponent interp INTERP InterpBlind InterpDefValuesForGlycolConc Interpolate Interpolate_Lagrange InterpolateBetweenFourValues InterpolateBetweenTwoValues InterpolatePipeTransBeam InterpProfAng InterpProfSlatAng InterpretWeatherDataLine InterpSlatAng InterpSw InterpValuesForGlycolConc IntInterfaceNodeEqns IntPreDefTableEntry IntToStr Invert3By3Matrix InvertMatrix InvJulianDay IPTrimSigDigits iRoundSigDigits IS_BEAM IS_DIFF IS_DSRATIO IS_F IS_LWP IS_OPENNESS IS_SWP isCompLoadRepReq IsControlledShade IsConverged_CurrentToPrevIteration IsConverged_PipeCurrentToPrevIteration IsCurveInputTypeValid IsCurveOutputTypeValid isExternalInterfaceErlVariable IsGlazeLayerX IsGZSLayer isInQuadrilateral IsInRange isInTriangle IsLeapYear IsNodeOnSetPtManager IsParentObject IsParentObjectCompSet IsShadingLayer IssueSevereAlphaInputFieldError IssueSevereInputFieldError IssueSevereRealInputFieldError IsValidConnectionType IsVBLayer isWithinRange ITERATE IterateRootFinder iTrimSigDigits JGDate JulianDay LClimb LDSumMax LDSumMean LEEDtariffReporting LimitCoilCapacity LimitController LimitTUCapacity LinesOut linint LoadEquipList LoadInterface LogicalToInteger LogicalToInteger LogPlantConvergencePoints lookupOperator LookUpScheduleValue LookUpSeason LookupSItoIP lubksb LUBKSB ludcmp LUDCMP LUdecomposition LUsolution MakeAnchorName MakeHVACTimeIntervalString MakeMirrorSurface MakeRectangularVertices MakeRelativeRectangularVertices MakeTransition MakeUPPERCase ManageAirflowNetworkBalance ManageAirHeatBalance ManageAirLoops ManageAirModel ManageBranchInput ManageControllers ManageCoolTower ManageDemand ManageEarthTube ManageElectCenterStorageInteractions ManageElectricLoadCenters ManageElectStorInteractions ManageEMS ManageExteriorEnergyUse ManageGeneratorControlState ManageGeneratorFuelFlow ManageHeatBalance ManageHeatBalFiniteDiff ManageHeatBalHAMT ManageHVAC ManageHybridVentilation ManageInsideAdaptiveConvectionAlgo ManageInternalHeatGains ManageInverter ManageMundtModel ManageNonZoneEquipment ManageOutsideAdaptiveConvectionAlgo ManageOutsideAirSystem ManagePlantLoadDistribution ManagePlantLoops ManageRefrigeratedCaseRacks ManageSetPoints ManageSimulation ManageSingleCommonPipe ManageSizing ManageSurfaceHeatBalance ManageSystemAvailability ManageThermalChimney ManageThermalComfort ManageTransformers ManageTwoWayCommonPipe ManageUCSDCVModel ManageUCSDDVModel ManageUCSDUFModels ManageUserDefinedPatterns ManageWater ManageWaterInits ManageWeather ManageZoneAirLoopEquipment ManageZoneAirUpdates ManageZoneContaminanUpdates ManageZoneEquipment MapExtConvClassificationToHcModels MapIntConvClassificationToHcModels MarkNode MatchAndSetColorTextString MatchPlantSys MatrixIndex matrixQBalance MeshPartition_CompareByDimension MeshPartition_SelectionSort MeshPartitionArray_Contains MinePlantStructForInfo MixedAirControlTempResidual ModifyWindow Modulus MonthToMonthNumber MovingAvg MRXINV MSHPCyclingResidual MSHPHeatRecovery MSHPVarSpeedResidual MultiModeDXCoilHumRatResidual MultiModeDXCoilHumRatResidual MultiModeDXCoilResidual MultiModeDXCoilResidual MultiModeDXCoilResidual MultiSpeedDXCoolingCoilStandardRatings MultiSpeedDXHeatingCoilStandardRatings MULTOL MyPlantSizingIndex NeighborInformationArray_Value NETRAD NewEMSVariable NewExpression newPreDefColumn newPreDefReport newPreDefSubTable NEWTON NodeHasSPMCtrlVarType NormalArea NumBranchesInBranchList NumCompsInBranch nusselt NusseltNumber OpenEPlusWeatherFile OPENNESS_LW OpenOutputFiles OpenOutputTabularFile OpenWeatherFile OPERATOR (*) OPERATOR (+) OPERATOR (-) OPERATOR (.dot.) OPERATOR (.twodcross.) OPERATOR (.twoddot.) OPERATOR (/) ORDER OutBaroPressAt OutDewPointTempAt OutDryBulbTempAt OutsidePipeHeatTransCoef OutWetBulbTempAt P01 PanesDeflection ParametricObjectsCheck parseComputeLine ParseExpression ParseStack ParseTime PartLoadFactor PassiveGapNusseltNumber PassPressureAcrossInterface PassPressureAcrossMixer PassPressureAcrossSplitter PD_BEAM PD_BEAM_CASE_I PD_BEAM_CASE_II PD_BEAM_CASE_III PD_BEAM_CASE_IV PD_BEAM_CASE_V PD_BEAM_CASE_VI PD_DIFF PD_LW PD_LWP PD_SWP PerformanceCurveObject PerformanceTableObject PerformIterationLoop PerformPipeCellSimulation PerformPipeCircuitSimulation PerformSolarCalculations PerformTemperatureFieldUpdate PierceSurface PierceSurfaceVector PipeCircuitInfo_InitInOutCells PipeSegmentInfo_InitPipeCells PIUInducesPlenumAir PIUnitHasMixer PlaneEquation PlantHalfLoopSolver PlantMassFlowRatesFunc PLRResidual PLRResidual PLRResidualMixedTank PLRResidualStratifiedTank PMVResidual POLY1F POLY2F POLYF polygon_contains_point_2d popStack pos PostIPProcessing POWER PreDefTableEntry PredictSystemLoads PredictZoneContaminants PreparePipeCircuitSimulation PrepDebugFilesAndVariables PreProcessorCheck PrepVariablesISO15099 PreScanReportingVariables PresProfile PressureCurveValue ProcessDataDicFile ProcessDateString ProcessEMSInput ProcessEPWHeader ProcessForDayTypes ProcessInput ProcessInputDataFile ProcessIntervalFields ProcessMinMaxDefLine ProcessNumber ProcessScheduleInput ProcessSurfaceVertices ProcessTokens ProduceMinMaxString ProduceMinMaxStringWStartMinute ProduceRDDMDD ProfileAngle PropagateResolvedFlow PStack PsyCpAirFnWTdb PsyHfgAirFnWTdb PsyHFnTdbRhPb PsyHFnTdbW PsyHgAirFnWTdb PsyPsatFnTemp PsyPsatFnTemp_raw PsyRhFnTdbRhov PsyRhFnTdbRhovLBnd0C PsyRhFnTdbWPb PsyRhoAirFnPbTdbW PsyRhovFnTdbRh PsyRhovFnTdbRhLBnd0C PsyRhovFnTdbWPb PsyTdbFnHW PsyTdpFnTdbTwbPb PsyTdpFnWPb PsyTsatFnHPb PsyTsatFnPb PsyTwbFnTdbWPb PsyTwbFnTdbWPb_raw PsyVFnTdbWPb PsyWFnTdbH PsyWFnTdbRhPb PsyWFnTdbTwbPb PsyWFnTdpPb psz Pt2Plane PullCompInterconnectTrigger PumpDataForTable PushBranchFlowCharacteristics PushInnerTimeStepArrays pushStack PushSystemTimestepHistories PushSystemTimestepHistories PushZoneTimestepHistories PushZoneTimestepHistories QsortC QsortPartition RadialCellInfo_XY_CrossSectArea RadialCellInformation_ctor RadialSizing_Thickness Rainflow RangeCheck RB_BEAM RB_DIFF RB_F RB_LWP RB_SWP rCheckDayScheduleValueMinMax rCheckScheduleValue rCheckScheduleValueMinMax1 rCheckScheduleValueMinMax2 ReadEnergyMeters ReadEPlusWeatherForDay ReadGeneralDomainInputs ReadHorizontalTrenchInputs ReadINIFile ReadInputLine ReadPipeCircuitInputs ReadPipeSegmentInputs ReadTableData ReadUserWeatherInput ReadWeatherForDay Real_ConstrainTo Real_IsInRange real_times_vector ReAllocateAndPreserveOutputVariablesForSimulation ReallocateIntegerArray ReallocateIVar ReallocateRealArray ReallocateRVar RealPreDefTableEntry RealToStr RecKeepHeatBalance RecordOutput RectangleF_Contains ReformEIRChillerCondInletTempResidual ReformEIRChillerHeatRecovery RegisterNodeConnection RegisterPlantCompDesignFlow RegulateCondenserCompFlowReqOp ReInitPlantLoopsAtFirstHVACIteration RemoveSpaces RemoveTrailingZeros reorder ReplaceBlanksWithUnderscores ReplaceBlanksWithUnderscores ReportAirflowNetwork ReportAirHeatBalance ReportAirLoopConnections ReportAirTerminalUserDefined ReportAndTestGlycols ReportAndTestRefrigerants ReportBaseboard ReportBaseboard ReportCBVAV ReportChillerIPLV ReportCoilUserDefined ReportCompSetMeterVariables ReportController ReportCoolBeam ReportCoolTower ReportCTFs ReportCWTankInits ReportDemandManagerList ReportDesiccantDehumidifier ReportDetailedIceStorage ReportDirectAir ReportDualDuct ReportDualDuctConnections ReportDuct ReportDXCoil ReportDXCoilRating ReportDYMeters ReportEarthTube ReportEconomicVariable ReportElectricBaseboard ReportEMS ReportEvapCooler ReportEvapFluidCooler ReportExteriorEnergyUse ReportFan ReportFanCoilUnit ReportFatalGlycolErrors ReportFatalRefrigerantErrors ReportFiniteDiffInits ReportFluidCooler ReportFluidHeatExchanger ReportForTabularReports ReportFurnace ReportGlass ReportHeatBalance ReportHeatingCoil ReportHeatRecovery ReportHighTempRadiantSystem ReportHRMeters ReportHumidifier ReportHWBaseboard ReportIllumMap ReportingFreqName ReportingThisVariable ReportInternalHeatGains ReportLoopConnections ReportLowTempRadiantSystem ReportMaxVentilationLoads ReportMeterDetails ReportMissing_RangeData ReportMixer ReportMNMeters ReportMoistureBalanceEMPD ReportMSHeatPump ReportNodeConnections ReportOAController ReportOAMixer ReportOrphanFluids ReportOrphanRecordObjects ReportOrphanSchedules ReportOutdoorAirUnit ReportOutputFileHeaders ReportParentChildren ReportPipesHeatTransfer ReportPIU ReportPlantProfile ReportPlantUserComponent ReportPlantValves ReportPondGroundHeatExchanger ReportPTUnit ReportPumps ReportPurchasedAir ReportPV ReportRackSystem ReportRefrigerationComponents ReportReturnAirPath ReportRuntimeLanguage ReportScheduleDetails ReportScheduleValues ReportSizingOutput ReportSMMeters ReportSolarCollector ReportSplitter ReportStandAloneERV ReportStandAloneWaterUse ReportSteamBaseboard ReportSteamCoil ReportSurfaceErrors ReportSurfaceGroundHeatExchngr ReportSurfaceHeatBalance ReportSurfaces ReportSurfaceShading ReportSys ReportSysSizing ReportSystemEnergyUse ReportThermalChimney ReportTowers ReportTSMeters ReportUnitarySystem ReportUnitHeater ReportUnitVentilator ReportVentilatedSlab ReportVRFCondenser ReportVRFTerminalUnit ReportWarmupConvergence ReportWaterCoil ReportWaterManager ReportWaterThermalTank ReportWaterUse ReportWeatherAndTimeInformation ReportWindowAC ReportWindTurbine ReportZoneAirLoopEquipment ReportZoneAirUserDefined ReportZoneDehumidifier ReportZoneEquipment ReportZoneEvaporativeCoolerUnit ReportZoneMeanAirTemp ReportZoneReturnPlenum ReportZoneSizing ReportZoneSupplyPlenum ResetAllPlantInterConnectFlags ResetController ResetEnvironmentCounter ResetHVACControl ResetNodeData ResetPerformanceCurveOutput ResetRootFinder ResetTerminalUnitFlowLimits ResetWeekDaysByMonth Resimulate resist ReSolveAirLoopControllers ResolveAirLoopFlowLimits ResolveLocationInformation ResolveLockoutFlags ResolveLoopFlowVsPressure ResolveParallelFlows ResolveSysFlow ReverseAndRecalculate RevertZoneTimestepHistories RevertZoneTimestepHistories RevisePlantCallingOrder RezeroZoneSizingArrays RhoH2O RHtoVP RKG RoundSigDigits rRoundSigDigits rTrimSigDigits SafeCopyPlantNode SafeDiv SafeDivide SameString SandiaCellTemperature SandiaEffectiveIrradiance SandiaF1 SandiaF2 SandiaImp SandiaIsc SandiaIx SandiaIxx SandiaModuleTemperature SandiaTcellFromTmodule SandiaVmp SandiaVoc SaveSimpleController ScanForReports ScanPlantLoopsForNodeNum ScanPlantLoopsForObject sCheckDayScheduleValueMinMax ScheduleAverageHoursPerWeek SEARCH SearchAscTable SearchWindow5DataFile SecantFormula SecantMethod selectTariff SetActuatedBranchFlowRate SetAdditionalNeighborData SetAllFlowLocks SetAllPlantSimFlagsToValue SetATMixerPriFlow SetATMixerPriFlow SetAverageAirFlow SetAverageAirFlow SetAverageAirFlow SetAverageAirFlow SetAverageAirFlow SetAverageAirFlow SetCoilDesFlow SetCoilSystemCoolingData SetCoilSystemHeatingDXFlag SetCompFlowRate SetComponentFlowRate SetCurrentWeather SetCurveOutputMinMaxValues SetDSTDateRanges SetDXCoilTypeData SetDXCoolingCoilData SetEquivalentLayerWindowProperties SetErlValueNumber SetExtConvectionCoeff SetFanData SetHeatExchangerData SetHeatToReturnAirFlag SetInitialMeterReportingAndOutputNames SetIntConvectionCoeff SetInternalVariableValue SetMinMax setNativeVariables SetNodeResult SetOAControllerData SetOnOffMassFlowRate SetOnOffMassFlowRate SetOnOffMassFlowRate SetOnOffMassFlowRateVSCoil SetOnOffMassFlowRateVSCoil SetOutAirNodes SetOutBulbTempAt SetPredefinedTables SetSimpleWSHPData SETSKY SetSpecialDayDates SetSpeedVariables SetStormWindowControl SetSurfHBDataForMundtModel SetSurfHBDataForTempDistModel SetSurfTmeanAir SETUP4x4_A SetupAdaptiveConvectionRadiantSurfaceData SetupAdaptiveConvectionStaticMetaData SetupAirLoopControllersTracer SetupAllOutputVariables SetUpAndSort SetupBranchControlTypes SetupCellNeighbors SetupCommonPipes SetupComplexFenestrationMaterialInput SetupComplexFenestrationStateInput SetupComplexWindowStateGeometry SetUpCompSets SetupDElightOutput4EPlus SetupDElightOutput4EPlus SetUpDesignDay SetupEMSActuator SetupEMSIntegerActuator SetupEMSIntegerInternalVariable SetupEMSInternalVariable SetupEMSLogicalActuator SetupEMSRealActuator SetupEMSRealInternalVariable SetupEnvironmentTypes SetupFuelConstituentData SetupGeneratorControlStateManager SetupIndividualControllerTracer SetupInitialPlantCallingOrder SetupIntegerOutputVariable SetupInterpolationValues SetupLoopFlowRequest SetupMeteredVarsForSetPt SetupMundtModel SetupNodeSetpointsAsActuators SetupNodeVarsForReporting SetupOutputVariable SetupPipeCircuitInOutCells SetupPlantEMSActuators SetupPollutionCalculations SetupPollutionMeterReporting SetupPossibleOperators SetupPrimaryAirSystemAvailMgrAsActuators SetupPumpMinMaxFlows SetupRealOutputVariable SetupRealOutputVariable_IntKey SetupReportInput SetupReports SetupRootFinder SetUpSchemeColors SetupShadeSurfacesForSolarCalcs SetupSimpleWindowGlazingSystem SetupSimulation SetupStratifiedNodes SetupSurfaceConstructionActuators SetupSurfaceConvectionActuators SetupSurfaceOutdoorBoundaryConditionActuators SetUpSysSizingArrays SetupTankDemandComponent SetupTankSupplyComponent SetupThermostatActuators SetupTimePointers SetupUnitConversions SetupWeekDaysByMonth SetupWindowShadingControlActuators SetupZoneEquipmentForConvectionFlowRegime SetupZoneGeometry SetupZoneInfoAsInternalDataAvail SetupZoneInternalGain SetupZoneInternalGain SetupZoneSizing SetUpZoneSizingArrays SetUTSCQdotSource SetVarSpeedCoilData SetVentedModuleQdotSource SetVSHPAirFlow SetVSHPAirFlow SetWindSpeedAt SetZoneEquipSimOrder shading shadingedge shadingin SHADOW SharedDVCVUFDataInit SHDBKS SHDGSS SHDRVL SHDSBS shift ShiftPipeTemperaturesForNewIteration ShiftPlantLoopSideCallingOrder ShiftTemperaturesForNewIteration ShiftTemperaturesForNewTimeStep ShowAuditErrorMessage ShowBranchesOnLoop ShowContinueError ShowContinueError ShowContinueErrorTimeStamp ShowContinueErrorTimeStamp ShowErrorMessage ShowErrorMessage ShowFatalError ShowFatalError ShowMessage ShowMessage ShowPsychrometricSummary ShowRecurringContinueErrorAtEnd ShowRecurringContinueErrorAtEnd ShowRecurringErrors ShowRecurringSevereErrorAtEnd ShowRecurringSevereErrorAtEnd ShowRecurringWarningErrorAtEnd ShowRecurringWarningErrorAtEnd ShowSevereError ShowSevereError ShowSevereMessage ShowSevereMessage ShowWarningError ShowWarningError ShowWarningMessage ShowWarningMessage showWarningsBasedOnTotal Sim4PipeFanCoil SimAirChillerSet SimAirLoop SimAirLoopComponent SimAirLoopComponents SimAirLoops SimAirLoopSplitter SimAirMixer SimAirTerminalUserDefined SimAirZonePlenum SimATMixer SimBaseboard SimBLASTAbsorber SimBoiler SimCBVAV SimCBVAV SimCentralGroundSourceHeatPump SimChiller SimCoilUserDefined SimComponentModelFan SimConstVol SimCoolBeam SimCostEstimate SimCTGenerator SimCTPlantHeatRecovery SimCyclingWindowAC SimDesiccantDehumidifier SimDetailedIceStorage SimDirectAir SimDistrictEnergy SimDualDuctConstVol SimDualDuctVarVol SimDualDuctVAVOutdoorAir SimDuct SimDXCoil SimDXCoilMultiMode SimDXCoilMultiSpeed SimDXCoolingSystem SimDXHeatPumpSystem SimElecBaseBoard SimElectricBaseBoard SimElectricConvective SimElectricEIRChiller SimEvapCooler SimEvapFluidCoolers SimExhaustAbsorber SimFanCoilUnit SimFluidCoolers SimFluidHeatExchanger SimFourPipeIndUnit SimFuelCellGenerator SimFuelCellPlantHeatRecovery SimFurnace SimGasAbsorber SimGroundHeatExchangers SimHeatPumpWaterHeater SimHeatRecovery SimHighTempRadiantSystem SimHPWatertoWaterCOOLING SimHPWatertoWaterHEATING SimHPWatertoWaterSimple SimHumidifier SimHVAC SimHWBaseboard SimHWConvective SimHXAssistedCoolingCoil SimICEngineGenerator SimICEPlantHeatRecovery SimIceStorage SimIndirectAbsorber SimIndUnit SimLowTempRadiantSystem SimMicroCHPGenerator SimMicroCHPPlantHeatRecovery SimMSHeatPump SimMSHP SimMTGenerator SimMTPlantHeatRecovery SimMultiSpeedCoils SimOAComponent SimOAController SimOAMixer SimOnOffFan SimOutdoorAirEquipComps SimOutdoorAirUnit SimOutsideAirSys SimOutsideEnergy SimPackagedTerminalUnit SimPipes SimPipesHeatTransfer SimPipingSystemCircuit SimPIU SimPlantEquip SimPlantValves SimpleCoolingCoilUAResidual SimpleEvapFluidCoolerUAResidual SimpleFluidCoolerUAResidual SimpleHeatingCoilUAResidual SimpleTowerApproachResidual SimpleTowerTrResidual SimpleTowerUAResidual SimPondGroundHeatExchanger SimPressureDropSystem SimPTUnit SimPumps SimPurchasedAir SimPVGenerator SimPVTcollectors SimReformulatedEIRChiller SimRefrigCondenser SimReturnAirPath SimSelectedEquipment SimSetPointManagers SimSimpleEvapFluidCooler SimSimpleFan SimSimpleFluidCooler SimSimpleTower SimSolarCollector SimStandAloneERV SimSteamBaseboard SimSteamBoiler SimSteamCoils SimSurfaceGroundHeatExchanger SimSysAvailManager SimTESCoil SimTowers SimTranspiredCollector SimulateAllInteriorRadialSoilSlices SimulateAllLoopSideBranches SimulateAllLoopSidePumps SimulateDemandManagerList SimulateDetailedRefrigerationSystems SimulateDetailedTransRefrigSystems SimulateDualDuct SimulateFanComponents SimulateFluidCell SimulateHeatingCoilComponents SimulateInnerMostRadialSoilSlice SimulateLoopSideBranchGroup SimulateOuterMostRadialSoilSlice SimulatePlantProfile SimulateRadialInsulationCell SimulateRadialPipeCell SimulateRadialToCartesianInterface SimulateSingleDuct SimulateSteamCoilComponents SimulateVRF SimulateWaterCoilComponents SimulateWaterHeaterStandAlone SimulateWaterUse SimulateWaterUseConnection SimUnitaryBypassVAV SimUnitarySystem SimUnitHeater SimUnitVentilator SimUnitVentOAMixer SimUserDefinedPlantComponent SimVariableSpeedCoils SimVariableSpeedHP SimVariableSpeedHP SimVariableTower SimVariableVolumeFan SimVAV SimVAVVS SimVentilatedSlab SimVentSlabOAMixer SimVRF SimVRFCondenserPlant SimWaterCoils SimWaterSource SimWaterThermalTank SimWatertoAirHP SimWatertoAirHPSimple SimWindowAC SimWindTurbine SimZoneAirLoopEquipment SimZoneAirUserDefined SimZoneDehumidifier SimZoneEquipment SimZoneEvaporativeCoolerUnit SimZoneExhaustFan SimZoneOutAirUnitComps SingelSpeedDXCoolingCoilStandardRatings SingleSpeedDXHeatingCoilStandardRatings SingleSpeedFluidCooler SizeAbsorpChiller SizeAirLoopBranches SizeAirLoops SizeBaseboard SizeBoiler SizeBoiler SizeCBVAV SizeConstCOPChiller SizeController SizeCoolBeam SizeDemandSidePlantConnections SizeDirectAir SizeDualDuct SizeDXCoil SizeElecReformEIRChiller SizeElectricBaseboard SizeElectricBaseboard SizeElectricChiller SizeElectricEIRChiller SizeEngineDrivenChiller SizeEvapCooler SizeEvapFluidCooler SizeExhaustAbsorber SizeFan SizeFanCoilUnit SizeFluidCooler SizeFluidHeatExchanger SizeFurnace SizeGasAbsorber SizeGTChiller SizeHeatingCoil SizeHeatRecovery SizeHighTempRadiantSystem SizeHumidifier SizeHVACWaterToAir SizeHWBaseboard SizeIndirectAbsorpChiller SizeIndUnit SizeLowTempRadiantSystem SizeMSHeatPump SizeOAController SizeOutdoorAirUnit SizePIU SizePlantLoop SizePTUnit SizePump SizePurchasedAir SizePVT SizeStandAloneERV SizeStandAloneWaterHeater SizeSteamBaseboard SizeSteamCoil SizeSupplySidePlantConnections SizeSys SizeTankForDemandSide SizeTankForSupplySide SizeTESCoil SizeTower SizeUCSDUF SizeUnitarySystem SizeUnitHeater SizeUnitVentilator SizeVarSpeedCoil SizeVentilatedSlab SizeVRF SizeVRFCondenser SizeVSMerkelTower SizeWaterCoil SizeWaterManager SizeWaterSource SizeWindowAC SizeWrapper SizeZoneDehumidifier SizeZoneEquipment SizeZoneEvaporativeCoolerUnit SkipEPlusWFHeader SkyDifSolarShading SkyGndWeight SkyWeight SLtoAMB SLtoGL SLVSKY solar_EN673 solarISO15099 SolarSprectrumAverage SOLMATS SolveAirLoopControllers SolveForWindowTemperatures SolveRegression SolveRegulaFalsi SolverMoistureBalanceEMPD SOLVZP SortHistory Specular_Adjust Specular_EstimateDiffuseProps Specular_F Specular_OffNormal Specular_RATDiff Specular_SWP SQLiteBegin SQLiteBegin SQLiteBindDouble SQLiteBindInteger SQLiteBindLogicalMacro SQLiteBindNULL SQLiteBindText SQLiteBindTextMacro SQLiteClearBindings SQLiteCloseDatabase SQLiteColumnInt SQLiteColumnIntMacro SQLiteCommit SQLiteCommit SQLiteExecuteCommand SQLiteExecuteCommandMacro SQLiteFinalizeCommand SQLiteOpenDatabase SQLiteOpenDatabaseMacro SQLitePrepareStatement SQLitePrepareStatementMacro SQLiteResetCommand SQLiteStepCommand SQLiteWriteMessage SQLiteWriteMessageMacro SQLiteWriteMessageMacro StandardIndexTypeKey StandardVariableTypeKey StartingWindowTemps StartingWinTempsForNominalCond SteamHeatingCoilResidual StorageType StoreAPumpOnCurrentTempLoop storeIterationResults StoreRecurringErrorMessage StringValue StrToReal SumAllInternalCO2Gains SumAllInternalConvectionGains SumAllInternalGenericContamGains SumAllInternalLatentGains SumAllInternalRadiationGains SumAllReturnAirConvectionGains SumAllReturnAirLatentGains SumHATsurf SumHATsurf SumHATsurf SumHATsurf SumHATsurf SumHATsurf SumInternalCO2GainsByTypes SumInternalConvectionGainsByTypes SumInternalLatentGainsByTypes SumInternalRadiationGainsByTypes SummarizeErrors SumReturnAirConvectionGainsByTypes SumZoneImpacts SUN3 SUN4 SupSATResidual SurfaceScheduledSolarInc SurveyDemandManagers SystemPropertiesAtLambdaAndPhi SystemSpectralPropertiesAtPhi TableLookupObject TARCOG90 TBND TdbFnHRhPb TDMA TDMA_R TellMeHowManyObjectItemArgs TemperaturesFromEnergy TempIPtoSI TempSItoIP terpld TESCoilHumRatResidual TESCoilResidual TestAirPathIntegrity TestBranchIntegrity TestCompSet TestCompSetInletOutletNodes TestInletOutletNodes TestReturnAirPathIntegrity TestSupplyAirPathIntegrity therm1d TightenNodeMinMaxAvails TimestepInitComplexFenestration TimestepTypeName TraceAirLoopController TraceAirLoopControllers TraceIndividualController TraceIterationStamp TrackAirLoopController TrackAirLoopControllers TRadC TransAndReflAtPhi TransformVertsByAspect TransTDD Triangulate TrimSigDigits TurnOffLoopEquipment TurnOffLoopSideEquipment TurnOffReportRangeCheckErrors TurnOnPlantLoopPipes TurnOnReportRangeCheckErrors TwoSpeedFluidCooler UnitarySystemHeatRecovery UpdateAbsorberChillerComponentGeneratorSide UpdateAirflowNetwork UpdateAirMixer UpdateAirSysCompPtrArray UpdateAirSysSubCompPtrArray UpdateAirSysSubSubCompPtrArray UpdateAirZoneReturnPlenum UpdateAirZoneSupplyPlenum UpdateAnyLoopDemandAlterations UpdateATMixer UpdateBaseboard UpdateBaseboardPlantConnection UpdateBasementSurfaceTemperatures UpdateBBElecRadSourceValAvg UpdateBBRadSourceValAvg UpdateBBSteamRadSourceValAvg UpdateBLASTAbsorberRecords UpdateBoilerRecords UpdateBoilerRecords UpdateBracket UpdateBranchConnections UpdateChillerComponentCondenserSide UpdateChillerheaterRecords UpdateChillerRecords UpdateColdWeatherProtection UpdateCommonPipe UpdateComplexWindows UpdateComponentHeatRecoverySide UpdateConstCOPChillerRecords UpdateController UpdateCoolBeam UpdateCoolTower UpdateCTGeneratorRecords UpdateDataandReport UpdateDemandManagers UpdateDesiccantDehumidifier UpdateDetailedIceStorage UpdateDualDuct UpdateDuct UpdateDXCoil UpdateElectricBaseboard UpdateElectricChillerRecords UpdateElectricEIRChillerRecords UpdateEMSTrendVariables UpdateEngineDrivenChiller UpdateEvapCooler UpdateEvapFluidCooler UpdateEvaporativeCondenserBasinHeater UpdateEvaporativeCondenserWaterUse UpdateExhaustAbsorberCoolRecords UpdateExhaustAbsorberHeatRecords UpdateExhaustAirFlows UpdateFan UpdateFinalSurfaceHeatBalance UpdateFluidCooler UpdateFluidHeatExchanger UpdateFuelCellGeneratorRecords UpdateGasAbsorberCoolRecords UpdateGasAbsorberHeatRecords UpdateGSHPRecords UpdateGSHPRecords UpdateGSHPRecords UpdateGTChillerRecords UpdateHalfLoopInletTemp UpdateHeatBalHAMT UpdateHeatingCoil UpdateHeatRecovery UpdateHighTempRadiantSystem UpdateHistories UpdateHistory UpdateHTRadSourceValAvg UpdateHumidifier UpdateHVACInterface UpdateHWBaseboard UpdateHWBaseboardPlantConnection UpdateIceFractions UpdateICEngineGeneratorRecords UpdateIndirectAbsorberRecords UpdateInternalGainValues UpdateIrrigation UpdateLoadCenterRecords UpdateLoopSideReportVars UpdateLowTempRadiantSystem UpdateMeterReporting UpdateMeters UpdateMeterValues UpdateMicroCHPGeneratorRecords UpdateMinMax UpdateMixedAirSetPoints UpdateMoistureBalanceEMPD UpdateMoistureBalanceFD UpdateMSHeatPump UpdateMTGeneratorRecords UpdateNode UpdateNodeThermalHistory UpdateOAController UpdateOAMixer UpdateOAPretreatSetPoints UpdatePipesHeatTransfer UpdatePipingSystems UpdatePlantLoopInterface UpdatePlantMixer UpdatePlantProfile UpdatePlantSplitter UpdatePlantValves UpdatePondGroundHeatExchanger UpdatePrecipitation UpdatePressureDrop UpdatePurchasedAir UpdatePVTcollectors UpdateRadSysSourceValAvg UpdateRecords UpdateReformEIRChillerRecords UpdateRefrigCondenser UpdateReportWaterSystem UpdateRootFinder UpdateScheduleValues UpdateSetPointManagers UpdateSimpleWatertoAirHP UpdateSoilProps UpdateSolarCollector UpdateSplitter UpdateSQLiteErrorRecord UpdateSQLiteErrorRecord UpdateSQLiteSimulationRecord UpdateSQLiteSimulationRecord UpdateSteamBaseboard UpdateSteamBaseboardPlantConnection UpdateSteamCoil UpdateSurfaceGroundHeatExchngr UpdateSys UpdateSysSizing UpdateSystemOutputRequired UpdateTabularReports UpdateTEStorage UpdateThermalHistories UpdateTowers UpdateTranspiredCollector UpdateUnitarySystemControl UpdateUtilityBills UpdateVarSpeedCoil UpdateVentilatedSlab UpdateVerticalGroundHeatExchanger UpdateVRFCondenser UpdateWaterCoil UpdateWaterConnections UpdateWaterManager UpdateWaterSource UpdateWaterThermalTank UpdateWaterToAirCoilPlantConnection UpdateWatertoAirHP UpdateWeatherData UpdateWholeBuildingRecords UpdateZoneAirLoopEquipment UpdateZoneCompPtrArray UpdateZoneDehumidifier UpdateZoneEquipment UpdateZoneInletConvergenceLog UpdateZoneListAndGroupLoads UpdateZoneSizing UpdateZoneSubCompPtrArray UpdateZoneSubSubCompPtrArray ValidateAndSetSysAvailabilityManagerType ValidateComponent ValidateDistributionSystem ValidateEMSProgramName ValidateEMSVariableName ValidateExhaustFanInput ValidateFlowControlPaths ValidateFuelType ValidateIndexType ValidateMaterialRoughness ValidateMonthDay ValidateNStandardizeMeterTitles ValidateObjectandParse ValidatePipeConstruction ValidatePLFCurve ValidateSection ValidateSectionsInput ValidateVariableType value_to_vector ValueToString VAVVSCoolingResidual VAVVSHCFanOnResidual VAVVSHWFanOnResidual VAVVSHWNoFanResidual VB_CriticalSlatAngle VB_DIFF VB_LWP VB_ShadeControl VB_SLAT_RADIUS_RATIO VB_SOL4 VB_SOL46_CURVE VB_SOL6 VB_SWP vec2d_cross_product vec2d_dot_product vec_cross_product vec_dot_product VecLength VecNegate VecNormalize VecRound VecSquaredLength vector_add vector_div_int vector_div_real vector_subtract vector_times_int vector_times_real vector_to_array VerifyControlledZoneForThermostat VerifyCustomMetersElecPowerMgr VerifyHeatExchangerParent VerifyName VerifySetPointManagers VerifyThermostatInZone VerifyUniqueBaseboardName VerifyUniqueBoilerName VerifyUniqueChillerName VerifyUniqueCoilName ViewFac VisibleSprectrumAverage Volume VRMLOut VSCoilCyclingHumResidual VSCoilCyclingResidual VSCoilCyclingResidual VSCoilSpeedHumResidual VSCoilSpeedResidual VSCoilSpeedResidual VSEvapUnitLoadResidual VSHPCyclingResidual VSHPCyclingResidual VSHPSpeedResidual VSHPSpeedResidual VSMerkelResidual W5InitGlassParameters W5LsqFit W5LsqFit2 W6CoordsFromWorldVect warnIfNativeVarname WetCoilOutletCondition WhichCompSet WhichParentCompSet WhichParentSet Width WindowGapAirflowControl WindowGasConductance WindowGasPropertiesAtTemp WindowHeatBalanceEquations WindowScheduledSolarAbs WindowShadingManager WindowTempsForNominalCond WindSpeedAt Windward WorldVectFromW6 WriteAdaptiveComfortTable WriteAirLoopStatistics WriteBEPSTable WriteCompCostTable WriteComponentSizing WriteCumulativeReportMeterData WriteDaylightMapTitle WriteDemandEndUseSummary WriteInputArguments WriteIntegerData WriteIntegerVariableOutput WriteMeterDictionaryItem WriteModifiedArguments WriteMonthlyTables WriteOutputArguments WriteOutputEN673 WritePoint WritePredefinedTables WriteRealData WriteRealVariableOutput WriteReportHeaders WriteReportIntegerData WriteReportMeterData WriteReportRealData WriteReportVariableDictionaryItem WriteRootFinderStatus WriteRootFinderTrace WriteRootFinderTraceHeader WriteSourceEnergyEndUseSummary writeSubtitle WriteSurfaceShadowing WriteTable WriteTableOfContents WriteTabularLifeCycleCostReport WriteTabularReports WriteTabularTariffReports WriteTARCOGInputFile writeTextLine WriteTimeBinTables WriteTimeStampFormatData WriteTrace WriteVeriSumTable WriteZoneLoadComponentTable WVDC XNormalArea XYRectangle XZRectangle YNormalArea YZRectangle ZeroHVACValues ZNormalArea