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 | ||
|---|---|---|---|---|---|---|
| logical, | intent(in) | :: | Derate | |||
| integer, | intent(in) | :: | SystemSourceType | |||
| integer, | intent(in) | :: | SystemID | |||
| real(kind=r64), | intent(in) | :: | InitialTotalLoad | |||
| real(kind=r64), | intent(in) | :: | AvailableTotalLoad | 
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 FinalRateCoils(Derate,SystemSourceType,SystemID,InitialTotalLoad,AvailableTotalLoad)!or unmet load and available load?
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Therese Stovall, ORNL
          !       DATE WRITTEN   January 2011
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! When compressor system, or secondary loop capacity is insufficient to meet coil loads
          !   Come back here and derate the coil case credits to show unmet load impact
          !   Note that the coil fan, heater, and defrost would be unaffected because they
          !   would still be running at level calculated previously
          ! METHODOLOGY EMPLOYED:
          ! USE STATEMENTS:
  USE CurveManager, ONLY: CurveValue
  USE DataLoopNode
  USE Psychrometrics,    ONLY: PsyRhoAirFnPbTdbW,RhoH2O,PsyWFnTdbTwbPb,PsyTwbFnTdbWPb,CPHW,&
                               PsyHFnTdbW,PsyTsatFnHPb, PsyWFnTdpPb,PsyHFnTdbRhPb, PsyRhFnTdbWPb, &
                               PsyTdpFnWPb, PsyWFnTdbH
  USE General,         ONLY:   CreateSysTimeIntervalString
  IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  LOGICAL, INTENT(IN)     :: Derate              !True if compressor rack or secondary ht exchanger unable to provide capacity
  INTEGER, INTENT(IN)     :: SystemSourceType    !Secondarysystem or DetailedSystem
  INTEGER, INTENT(IN)     :: SystemID            !ID for Secondary loop or detailed system calling for derate
  REAL(r64), INTENT(IN)   :: InitialTotalLoad    !Load on system or secondary loop as initially calculated [W]
  REAL(r64), INTENT(IN)   :: AvailableTotalLoad  !Load that system or secondary loop is able to serve [W]
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER      :: NumCoils             =0   ! Number of coils on this system or secondary loop
INTEGER      :: CoilID               =0   ! Index to coil
INTEGER      :: CoilIndex            =0   ! rank of coils within system
REAL(r64)    :: DeRateFactor         =0.0d0 ! Ratio of energy available from system or secondary loop
REAL(r64)    :: InitLatCreditEnergy  =0.0d0 ! Latent credit energy before derate [W]
REAL(r64)    :: InitKgFrost          =0.0d0 ! Initial amount of frost on coils based on latent load before derate [kg]
REAL(r64)    :: FrostReduction       =0.0d0 ! Change in frost on coils based on derated latent load [kg]
SELECT CASE (SystemSourceType)
CASE (DetailedSystem)
    NumCoils = System(SystemID)%NumCoils
CASE (SecondarySystem)
    NumCoils = Secondary(SystemID)%NumCoils
END SELECT !DeRateCoils
IF(DeRate) THEN
  CALL ShowRecurringWarningErrorAtEnd('Refrigeration:System chilling WarehouseCoils '// &
        TRIM(System(SystemID)%Name) // &
        ' - Refrigeration system unable to meet load of warehouse coils chilled by system ... continues by derating coil load',&
        System(SystemID)%InsuffCapWarn)
  DeRateFactor = AvailableTotalLoad/InitialTotalLoad
  DO CoilIndex = 1,NumCoils
    CoilID = System(SystemID)%CoilNum(CoilIndex)
    !need to adjust ice on coil due to reduction in latent load met by coil
    InitLatCreditEnergy = WarehouseCoil(CoilID)%LatCreditEnergy
    InitKgFrost         = WarehouseCoil(CoilID)%KgFrost
    WarehouseCoil(CoilID)%TotalCoolingLoad         = DeRateFactor * WarehouseCoil(CoilID)%TotalCoolingLoad
    WarehouseCoil(CoilID)%TotalCoolingEnergy       = DeRateFactor * WarehouseCoil(CoilID)%TotalCoolingEnergy
    WarehouseCoil(CoilID)%SensCoolingEnergyRate    = DeRateFactor * WarehouseCoil(CoilID)%SensCoolingEnergyRate
    WarehouseCoil(CoilID)%SensCoolingEnergy        = DeRateFactor * WarehouseCoil(CoilID)%SensCoolingEnergy
    WarehouseCoil(CoilID)%LatCreditRate            = DeRateFactor * WarehouseCoil(CoilID)%LatCreditRate
    WarehouseCoil(CoilID)%LatCreditEnergy          = DeRateFactor * WarehouseCoil(CoilID)%LatCreditEnergy
    WarehouseCoil(CoilID)%LatKgPerS_ToZone         = DeRateFactor * WarehouseCoil(CoilID)%LatKgPerS_ToZone
    WarehouseCoil(CoilID)%SensCreditRate           = WarehouseCoil(CoilID)%SensCoolingEnergyRate -   &
                             WarehouseCoil(CoilID)%ElecFanPower - WarehouseCoil(CoilID)%ElecHeaterPower -   &
                             WarehouseCoil(CoilID)%ThermalDefrostPower
    WarehouseCoil(CoilID)%SensCreditEnergy         = WarehouseCoil(CoilID)%SensCreditRate * TimeStepSys * SecInHour
    FrostReduction = (InitLatCreditEnergy - WarehouseCoil(CoilID)%LatCreditEnergy)/IcetoVaporEnthalpy
    WarehouseCoil(CoilID)%KgFrost = Max(0.d0,(WarehouseCoil(CoilID)%KgFrost - FrostReduction))
    IF(WarehouseCoil(CoilID)%SensCreditRate >= 0.d0) THEN
      WarehouseCoil(CoilID)%ReportSensCoolCreditRate = WarehouseCoil(CoilID)%SensCreditRate
      WarehouseCoil(CoilID)%ReportHeatingCreditRate = 0.d0
    ELSE
      WarehouseCoil(CoilID)%ReportSensCoolCreditRate = 0.d0
      WarehouseCoil(CoilID)%ReportHeatingCreditRate = - WarehouseCoil(CoilID)%SensCreditRate
    END IF
    WarehouseCoil(CoilID)%ReportSensCoolCreditEnergy = WarehouseCoil(CoilID)%ReportSensCoolCreditRate * &
                                                      TimeStepSys * SecInHour
    WarehouseCoil(CoilID)%ReportHeatingCreditEnergy = WarehouseCoil(CoilID)%ReportHeatingCreditRate * &
                                                      TimeStepSys * SecInHour
    WarehouseCoil(CoilID)%ReportTotalCoolCreditRate = WarehouseCoil(CoilID)%ReportSensCoolCreditRate + &
                                                      WarehouseCoil(CoilID)%LatCreditRate
    WarehouseCoil(CoilID)%ReportTotalCoolCreditEnergy = WarehouseCoil(CoilID)%ReportSensCoolCreditEnergy + &
                                                      WarehouseCoil(CoilID)%LatCreditEnergy
  END DO
END IF !Derate logical true
RETURN
END SUBROUTINE FinalRateCoils