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) | :: | DXCoilNum | 
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 ReportDXCoil(DXCoilNum)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Fred Buhl
          !       DATE WRITTEN   May 2000
          !       MODIFIED       Richard Raustad/Don Shirey Oct 2001, Feb 2004
          !                      Feb 2005 M. J. Witte, GARD Analytics, Inc.
          !                        Always update evap value to support new coil type COIL:DX:MultiMode:CoolingEmpirical:
          !                      Lixing Gu. Jan. 5, 2007, pass information to the AirflowNetwork model
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! Fills some of the report variables for the DX coils
          ! METHODOLOGY EMPLOYED:
          ! na
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE DataHVACGlobals, ONLY: TimeStepSys, DXElecCoolingPower, DXElecHeatingPower
  USE Psychrometrics,  ONLY: RhoH2O
  USE DataWater,       ONLY: WaterStorage
  USE DataAirLoop,     ONLY: LoopDXCoilRTF
  IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  INTEGER, INTENT (IN) :: DXCoilNum ! number of the current fan coil unit being simulated
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: rhoWater
REAL(r64) :: Tavg
REAL(r64) :: SpecHumOut
REAL(r64) :: SpecHumIn
REAL(r64) :: ReportingConstant ! Number of seconds per HVAC system time step, to convert from W (J/s) to J
ReportingConstant = TimeStepSys*SecInHour
SELECT CASE(DXCoil(DXCoilNum)%DXCoilType_Num)
CASE (CoilDX_HeatingEmpirical,CoilVRF_Heating)
  DXCoil(DXCoilNum)%TotalHeatingEnergy = DXCoil(DXCoilNum)%TotalHeatingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%ElecHeatingConsumption = DXCoil(DXCoilNum)%ElecHeatingPower*ReportingConstant
  DXCoil(DXCoilNum)%DefrostConsumption = DXCoil(DXCoilNum)%DefrostPower*ReportingConstant
  DXCoil(DXCoilNum)%CrankcaseHeaterConsumption = DXCoil(DXCoilNum)%CrankcaseHeaterPower*ReportingConstant
  DXElecHeatingPower = DXCoil(DXCoilNum)%ElecHeatingPower + DXCoil(DXCoilNum)%CrankcaseHeaterPower
CASE (CoilDX_MultiSpeedHeating)
  DXCoil(DXCoilNum)%TotalHeatingEnergy = DXCoil(DXCoilNum)%TotalHeatingEnergyRate*ReportingConstant
  If (DXCoil(DXCoilNum)%FuelType .EQ. FuelTypeElectricity) Then
    DXCoil(DXCoilNum)%ElecHeatingConsumption = DXCoil(DXCoilNum)%ElecHeatingPower*ReportingConstant
  Else
    DXCoil(DXCoilNum)%FuelConsumed = DXCoil(DXCoilNum)%FuelUsed*ReportingConstant
  End If
  DXCoil(DXCoilNum)%DefrostConsumption = DXCoil(DXCoilNum)%DefrostPower*ReportingConstant
  DXCoil(DXCoilNum)%CrankcaseHeaterConsumption = DXCoil(DXCoilNum)%CrankcaseHeaterPower*ReportingConstant
  DXElecHeatingPower = DXCoil(DXCoilNum)%ElecHeatingPower + DXCoil(DXCoilNum)%CrankcaseHeaterPower
CASE (CoilDX_MultiSpeedCooling)
  DXCoil(DXCoilNum)%TotalCoolingEnergy = DXCoil(DXCoilNum)%TotalCoolingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%SensCoolingEnergy = DXCoil(DXCoilNum)%SensCoolingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%LatCoolingEnergy = DXCoil(DXCoilNum)%TotalCoolingEnergy - DXCoil(DXCoilNum)%SensCoolingEnergy
  DXCoil(DXCoilNum)%CrankcaseHeaterConsumption = DXCoil(DXCoilNum)%CrankcaseHeaterPower*ReportingConstant
  DXElecCoolingPower = DXCoil(DXCoilNum)%ElecCoolingPower
  DXCoil(DXCoilNum)%EvapCondPumpElecConsumption = DXCoil(DXCoilNum)%EvapCondPumpElecPower*ReportingConstant
  DXCoil(DXCoilNum)%EvapWaterConsump = DXCoil(DXCoilNum)%EvapWaterConsumpRate*ReportingConstant
  If (DXCoil(DXCoilNum)%FuelType .EQ. FuelTypeElectricity) Then
    DXCoil(DXCoilNum)%ElecCoolingConsumption = DXCoil(DXCoilNum)%ElecCoolingPower*ReportingConstant
  Else
    DXCoil(DXCoilNum)%FuelConsumed = DXCoil(DXCoilNum)%FuelUsed*ReportingConstant
  End If
  If (ANY(DXCoil(DXCoilNum)%CondenserType == EvapCooled)) THEN
    DXCoil(DXCoilNum)%BasinHeaterConsumption = DXCoil(DXCoilNum)%BasinHeaterPower*ReportingConstant
  Endif
