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) | :: | TypeOfNum | |||
| integer, | intent(in) | :: | InletNodeNum | |||
| integer, | intent(in) | :: | OutletNodeNum | |||
| integer, | intent(in) | :: | HeatSourceType | |||
| real(kind=r64), | intent(in) | :: | ModelGeneratorHeatRate | |||
| real(kind=r64), | intent(in) | :: | ModelMassFlowRate | |||
| logical, | intent(in) | :: | FirstHVACIteration | 
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 UpdateAbsorberChillerComponentGeneratorSide(LoopNum, LoopSide, TypeOfNum,              &
                                     InletNodeNum, OutletNodeNum, HeatSourceType, &
                                     ModelGeneratorHeatRate, ModelMassFlowRate, FirstHVACIteration)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Brent Griffith
          !       DATE WRITTEN   February 2010
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! provides reusable update routine for absoption chiller's generator
          ! connection to plant loops
          ! METHODOLOGY EMPLOYED:
          ! check if anything changed or doesn't agree and set simulation flags.
          ! update outlet conditions if needed or possible
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE DataPlant,      ONLY: PlantLoop
  USE DataLoopNode ,  ONLY: Node, NodeType_Water, NodeType_Steam
  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) :: TypeOfNum ! Component's type index
  INTEGER ,  INTENT(IN) :: InletNodeNum ! Component's inlet node pointer
  INTEGER ,  INTENT(IN) :: OutletNodeNum ! Component's outlet node pointer
  INTEGER ,  INTENT(IN) :: HeatSourceType ! Type of fluid in Generator loop
  REAL(r64), INTENT(IN) :: ModelGeneratorHeatRate ! model's generator heat rate (W)
  REAL(r64), INTENT(IN) :: ModelMassFlowRate  ! model's generator mass flow rate (kg/s)
  LOGICAL,   INTENT(IN) :: FirstHVACIteration
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  LOGICAL :: DidAnythingChange = .FALSE. ! set to true if conditions changed
  INTEGER :: OtherLoopNum  ! local loop pointer for remote connected loop
  INTEGER :: OtherLoopSide ! local loop side pointer for remote connected loop
!  INTEGER :: CountConnectedLoops ! local total number of connected loops
  INTEGER :: ConnectLoopNum  ! local do loop counter
  DidAnythingChange = .FALSE.
  ! check if node heat rate compares well with generator heat rate
  IF (HeatSourceType == NodeType_Water) THEN
  ELSEIF (HeatSourceType == NodeType_Steam) THEN
  ELSE
   ! throw error
  ENDIF
  !check if any conditions have changed
  IF (Node(InletNodeNum)%MassFlowRate /= ModelMassFlowRate) DidAnythingChange = .TRUE.
    IF ((Node(InletNodeNum)%MassFlowRate == 0.0D0) .AND. (ModelGeneratorHeatRate > 0.0D0) ) THEN
  ! DSU3 TODO also send a request that generator loop be made available, interlock message infrastructure??
    DidAnythingChange = .TRUE.
  ENDIF
  IF (DidAnythingChange .OR. FirstHVACIteration) THEN
    ! set sim flag for this loop
    PlantLoop(LoopNum)%LoopSide(LoopSide)%SimLoopSideNeeded = .TRUE.
    !set sim flag on connected loops to true because this side changed
    IF (PlantLoop(LoopNum)%LoopSide(LoopSide)%TotalConnected > 0) THEN
      DO ConnectLoopNum = 1, PlantLoop(LoopNum)%LoopSide(LoopSide)%TotalConnected
        IF (PlantLoop(LoopNum)%LoopSide(LoopSide)%Connected(ConnectLoopNum)%LoopDemandsOnRemote) THEN
          OtherLoopNum  = PlantLoop(LoopNum)%LoopSide(LoopSide)%Connected(ConnectLoopNum)%LoopNum
          OtherLoopSide = PlantLoop(LoopNum)%LoopSide(LoopSide)%Connected(ConnectLoopNum)%LoopSideNum
          PlantLoop(OtherLoopNum)%LoopSide(OtherLoopSide)%SimLoopSideNeeded = .TRUE.
        ENDIF
      ENDDO
    ENDIF
  ELSE ! nothing changed so turn off sim flag
    PlantLoop(LoopNum)%LoopSide(LoopSide)%SimLoopSideNeeded = .FALSE.
  ENDIF
  RETURN
END SUBROUTINE UpdateAbsorberChillerComponentGeneratorSide