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 | :: | BaseboardNum | ||||
| real(kind=r64), | intent(out) | :: | LoadMet | 
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 CalcSteamBaseboard(BaseboardNum, LoadMet)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Daeho Kang
          !       DATE WRITTEN   September 2009
          !       MODIFIED       Sep 2011 LKL/BG - resimulate only zones needing it for Radiant systems
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine calculates both the convective and radiant heat transfer rate
          ! of steam baseboard heaters. The heater is assumed to be crossflow with
          ! both fluids unmixed. The air flow is bouyancy driven and a constant airflow.
          ! METHODOLOGY EMPLOYED:
          ! Equations that calculates heating capacity of steam coils and outlet air and water temperatures
          ! of the zone control steam coil in steam coil module in EnergyPlus are employed.
          ! REFERENCES:
          ! USE STATEMENTS:
    USE ScheduleManager,       ONLY: GetCurrentScheduleValue
    USE DataZoneEnergyDemands, ONLY: ZoneSysEnergyDemand, CurDeadbandOrSetback
    USE FluidProperties,       ONLY: GetSatEnthalpyRefrig, GetSatDensityRefrig, GetSatSpecificHeatRefrig
    USE DataInterfaces, ONLY: CalcHeatBalanceOutsideSurf, CalcHeatBalanceInsideSurf
    USE DataHVACGlobals, ONLY: SmallLoad
    USE DataBranchAirLoopPlant, ONLY : MassFlowTolerance
    IMPLICIT NONE
          ! SUBROUTINE ARGUMENT DEFINITIONS:
    INTEGER                :: BaseboardNum
    REAL(r64), INTENT(OUT) :: LoadMet
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! INTERFACE BLOCK SPECIFICATIONS
          ! na
          ! DERIVED TYPE DEFINITIONS
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
    INTEGER   :: ZoneNum
    REAL(r64) :: RadHeat
    REAL(r64) :: SteamBBHeat
    REAL(r64) :: SteamInletTemp
    REAL(r64) :: SteamOutletTemp
    REAL(r64) :: SteamMassFlowRate
    REAL(r64) :: SubCoolDeltaT
    REAL(r64) :: QZnReq
    REAL(r64) :: EnthSteamInDry
    REAL(r64) :: EnthSteamOutWet
    REAL(r64) :: LatentHeatSteam
    REAL(r64) :: Cp
    ZoneNum = SteamBaseboard(BaseboardNum)%ZonePtr
    QZnReq  = ZoneSysEnergyDemand(ZoneNum)%RemainingOutputReqToHeatSP
    SteamInletTemp    = Node(SteamBaseboard(BaseboardNum)%SteamInletNode)%Temp
    SteamOutletTemp = SteamInletTemp
    SteamMassFlowRate = Node(SteamBaseboard(BaseboardNum)%SteamInletNode)%MassFlowRate
    SubCoolDeltaT     = SteamBaseboard(BaseboardNum)%DegOfSubCooling
    IF (QZnReq > SmallLoad &
        .AND. .NOT. CurDeadbandOrSetback(ZoneNum) &
        .AND. SteamMassFlowRate > 0.0d0 &
        .AND. GetCurrentScheduleValue(SteamBaseboard(BaseboardNum)%SchedPtr) > 0) THEN
       ! Unit is on
      EnthSteamInDry  = GetSatEnthalpyRefrig('STEAM',SteamInletTemp,1.0d0, &
                        SteamBaseboard(BaseboardNum)%FluidIndex,'CalcSteamBaseboard')
      EnthSteamOutWet = GetSatEnthalpyRefrig('STEAM',SteamInletTemp,0.0d0, &
                        SteamBaseboard(BaseboardNum)%FluidIndex,'CalcSteamBaseboard')
      LatentHeatSteam = EnthSteamInDry-EnthSteamOutWet
      Cp = GetSatSpecificHeatRefrig('STEAM',SteamInletTemp,0.0d0,SteamBaseboard(BaseboardNum)%FluidIndex, &
                                    'CalcSteamBaseboard')
      SteamBBHeat = SteamMassFlowRate*(LatentHeatSteam+SubCoolDeltaT*Cp) ! Baseboard heating rate
      SteamOutletTemp = SteamInletTemp - SubCoolDeltaT ! Outlet temperature of steam
        ! Estimate radiant heat addition
      RadHeat = SteamBBHeat * SteamBaseboard(BaseboardNum)%FracRadiant ! Radiant heating rate
      QBBSteamRadSource(BaseboardNum) = RadHeat ! Radiant heat source which will be distributed to surfaces and people
       ! Now, distribute the radiant energy of all systems to the appropriate surfaces, to people, and the air
      CALL DistributeBBSteamRadGains
       ! Now "simulate" the system by recalculating the heat balances
      CALL CalcHeatBalanceOutsideSurf(ZoneNum)
      CALL CalcHeatBalanceInsideSurf(ZoneNum)
        ! Here an assumption is made regarding radiant heat transfer to people.
        ! While the radiant heat transfer to people array will be used by the thermal comfort
        ! routines, the energy transfer to people would get lost from the perspective
        ! of the heat balance.  So, to avoid this net loss of energy which clearly
        ! gets added to the zones, we must account for it somehow.  This assumption
        ! that all energy radiated to people is converted to convective energy is
        ! not very precise, but at least it conserves energy. The system impact to heat balance
        ! should include this.
        ! Actual system load that the unit should meet
      LoadMet = (SumHATsurf(ZoneNum) - ZeroSourceSumHATsurf(ZoneNum)) &
                + (SteamBBHeat * SteamBaseboard(BaseboardNum)%FracConvect) &
                + (RadHeat * SteamBaseboard(BaseboardNum)%FracDistribPerson)
      SteamBaseboard(BaseboardNum)%SteamOutletEnthalpy = SteamBaseboard(BaseboardNum)%SteamInletEnthalpy &
                                                          - SteamBBHeat / SteamMassFlowRate
      SteamBaseboard(BaseboardNum)%SteamOutletQuality  = 0.0d0
    ELSE
      SteamOutletTemp   = SteamInletTemp
      SteamBBHeat       = 0.0d0
      LoadMet           = 0.0d0
      RadHeat           = 0.0d0
      SteamMassFlowRate = 0.0d0
      QBBSteamRadSource(BaseboardNum) = 0.0d0
      SteamBaseboard(BaseboardNum)%SteamOutletQuality  = 0.0d0
      SteamBaseboard(BaseboardNum)%SteamOutletEnthalpy = SteamBaseboard(BaseboardNum)%SteamInletEnthalpy
    END IF
    SteamBaseboard(BaseboardNum)%SteamOutletTemp     = SteamOutletTemp
    SteamBaseboard(BaseboardNum)%SteamMassFlowRate   = SteamMassFlowRate
    SteamBaseboard(BaseboardNum)%SteamOutletEnthalpy = SteamBaseboard(BaseboardNum)%SteamOutletEnthalpy
    SteamBaseboard(BaseboardNum)%SteamOutletQuality  = SteamBaseboard(BaseboardNum)%SteamOutletQuality
    SteamBaseboard(BaseboardNum)%TotPower            = LoadMet
    SteamBaseboard(BaseboardNum)%Power               = SteamBBHeat
    SteamBaseboard(BaseboardNum)%ConvPower           = SteamBBHeat - RadHeat
    SteamBaseboard(BaseboardNum)%RadPower            = RadHeat
    RETURN
  END SUBROUTINE CalcSteamBaseboard