CASE (CoilDX_HeatPumpWaterHeater)
! water heating energy for HP water heater DX Coil condenser
  DXCoil(DXCoilNum)%TotalHeatingEnergy = DXCoil(DXCoilNum)%TotalHeatingEnergyRate*ReportingConstant
! water heating power for HP water heater
  DXCoil(DXCoilNum)%ElecWaterHeatingConsumption = DXCoil(DXCoilNum)%ElecWaterHeatingPower*ReportingConstant
! other usual DX cooling coil outputs
  DXCoil(DXCoilNum)%TotalCoolingEnergy = DXCoil(DXCoilNum)%TotalCoolingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%SensCoolingEnergy = DXCoil(DXCoilNum)%SensCoolingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%LatCoolingEnergy = DXCoil(DXCoilNum)%TotalCoolingEnergy - DXCoil(DXCoilNum)%SensCoolingEnergy
  DXCoil(DXCoilNum)%ElecCoolingConsumption = DXCoil(DXCoilNum)%ElecCoolingPower*ReportingConstant
  DXCoil(DXCoilNum)%CrankcaseHeaterConsumption = DXCoil(DXCoilNum)%CrankcaseHeaterPower*ReportingConstant
! DXElecCoolingPower global is only used for air-to-air cooling and heating coils
  DXElecCoolingPower = 0.0d0
CASE DEFAULT
  DXCoil(DXCoilNum)%TotalCoolingEnergy = DXCoil(DXCoilNum)%TotalCoolingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%SensCoolingEnergy = DXCoil(DXCoilNum)%SensCoolingEnergyRate*ReportingConstant
  DXCoil(DXCoilNum)%LatCoolingEnergy = DXCoil(DXCoilNum)%TotalCoolingEnergy - DXCoil(DXCoilNum)%SensCoolingEnergy
  DXCoil(DXCoilNum)%ElecCoolingConsumption = DXCoil(DXCoilNum)%ElecCoolingPower*ReportingConstant
  DXCoil(DXCoilNum)%CrankcaseHeaterConsumption = DXCoil(DXCoilNum)%CrankcaseHeaterPower*ReportingConstant
  DXElecCoolingPower = DXCoil(DXCoilNum)%ElecCoolingPower
  DXCoil(DXCoilNum)%EvapCondPumpElecConsumption = DXCoil(DXCoilNum)%EvapCondPumpElecPower*ReportingConstant
  DXCoil(DXCoilNum)%EvapWaterConsump = DXCoil(DXCoilNum)%EvapWaterConsumpRate*ReportingConstant
  If (ANY(DXCoil(DXCoilNum)%CondenserType == EvapCooled)) THEN
    DXCoil(DXCoilNum)%BasinHeaterConsumption = DXCoil(DXCoilNum)%BasinHeaterPower*ReportingConstant
  Endif
END SELECT
IF (DXCoil(DXCoilNum)%CondensateCollectMode == CondensateToTank) THEN
  ! calculate and report condensation rates  (how much water extracted from the air stream)
  ! water flow of water in m3/s for water system interactions
  !  put here to catch all types of DX coils
  Tavg =( DXCoil(DXCoilNum)%InletAirTemp - DXCoil(DXCoilNum)%OutletAirTemp)/2.0d0
  rhoWater = RhoH2O(Tavg)
! CR9155 Remove specific humidity calculations
  SpecHumIn = DXCoil(DXCoilNum)%InletAirHumRat
  SpecHumOut = DXCoil(DXCoilNum)%OutletAirHumRat
  !  mdot * del HumRat / rho water
  DXCoil(DXCoilNum)%CondensateVdot = MAX(0.0d0, (DXCoil(DXCoilNum)%InletAirMassFlowRate *   &
            (SpecHumIn - SpecHumOut) / rhoWater) )
  DXCoil(DXCoilNum)%CondensateVol  = DXCoil(DXCoilNum)%CondensateVdot *ReportingConstant
  WaterStorage(DXCoil(DXCoilNum)%CondensateTankID)%VdotAvailSupply(DXCoil(DXCoilNum)%CondensateTankSupplyARRID) &
      =  DXCoil(DXCoilNum)%CondensateVdot
  WaterStorage(DXCoil(DXCoilNum)%CondensateTankID)%TwaterSupply(DXCoil(DXCoilNum)%CondensateTankSupplyARRID) &
      =  DXCoil(DXCoilNum)%OutletAirTemp
ENDIF
LoopDXCoilRTF = MAX(DXCoil(DXCoilNum)%CoolingCoilRuntimeFraction,DXCoil(DXCoilNum)%HeatingCoilRuntimeFraction)
RETURN
END SUBROUTINE ReportDXCoil