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) | :: | ChillNum | |||
| logical, | intent(in) | :: | RunFlag | 
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 InitExhaustAbsorber(ChillNum,RunFlag)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Fred Buhl
          !       DATE WRITTEN   June 2003
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine is for initializations of Exhaust Fired absorption chiller
          ! components.
          ! METHODOLOGY EMPLOYED:
          ! Uses the status flags to trigger initializations.
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE DataGlobals,     ONLY : BeginEnvrnFlag, AnyEnergyManagementSystemInModel
  USE DataPlant,       ONLY : TypeOf_Chiller_ExhFiredAbsorption, ScanPlantLoopsForObject, PlantLoop, &
                              PlantSizeNotComplete, PlantSizesOkayToFinalize
  USE PlantUtilities,  ONLY : InterConnectTwoPlantLoopSides, InitComponentNodes, SetComponentFlowRate
  USE FluidProperties, ONLY : GetDensityGlycol
  USE EMSManager,      ONLY : iTemperatureSetpoint, CheckIfNodeSetpointManagedByEMS
  USE Psychrometrics,  ONLY : RhoH2O
          ! na
  IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER, INTENT (IN) :: ChillNum           ! number of the current engine driven chiller being simulated
  LOGICAL, INTENT(IN)  :: RunFlag            ! TRUE when chiller operating
                                             ! used to determine if heating side or cooling
                                             ! side of chiller-heater is being called
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  LOGICAL,SAVE        :: MyOneTimeFlag = .true.
  LOGICAL, ALLOCATABLE,Save, DIMENSION(:) :: MyEnvrnFlag
  LOGICAL, ALLOCATABLE, DIMENSION(:), SAVE :: MyPlantScanFlag
  INTEGER :: CondInletNode      ! node number of water inlet node to the condenser
  INTEGER :: CondOutletNode     ! node number of water outlet node from the condenser
  INTEGER :: HeatInletNode      ! node number of hot water inlet node
  INTEGER :: HeatOutletNode     ! node number of hot water outlet node
  LOGICAL :: errFlag
  REAL(r64) :: rho ! local fluid density
  REAL(r64) :: mdot ! lcoal fluid mass flow rate
  ! Do the one time initializations
  IF (MyOneTimeFlag) THEN
    ALLOCATE(MyPlantScanFlag(NumExhaustAbsorbers))
    ALLOCATE(MyEnvrnFlag(NumExhaustAbsorbers))
    MyEnvrnFlag = .TRUE.
    MyOneTimeFlag = .false.
    MyPlantScanFlag = .TRUE.
  END IF
  ! Init more variables
  IF (MyPlantScanFlag(ChillNum)) THEN
    ! Locate the chillers on the plant loops for later usage
    errFlag=.false.
    CALL ScanPlantLoopsForObject(ExhaustAbsorber(ChillNum)%Name, &
                                 TypeOf_Chiller_ExhFiredAbsorption, &
                                 ExhaustAbsorber(ChillNum)%CWLoopNum, &
                                 ExhaustAbsorber(ChillNum)%CWLoopSideNum, &
                                 ExhaustAbsorber(ChillNum)%CWBranchNum, &
                                 ExhaustAbsorber(ChillNum)%CWCompNum, &
                                 LowLimitTemp = ExhaustAbsorber(ChillNum)%CHWLowLimitTemp, &
                                 InletNodeNumber = ExhaustAbsorber(ChillNum)%ChillReturnNodeNum,  &
                                 errFlag=errFlag)
    IF (errFlag) THEN
      CALL ShowFatalError('InitExhaustAbsorber: Program terminated due to previous condition(s).')
    ENDIF
    CALL ScanPlantLoopsForObject(ExhaustAbsorber(ChillNum)%Name, &
                                 TypeOf_Chiller_ExhFiredAbsorption, &
                                 ExhaustAbsorber(ChillNum)%HWLoopNum, &
                                 ExhaustAbsorber(ChillNum)%HWLoopSideNum, &
                                 ExhaustAbsorber(ChillNum)%HWBranchNum, &
                                 ExhaustAbsorber(ChillNum)%HWCompNum, &
                                 InletNodeNumber = ExhaustAbsorber(ChillNum)%HeatReturnNodeNum,  &
                                 errFlag=errFlag)
    IF (errFlag) THEN
      CALL ShowFatalError('InitExhaustAbsorber: Program terminated due to previous condition(s).')
    ENDIF
    IF (ExhaustAbsorber(ChillNum)%isWaterCooled) THEN
      CALL ScanPlantLoopsForObject(ExhaustAbsorber(ChillNum)%Name, &
                                   TypeOf_Chiller_ExhFiredAbsorption, &
                                   ExhaustAbsorber(ChillNum)%CDLoopNum, &
                                   ExhaustAbsorber(ChillNum)%CDLoopSideNum, &
                                   ExhaustAbsorber(ChillNum)%CDBranchNum, &
                                   ExhaustAbsorber(ChillNum)%CDCompNum, &
                                   InletNodeNumber = ExhaustAbsorber(ChillNum)%CondReturnNodeNum,  &
                                   errFlag=errFlag)
      IF (errFlag) THEN
        CALL ShowFatalError('InitExhaustAbsorber: Program terminated due to previous condition(s).')
      ENDIF
      CALL InterConnectTwoPlantLoopSides( ExhaustAbsorber(ChillNum)%CWLoopNum,      &
                                          ExhaustAbsorber(ChillNum)%CWLoopSideNum,  &
                                          ExhaustAbsorber(ChillNum)%CDLoopNum,      &
                                          ExhaustAbsorber(ChillNum)%CDLoopSideNum,  &
                                          TypeOf_Chiller_ExhFiredAbsorption , .TRUE.)
      CALL InterConnectTwoPlantLoopSides( ExhaustAbsorber(ChillNum)%HWLoopNum,      &
                                          ExhaustAbsorber(ChillNum)%HWLoopSideNum,  &
                                          ExhaustAbsorber(ChillNum)%CDLoopNum,      &
                                          ExhaustAbsorber(ChillNum)%CDLoopSideNum,  &
                                          TypeOf_Chiller_ExhFiredAbsorption , .TRUE. )
    ENDIF
    CALL InterConnectTwoPlantLoopSides( ExhaustAbsorber(ChillNum)%CWLoopNum,      &
                                        ExhaustAbsorber(ChillNum)%CWLoopSideNum,  &
                                        ExhaustAbsorber(ChillNum)%HWLoopNum,      &
                                        ExhaustAbsorber(ChillNum)%HWLoopSideNum,  &
                                          TypeOf_Chiller_ExhFiredAbsorption, .TRUE. )
    ! check if outlet node of chilled water side has a setpoint.
    IF ((Node(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum)%TempSetPoint == SensedNodeFlagValue) .AND. &
        (Node(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum)%TempSetPointHi == SensedNodeFlagValue)) THEN
      IF (.NOT. AnyEnergyManagementSystemInModel) THEN
        IF (.NOT. ExhaustAbsorber(ChillNum)%ChillSetpointErrDone) THEN
          CALL ShowWarningError('Missing temperature setpoint on cool side for chiller heater named ' // &
                                        TRIM(ExhaustAbsorber(ChillNum)%Name) )
          CALL ShowContinueError('  A temperature setpoint is needed at the outlet node of this chiller ' // &
                                           ', use a SetpointManager')
          CALL ShowContinueError('  The overall loop setpoint will be assumed for chiller. The simulation continues ... ')
          ExhaustAbsorber(ChillNum)%ChillSetpointErrDone = .TRUE.
        ENDIF
      ELSE
       ! need call to EMS to check node
        errFlag = .FALSE. ! but not really fatal yet, but should be.
        CALL CheckIfNodeSetpointManagedByEMS(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum,iTemperatureSetpoint, errFlag)
        IF (errFlag) THEN
          IF (.NOT. ExhaustAbsorber(ChillNum)%ChillSetpointErrDone) THEN
            CALL ShowWarningError('Missing temperature setpoint on cool side for chiller heater named ' // &
                                        TRIM(ExhaustAbsorber(ChillNum)%Name) )
            CALL ShowContinueError('  A temperature setpoint is needed at the outlet node of this chiller evaporator ')
            CALL ShowContinueError('  use a Setpoint Manager to establish a setpoint at the chiller evaporator outlet node ')
            CALL ShowContinueError('  or use an EMS actuator to establish a setpoint at the outlet node ')
            CALL ShowContinueError('  The overall loop setpoint will be assumed for chiller. The simulation continues ... ')
            ExhaustAbsorber(ChillNum)%ChillSetpointErrDone = .TRUE.
          ENDIF
        ENDIF
      ENDIF
      ExhaustAbsorber(ChillNum)%ChillSetpointSetToLoop = .TRUE.
      Node(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum)%TempSetPoint =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPoint
      Node(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum)%TempSetPointHi =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPointHi
    ENDIF
    ! check if outlet node of hot water side has a setpoint.
    IF ((Node(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum)%TempSetPoint == SensedNodeFlagValue) .AND. &
        (Node(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum)%TempSetPointLo == SensedNodeFlagValue)) THEN
      IF (.NOT. AnyEnergyManagementSystemInModel) THEN
        IF (.NOT. ExhaustAbsorber(ChillNum)%HeatSetpointErrDone) THEN
          CALL ShowWarningError('Missing temperature setpoint on heat side for chiller heater named ' // &
                                        TRIM(ExhaustAbsorber(ChillNum)%Name) )
          CALL ShowContinueError('  A temperature setpoint is needed at the outlet node of this chiller ' // &
                                           ', use a SetpointManager')
          CALL ShowContinueError('  The overall loop setpoint will be assumed for chiller. The simulation continues ... ')
          ExhaustAbsorber(ChillNum)%HeatSetpointErrDone = .TRUE.
        ENDIF
      ELSE
       ! need call to EMS to check node
        errFlag = .FALSE. ! but not really fatal yet, but should be.
        CALL CheckIfNodeSetpointManagedByEMS(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum,iTemperatureSetpoint, errFlag)
        IF (errFlag) THEN
          IF (.NOT. ExhaustAbsorber(ChillNum)%HeatSetpointErrDone) THEN
            CALL ShowWarningError('Missing temperature setpoint on heat side for chiller heater named ' // &
                                        TRIM(ExhaustAbsorber(ChillNum)%Name) )
            CALL ShowContinueError('  A temperature setpoint is needed at the outlet node of this chiller heater ')
            CALL ShowContinueError('  use a Setpoint Manager to establish a setpoint at the heater side outlet node ')
            CALL ShowContinueError('  or use an EMS actuator to establish a setpoint at the outlet node ')
            CALL ShowContinueError('  The overall loop setpoint will be assumed for heater side. The simulation continues ... ')
            ExhaustAbsorber(ChillNum)%HeatSetpointErrDone = .TRUE.
          ENDIF
        ENDIF
      ENDIF
      ExhaustAbsorber(ChillNum)%HeatSetpointSetToLoop = .TRUE.
      Node(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum)%TempSetPoint =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%HWLoopNum)%TempSetPointNodeNum)%TempSetPoint
      Node(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum)%TempSetPointLo =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%HWLoopNum)%TempSetPointNodeNum)%TempSetPointLo
    ENDIF
    MyPlantScanFlag(ChillNum)=.FALSE.
  ENDIF
  CondInletNode  = ExhaustAbsorber(ChillNum)%CondReturnNodeNum
  CondOutletNode = ExhaustAbsorber(ChillNum)%CondSupplyNodeNum
  HeatInletNode  = ExhaustAbsorber(ChillNum)%HeatReturnNodeNum
  HeatOutletNode = ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum
  IF(MyEnvrnFlag(ChillNum) .and. BeginEnvrnFlag .AND. (PlantSizesOkayToFinalize))THEN
    IF (PlantSizeNotComplete) CALL SizeExhaustAbsorber(ChillNum)
    IF (ExhaustAbsorber(ChillNum)%isWaterCooled) THEN
      ! init max available condenser water flow rate
      IF (ExhaustAbsorber(ChillNum)%CDLoopNum > 0) THEN
        rho = GetDensityGlycol(PlantLoop(ExhaustAbsorber(ChillNum)%CDLoopNum)%FluidName, &
                                InitConvTemp,  &
                                PlantLoop(ExhaustAbsorber(ChillNum)%CDLoopNum)%FluidIndex, &
                                'InitExhaustAbsorber')
      ELSE
        rho = RhoH2O(InitConvTemp)
      ENDIF
      ExhaustAbsorber(ChillNum)%DesCondMassFlowRate = rho * ExhaustAbsorber(ChillNum)%CondVolFlowRate
      CALL InitComponentNodes(0.d0, ExhaustAbsorber(ChillNum)%DesCondMassFlowRate, &
                                    CondInletNode, CondOutletNode,      &
                                    ExhaustAbsorber(ChillNum)%CDLoopNum,     &
                                    ExhaustAbsorber(ChillNum)%CDLoopSideNum, &
                                    ExhaustAbsorber(ChillNum)%CDBranchNum,   &
                                    ExhaustAbsorber(ChillNum)%CDCompNum)
    ENDIF
    IF (ExhaustAbsorber(ChillNum)%HWLoopNum > 0) THEN
      rho = GetDensityGlycol(PlantLoop(ExhaustAbsorber(ChillNum)%HWLoopNum)%FluidName, &
                                InitConvTemp,  &
                                PlantLoop(ExhaustAbsorber(ChillNum)%HWLoopNum)%FluidIndex, &
                                'InitExhaustAbsorber')
    ELSE
       rho = RhoH2O(InitConvTemp)
    ENDIF
    ExhaustAbsorber(ChillNum)%DesHeatMassFlowRate = rho * ExhaustAbsorber(ChillNum)%HeatVolFlowRate
    !init available hot water flow rate
    CALL InitComponentNodes(0.d0, ExhaustAbsorber(ChillNum)%DesHeatMassFlowRate, &
                                  HeatInletNode, HeatOutletNode,      &
                                 ExhaustAbsorber(ChillNum)%HWLoopNum, &
                                 ExhaustAbsorber(ChillNum)%HWLoopSideNum, &
                                 ExhaustAbsorber(ChillNum)%HWBranchNum, &
                                 ExhaustAbsorber(ChillNum)%HWCompNum)
    IF (ExhaustAbsorber(ChillNum)%CWLoopNum > 0) THEN
      rho = GetDensityGlycol(PlantLoop(ExhaustAbsorber(ChillNum)%CWLoopNum)%FluidName, &
                                InitConvTemp,  &
                                PlantLoop(ExhaustAbsorber(ChillNum)%CWLoopNum)%FluidIndex, &
                                'InitExhaustAbsorber')
    ELSE
       rho = RhoH2O(InitConvTemp)
    ENDIF
    ExhaustAbsorber(ChillNum)%DesEvapMassFlowRate = rho * ExhaustAbsorber(ChillNum)%EvapVolFlowRate
    !init available hot water flow rate
    CALL InitComponentNodes(0.d0, ExhaustAbsorber(ChillNum)%DesEvapMassFlowRate, &
                                  ExhaustAbsorber(ChillNum)%ChillReturnNodeNum,   &
                                  ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum,   &
                                  ExhaustAbsorber(ChillNum)%CWLoopNum,     &
                                  ExhaustAbsorber(ChillNum)%CWLoopSideNum, &
                                  ExhaustAbsorber(ChillNum)%CWBranchNum,   &
                                  ExhaustAbsorber(ChillNum)%CWCompNum)
    MyEnvrnFlag(ChillNum) = .FALSE.
  END IF
  IF(.not. BeginEnvrnFlag)Then
    MyEnvrnFlag(ChillNum) = .TRUE.
  End IF
  !this component model works off setpoints on the leaving node
  ! fill from plant if needed
  IF (ExhaustAbsorber(ChillNum)%ChillSetpointSetToLoop) THEN
    Node(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum)%TempSetPoint =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPoint
    Node(ExhaustAbsorber(ChillNum)%ChillSupplyNodeNum)%TempSetPointHi =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%CWLoopNum)%TempSetPointNodeNum)%TempSetPointHi
  ENDIF
  IF ( ExhaustAbsorber(ChillNum)%HeatSetpointSetToLoop ) THEN
    Node(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum)%TempSetPoint =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%HWLoopNum)%TempSetPointNodeNum)%TempSetPoint
    Node(ExhaustAbsorber(ChillNum)%HeatSupplyNodeNum)%TempSetPointLo =  &
              Node(PlantLoop(ExhaustAbsorber(ChillNum)%HWLoopNum)%TempSetPointNodeNum)%TempSetPointLo
  ENDIF
  IF ((ExhaustAbsorber(ChillNum)%isWaterCooled) .AND. &
      ((ExhaustAbsorber(ChillNum)%InHeatingMode) .OR. (ExhaustAbsorber(ChillNum)%InCoolingMode)) &
        .AND. (.NOT. MyPlantScanFlag(ChillNum)) ) THEN
    mdot = ExhaustAbsorber(ChillNum)%DesCondMassFlowRate
    CALL SetComponentFlowRate(mdot, &
                              ExhaustAbsorber(ChillNum)%CondReturnNodeNum,     &
                              ExhaustAbsorber(ChillNum)%CondSupplyNodeNum,     &
                              ExhaustAbsorber(ChillNum)%CDLoopNum,     &
                              ExhaustAbsorber(ChillNum)%CDLoopSideNum, &
                              ExhaustAbsorber(ChillNum)%CDBranchNum,   &
                              ExhaustAbsorber(ChillNum)%CDCompNum)
  ELSE
    mdot = 0.d0
    CALL SetComponentFlowRate(mdot, &
                              ExhaustAbsorber(ChillNum)%CondReturnNodeNum,     &
                              ExhaustAbsorber(ChillNum)%CondSupplyNodeNum,     &
                              ExhaustAbsorber(ChillNum)%CDLoopNum,     &
                              ExhaustAbsorber(ChillNum)%CDLoopSideNum, &
                              ExhaustAbsorber(ChillNum)%CDBranchNum,   &
                              ExhaustAbsorber(ChillNum)%CDCompNum)
  END IF
  RETURN
END SUBROUTINE InitExhaustAbsorber