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 | 
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 SizeGTChiller(ChillNum)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Fred Buhl
          !       DATE WRITTEN   June 2002
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine is for sizing Gas Turbine Chiller Components for which capacities and flow rates
          ! have not been specified in the input.
          ! METHODOLOGY EMPLOYED:
          ! Obtains evaporator flow rate from the plant sizing array. Calculates nominal capacity from
          ! the evaporator flow rate and the chilled water loop design delta T. The condenser flow rate
          ! is calculated from the nominal capacity, the COP, and the condenser loop design delta T.
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE DataSizing
  USE DataPlant, ONLY : PlantLoop, PlantSizesOkayToFinalize
  USE PlantUtilities, ONLY: RegisterPlantCompDesignFlow
  USE ReportSizingManager, ONLY: ReportSizingOutput
  USE OutputReportPredefined
  USE FluidProperties, ONLY: GetDensityGlycol, GetSpecificHeatGlycol
  IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  Integer, Intent(IN) :: ChillNum
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
!unused1208  INTEGER             :: PltSizIndex   ! Plant Sizing Do loop index
  INTEGER             :: PltSizNum     ! Plant Sizing index corresponding to CurLoopNum
  INTEGER             :: PltSizCondNum ! Plant Sizing index for condenser loop
  LOGICAL             :: ErrorsFound   ! If errors detected in input
  LOGICAL             :: LoopErrorsFound
  REAL(r64)           :: EngineEff     ! this should be an input! needed to autosize the engine capacity.
  CHARACTER(len=MaxNameLength) :: equipName
  REAL(r64)           ::  rho  ! local fluid density
  REAL(r64)           ::  Cp   ! local fluid specific heat
  REAL(r64)           ::  tmpNomCap ! local nominal capacity cooling power
  REAL(r64)           ::  tmpEvapVolFlowRate ! local evaporator design volume flow rate
  REAL(r64)           ::  tmpCondVolFlowRate ! local condenser design volume flow rate
  PltSizNum = 0
  PltSizCondNum = 0
  EngineEff = 0.35d0
  ErrorsFound = .FALSE.
  tmpNomCap          = GTChiller(ChillNum)%Base%NomCap
  tmpEvapVolFlowRate = GTChiller(ChillNum)%Base%EvapVolFlowRate
  tmpCondVolFlowRate = GTChiller(ChillNum)%Base%CondVolFlowRate
  IF (GTChiller(ChillNum)%Base%CondenserType == WaterCooled) THEN
    IF (GTChiller(ChillNum)%Base%CondVolFlowRate == AutoSize) THEN
      PltSizCondNum = PlantLoop(GTChiller(ChillNum)%Base%CDLoopNum)%PlantSizNum
    END IF
  END IF
  PltSizNum = PlantLoop(GTChiller(ChillNum)%Base%CWLoopNum)%PlantSizNum
  IF (GTChiller(ChillNum)%Base%NomCap  == AutoSize) THEN
    IF (PltSizNum > 0) THEN
      IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
        rho = GetDensityGlycol(PlantLoop(GTChiller(ChillNum)%Base%CWLoopNum)%FluidName,  &
                                  InitConvTemp, &
                                  PlantLoop(GTChiller(ChillNum)%Base%CWLoopNum)%FluidIndex,&
                                  'SizeGTChiller')
        Cp = GetSpecificHeatGlycol(PlantLoop(GTChiller(ChillNum)%Base%CWLoopNum)%FluidName,  &
                                   InitConvTemp,                      &
                                   PlantLoop(GTChiller(ChillNum)%Base%CWLoopNum)%FluidIndex, &
                                   'SizeGTChiller')
        tmpNomCap = Cp * Rho * PlantSizData(PltSizNum)%DeltaT &
                                        * PlantSizData(PltSizNum)%DesVolFlowRate * GTChiller(ChillNum)%Base%SizFac
        IF (PlantSizesOkayToFinalize)  GTChiller(ChillNum)%Base%NomCap = tmpNomCap
      ELSE
        tmpNomCap = 0.d0
        IF (PlantSizesOkayToFinalize) GTChiller(ChillNum)%Base%NomCap = tmpNomCap
      END IF
      IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:CombustionTurbine', GTChiller(ChillNum)%Base%Name, &
                              'Nominal Capacity [W]', GTChiller(ChillNum)%Base%NomCap)
    ELSE
      CALL ShowSevereError('Autosizing of Gas Turbine Chiller nominal capacity requires a loop Sizing:Plant object')
      CALL ShowContinueError('Occurs in Gas Turbine Chiller object='//TRIM(GTChiller(ChillNum)%Base%Name))
      ErrorsFound = .TRUE.
    END IF
  END IF
  IF (GTChiller(ChillNum)%Base%EvapVolFlowRate == AutoSize) THEN
    IF (PltSizNum > 0) THEN
      IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
        tmpEvapVolFlowRate = PlantSizData(PltSizNum)%DesVolFlowRate * GTChiller(ChillNum)%Base%SizFac
        IF (PlantSizesOkayToFinalize) GTChiller(ChillNum)%Base%EvapVolFlowRate = tmpEvapVolFlowRate
      ELSE
        tmpEvapVolFlowRate = 0.d0
        IF (PlantSizesOkayToFinalize) GTChiller(ChillNum)%Base%EvapVolFlowRate = tmpEvapVolFlowRate
      END IF
      IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:CombustionTurbine', GTChiller(ChillNum)%Base%Name, &
                              'Design Chilled Water Flow Rate [m3/s]', &
                              GTChiller(ChillNum)%Base%EvapVolFlowRate)
    ELSE
      CALL ShowSevereError('Autosizing of Gas Turbine Chiller evap flow rate requires a loop Sizing:Plant object')
      CALL ShowContinueError('Occurs in Gas Turbine Chiller object='//TRIM(GTChiller(ChillNum)%Base%Name))
      ErrorsFound = .TRUE.
    END IF
  END IF
  CALL RegisterPlantCompDesignFlow(GTChiller(ChillNum)%Base%EvapInletNodeNum,tmpEvapVolFlowRate)
  IF (GTChiller(ChillNum)%Base%CondVolFlowRate == AutoSize) THEN
    IF (PltSizCondNum > 0) THEN
      IF (PlantSizData(PltSizNum)%DesVolFlowRate >= SmallWaterVolFlow) THEN
        rho = GetDensityGlycol(PlantLoop(GTChiller(ChillNum)%Base%CDLoopNum)%FluidName,  &
                                  GTChiller(ChillNum)%TempDesCondIn, &
                                  PlantLoop(GTChiller(ChillNum)%Base%CDLoopNum)%FluidIndex,&
                                  'SizeGTChiller')
        Cp = GetSpecificHeatGlycol(PlantLoop(GTChiller(ChillNum)%Base%CDLoopNum)%FluidName,  &
                                 GTChiller(ChillNum)%TempDesCondIn,                      &
                                 PlantLoop(GTChiller(ChillNum)%Base%CDLoopNum)%FluidIndex, &
                                 'SizeGTChiller')
        tmpCondVolFlowRate = tmpNomCap *  (1.0d0 + 1.0d0/GTChiller(ChillNum)%Base%COP) / &
                                ( PlantSizData(PltSizCondNum)%DeltaT * Cp * Rho)
        IF (PlantSizesOkayToFinalize) GTChiller(ChillNum)%Base%CondVolFlowRate = tmpCondVolFlowRate
      ELSE
        tmpCondVolFlowRate = 0.d0
        IF (PlantSizesOkayToFinalize) GTChiller(ChillNum)%Base%CondVolFlowRate = tmpCondVolFlowRate
      END IF
      IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:CombustionTurbine', GTChiller(ChillNum)%Base%Name, &
                              'Design Condenser Water Flow Rate [m3/s]', &
                              GTChiller(ChillNum)%Base%CondVolFlowRate)
    ELSE
      CALL ShowSevereError('Autosizing of Gas Turbine Chiller condenser flow rate requires a condenser')
      CALL ShowContinueError('loop Sizing:Plant object')
      CALL ShowContinueError('Occurs in Gas Turbine Chiller object='//TRIM(GTChiller(ChillNum)%Base%Name))
      ErrorsFound = .TRUE.
    END IF
  END IF
  ! save the design condenser water volumetric flow rate for use by the condenser water loop sizing algorithms
  IF (GTChiller(ChillNum)%Base%CondenserType == WaterCooled) &
    CALL RegisterPlantCompDesignFlow(GTChiller(ChillNum)%Base%CondInletNodeNum,tmpCondVolFlowRate)
  IF (GTChiller(ChillNum)%GTEngineCapacity  == AutoSize .and. PlantSizesOkayToFinalize ) THEN
    GTChiller(ChillNum)%GTEngineCapacity = GTChiller(ChillNum)%Base%NomCap * EngineEff &
                                                    / GTChiller(ChillNum)%Base%COP
  IF (PlantSizesOkayToFinalize) CALL ReportSizingOutput('Chiller:CombustionTurbine', GTChiller(ChillNum)%Base%Name, &
                            'Gas Turbine Engine Capacity [W]', GTChiller(ChillNum)%GTEngineCapacity)
  END IF
  IF (PlantSizesOkayToFinalize) Then
    !create predefined report
    equipName = GTChiller(ChillNum)%Base%Name
    CALL PreDefTableEntry(pdchMechType,equipName,'Chiller:CombustionTurbine')
    CALL PreDefTableEntry(pdchMechNomEff,equipName,GTChiller(ChillNum)%Base%COP)
    CALL PreDefTableEntry(pdchMechNomCap,equipName,GTChiller(ChillNum)%Base%NomCap)
  ENDIF
  IF (ErrorsFound) THEN
    CALL ShowFatalError('Preceding sizing errors cause program termination')
  END IF
  RETURN
END SUBROUTINE SizeGTChiller