Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE CheckControllerListOrder
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         B. Griffith
          !       DATE WRITTEN   Oct 10.
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! check that if multiple controllers on an air loop, that they aren't listed in a bad order
          ! CR 8253
          ! METHODOLOGY EMPLOYED:
          ! setup data for sensed nodes and compare positions if on the same branch
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE DataAirSystems,  ONLY: PrimaryAirSystem
  USE DataHVACGlobals, ONLY: NumPrimaryAirSys
  USE InputProcessor,  ONLY: SameString, FindItemInList
  USE DataInterfaces,  ONLY: ShowFatalError, ShowContinueError, ShowSevereError
  IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
          ! na
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  INTEGER :: AirSysNum
  INTEGER :: ContrlNum
  INTEGER :: WaterCoilContrlCount
  INTEGER, DIMENSION(:,:), ALLOCATABLE :: ContrlSensedNodeNums !array for storing sense node info
  INTEGER :: SensedNodeIndex
  INTEGER :: BranchNodeIndex
  INTEGER :: BranchNum
  INTEGER :: foundControl
  Do AirSysNum = 1, NumPrimaryAirSys
    IF (PrimaryAirSystem(AirSysNum)%NumControllers > 1) THEN
      ! first see how many are water coil controllers
      WaterCoilContrlCount = 0 !init
      DO ContrlNum =1, PrimaryAirSystem(AirSysNum)%NumControllers
        If (SameString(PrimaryAirSystem(AirSysNum)%ControllerType(ContrlNum), 'CONTROLLER:WATERCOIL')) THEN
          WaterCoilContrlCount = WaterCoilContrlCount + 1
        ENDIF
      ENDDO
      IF (WaterCoilContrlCount > 1) THEN
        ALLOCATE(ContrlSensedNodeNums(WaterCoilContrlCount, 3))
        ContrlSensedNodeNums=0
        SensedNodeIndex = 0
        DO ContrlNum =1, PrimaryAirSystem(AirSysNum)%NumControllers
          IF (SameString(PrimaryAirSystem(AirSysNum)%ControllerType(ContrlNum), 'CONTROLLER:WATERCOIL')) THEN
            SensedNodeIndex = SensedNodeIndex + 1
            foundControl = FindItemInList(PrimaryAirSystem(AirSysNum)%ControllerName(ContrlNum), &
                                             ControllerProps%ControllerName, NumControllers)
            IF (foundControl > 0) THEN
              ContrlSensedNodeNums(SensedNodeIndex, 1) = ControllerProps(foundControl)%SensedNode
            ENDIF
          ENDIF
        ENDDO
      ENDIF
      !fill branch index for sensed nodes
      IF (ALLOCATED(ContrlSensedNodeNums)) THEN
        DO BranchNum = 1,PrimaryAirSystem(AirSysNum)%NumBranches
          DO SensedNodeIndex =1, WaterCoilContrlCount
            DO BranchNodeIndex = 1, PrimaryAirSystem(AirSysNum)%Branch(BranchNum)%TotalNodes
              IF ( ContrlSensedNodeNums(SensedNodeIndex, 1) &
                   == PrimaryAirSystem(AirSysNum)%Branch(BranchNum)%NodeNum(BranchNodeIndex)) THen
                ContrlSensedNodeNums(SensedNodeIndex, 2) = BranchNodeIndex
                ContrlSensedNodeNums(SensedNodeIndex, 3) = BranchNum
              ENDIF
            ENDDO
          ENDDO
        ENDDO
      ENDIF
      ! check if flow order doesn't agree with controller order
      IF (ALLOCATED(ContrlSensedNodeNums)) THEN
        DO SensedNodeIndex =1, WaterCoilContrlCount
          IF (SensedNodeIndex == 1) CYCLE
          IF (ContrlSensedNodeNums(SensedNodeIndex, 2) < ContrlSensedNodeNums(SensedNodeIndex-1, 2)) THEN
            !now see if on the same branch
            IF (ContrlSensedNodeNums(SensedNodeIndex, 3) == ContrlSensedNodeNums(SensedNodeIndex-1, 3)) THEN
              ! we have a flow order problem with water coil controllers
              CALL ShowSevereError('CheckControllerListOrder: A water coil controller list has the wrong order')
              CALL ShowContinueError('Check the AirLoopHVAC:ControllerList for the air loop called "' &
                                     //Trim(PrimaryAirSystem(AirSysNum)%Name)//'"')
              CALL ShowContinueError('When there are multiple Controller:WaterCoil objects for the same air loop, ' &
                                    //'they need to be listed in the proper order.')
              CALL ShowContinueError('The controllers should be listed in natural flow order with those for upstream' &
                                   //' coils listed before those for downstream coils.')
              CALL ShowContinueError('The sensed nodes specified for the respective controllers should also reflect this order.')
            ENDIF
          ENDIF
        ENDDO
      ENDIF
      IF (ALLOCATED(ContrlSensedNodeNums)) DEALLOCATE(ContrlSensedNodeNums)
    ENDIF ! controllers > 1
  ENDDO
  RETURN
END SUBROUTINE CheckControllerListOrder