Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| integer, | intent(in) | :: | LoopNum | |||
| integer, | intent(in) | :: | LoopSide | |||
| integer, | intent(in) | :: | BranchNum | |||
| integer, | intent(in) | :: | CompNum | |||
| integer, | intent(inout) | :: | UniqueCriteriaCheckIndex | |||
| integer, | intent(in) | :: | ConnectedLoopNum | |||
| integer, | intent(in) | :: | ConnectedLoopSide | |||
| integer, | intent(in) | :: | CriteriaType | |||
| real(kind=r64), | intent(in) | :: | CriteriaValue | 
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 PullCompInterconnectTrigger(LoopNum, LoopSide, BranchNum, CompNum, &
                                       UniqueCriteriaCheckIndex,              &
                                       ConnectedLoopNum, ConnectedLoopSide,   &
                                       CriteriaType, CriteriaValue)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Edwin Lee
          !       DATE WRITTEN   September 2010
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! Provides a generic means for components to trigger interconnected loop sides sim flags
          ! METHODOLOGY EMPLOYED:
          ! Determine convergence criteria based on *CriteriaType* variable.  This routine only turns
          !  the loop side sim flag ON, it doesn't turn it OFF.
          ! The convergence value history was originally going to be put at the Branch()%Comp()%...
          !  level, but this would be quite difficult if we had multiple convergence checks for the
          !  same component, such as if a chiller was trying to turn on the condenser side and the
          !  heat recovery side.
          ! It was determined to use a local array, which is only reallocated during the first stages
          !  of the simulation when components are first calling their sim flag requests.  After that
          !  the INOUT index variable will be used to avoid reallocation and string compares.
          ! Error handling will be put in to ensure unique identifiers are used for debugging purposes.
          ! A single component may have multiple check indeces, but a single index will only have one
          !  associated component.  Therefore whenever we come in with a non-zero index, we will just
          !  verify that the stored loop/side/branch/comp matches
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE DataPlant,      ONLY: PlantLoop, CriteriaType_MassFlowRate, CriteriaType_Temperature, CriteriaType_HeatTransferRate, &
                            CriteriaDelta_MassFlowRate, CriteriaDelta_Temperature, CriteriaDelta_HeatTransferRate
  IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER,          INTENT(IN)     :: LoopNum                  ! component's loop index
  INTEGER,          INTENT(IN)     :: LoopSide                 ! component's loop side number
  INTEGER,          INTENT(IN)     :: BranchNum                ! Component's branch number
  INTEGER,          INTENT(IN)     :: CompNum                  ! Component's comp number
  INTEGER,          INTENT(IN OUT) :: UniqueCriteriaCheckIndex ! An integer given to this particular check
                                                               !      -- set this to zero initially in calling routine
  INTEGER,          INTENT(IN)     :: ConnectedLoopNum         ! Component's interconnected loop number
  INTEGER,          INTENT(IN)     :: ConnectedLoopSide        ! Component's interconnected loop side number
  INTEGER,          INTENT(IN)     :: CriteriaType             ! The criteria check to use, see DataPlant: SimFlagCriteriaTypes
  REAL(r64),        INTENT(IN)     :: CriteriaValue            ! The value of the criteria check to evaluate
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
  TYPE CriteriaData
    INTEGER    :: CallingCompLoopNum     = 0     ! for debug error handling
    INTEGER    :: CallingCompLoopSideNum = 0     ! for debug error handling
    INTEGER    :: CallingCompBranchNum   = 0     ! for debug error handling
    INTEGER    :: CallingCompCompNum     = 0     ! for debug error handling
    REAL(r64)  :: ThisCriteriaCheckValue = 0.0d0 ! the previous value, to check the current against
  END TYPE CriteriaData
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  TYPE(CriteriaData), DIMENSION(:), ALLOCATABLE, SAVE :: CriteriaChecks ! stores criteria information
  TYPE(CriteriaData), DIMENSION(:), ALLOCATABLE :: TempCriteriaChecks   ! used for reallocation during initial calls
  TYPE(CriteriaData) :: CurCriteria ! for convenience
  INTEGER  :: PreviousNumChecksStored
  INTEGER, SAVE  :: CurrentNumChecksStored
  IF (UniqueCriteriaCheckIndex .LE. 0) THEN ! If we don't yet have an index, we need to initialize
    ! We need to start by allocating, or REallocating the array
    IF (.NOT. ALLOCATED(CriteriaChecks)) THEN
      CurrentNumChecksStored = 1
      ALLOCATE(CriteriaChecks(CurrentNumChecksStored))
    ELSE
      IF (ALLOCATED(TempCriteriaChecks)) DEALLOCATE(TempCriteriaChecks)
      PreviousNumChecksStored = SIZE(CriteriaChecks)
      CurrentNumChecksStored = PreviousNumChecksStored + 1
      ALLOCATE(TempCriteriaChecks(CurrentNumChecksStored))
      TempCriteriaChecks(1:PreviousNumChecksStored) = CriteriaChecks
      DEALLOCATE(CriteriaChecks)
      ALLOCATE(CriteriaChecks(CurrentNumChecksStored))
    END IF
    ! Store the unique name and location
    CriteriaChecks(CurrentNumChecksStored)%CallingCompLoopNum = LoopNum
    CriteriaChecks(CurrentNumChecksStored)%CallingCompLoopSideNum = LoopSide
    CriteriaChecks(CurrentNumChecksStored)%CallingCompBranchNum = BranchNum
    CriteriaChecks(CurrentNumChecksStored)%CallingCompCompNum = CompNum
    ! Since this was the first pass, it is safe to assume something has changed!
    ! Therefore we'll set the sim flag to true
    PlantLoop(ConnectedLoopNum)%LoopSide(ConnectedLoopSide)%SimLoopSideNeeded = .TRUE.
    ! Make sure we return the proper value of index
    UniqueCriteriaCheckIndex = CurrentNumChecksStored
  ELSE ! We already have an index
    ! If we have an index, we need to do a brief error handling, then determine
    !  sim flag status based on the criteria type
    ! First store the current check in a single variable instead of array for readability
    CurCriteria = CriteriaChecks(UniqueCriteriaCheckIndex)
    ! Check to make sure we didn't reuse the index in multiple components
    IF (     CurCriteria%CallingCompLoopNum     .NE. LoopNum &
        .OR. CurCriteria%CallingCompLoopSideNum .NE. LoopSide &
        .OR. CurCriteria%CallingCompBranchNum   .NE. BranchNum &
        .OR. CurCriteria%CallingCompCompNum     .NE. CompNum) THEN
      ! Diagnostic fatal: component does not properly utilize unique indexing
    END IF
    ! Initialize, then check if we are out of range
    SELECT CASE (CriteriaType)
      CASE (CriteriaType_MassFlowRate)
        IF (ABS(CurCriteria%ThisCriteriaCheckValue-CriteriaValue)>CriteriaDelta_MassFlowRate) THEN
          PlantLoop(ConnectedLoopNum)%LoopSide(ConnectedLoopSide)%SimLoopSideNeeded = .TRUE.
        END IF
      CASE (CriteriaType_Temperature)
        IF (ABS(CurCriteria%ThisCriteriaCheckValue-CriteriaValue)>CriteriaDelta_Temperature) THEN
          PlantLoop(ConnectedLoopNum)%LoopSide(ConnectedLoopSide)%SimLoopSideNeeded = .TRUE.
        END IF
      CASE (CriteriaType_HeatTransferRate)
        IF (ABS(CurCriteria%ThisCriteriaCheckValue-CriteriaValue)>CriteriaDelta_HeatTransferRate) THEN
          PlantLoop(ConnectedLoopNum)%LoopSide(ConnectedLoopSide)%SimLoopSideNeeded = .TRUE.
        END IF
      CASE DEFAULT
       ! Diagnostic fatal: improper criteria type
    END SELECT
  END IF ! if we have an index or not
  ! Store the value for the next pass
  CriteriaChecks(UniqueCriteriaCheckIndex)%ThisCriteriaCheckValue = CriteriaValue
 RETURN
END SUBROUTINE PullCompInterconnectTrigger