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 | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | CompType | |||
character(len=*), | intent(in) | :: | CompName | |||
integer, | intent(in) | :: | CompTypeNum | |||
real(kind=r64), | intent(in) | :: | CoolCapVal | |||
real(kind=r64), | intent(in) | :: | SEERValueIP | |||
real(kind=r64), | intent(in) | :: | EERValueSI | |||
real(kind=r64), | intent(in) | :: | EERValueIP | |||
real(kind=r64), | intent(in) | :: | IEERValueIP | |||
real(kind=r64), | intent(in) | :: | HighHeatingCapVal | |||
real(kind=r64), | intent(in) | :: | LowHeatingCapVal | |||
real(kind=r64), | intent(in) | :: | HSPFValueIP | |||
integer, | intent(in) | :: | RegionNum |
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 ReportDXCoilRating(CompType,CompName,CompTypeNum, CoolCapVal,SEERValueIP,EERValueSI,EERValueIP, &
IEERValueIP,HighHeatingCapVal, LowHeatingCapVal, HSPFValueIP, RegionNum)
! SUBROUTINE INFORMATION:
! AUTHOR Bereket Nigusse, Chandan Sharma
! DATE WRITTEN February 2010
! MODIFIED May 2010 (Added EER and IEER entries)
! March 2012 (Added HSPF and High/Low Heating Capacity entries)
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine writes the standard rating (net) cooling capacity, SEER, EER and IEER values to
! the "eio" and tabular output files for Single Speed compressor DX Cooling Coils.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE DataPrecisionGlobals
USE DataGlobals, ONLY : OutputFileInits
USE General, ONLY: RoundSigDigits
USE OutputReportPredefined
USE DataHVACGlobals, ONLY: CoilDX_CoolingSingleSpeed, CoilDX_HeatingEmpirical, CoilDX_MultiSpeedCooling, &
CoilDX_MultiSpeedHeating
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=*), INTENT(IN) :: CompType ! Type of component
CHARACTER(len=*), INTENT(IN) :: CompName ! Name of component
INTEGER, INTENT(IN) :: CompTypeNum ! TypeNum of component
REAL(r64), INTENT(IN) :: SEERValueIP ! SEER value in IP units {Btu/W-h}
REAL(r64), INTENT(IN) :: CoolCapVal ! Standard total (net) cooling capacity for AHRI Std. 210/240 {W}
! or ANSI/AHRI Std. 340/360 {W}
REAL(r64), INTENT(IN) :: EERValueSI ! EER value in SI units {W/W}
REAL(r64), INTENT(IN) :: EERValueIP ! EER value in IP units {Btu/W-h}
REAL(r64), INTENT(IN) :: IEERValueIP ! IEER value in IP units {Btu/W-h}
REAL(r64), INTENT(IN) :: HighHeatingCapVal ! High Temperature Heating Standard (Net) Rating Capacity
! for AHRI Std. 210/240 {W}
REAL(r64), INTENT(IN) :: LowHeatingCapVal ! Low Temperature Heating Standard (Net) Rating Capacity
! for AHRI Std. 210/240 {W}
REAL(r64), INTENT(IN) :: HSPFValueIP ! IEER value in IP units {Btu/W-h}
INTEGER, INTENT(IN) :: RegionNum ! Region Number for which HSPF is calculated
! SUBROUTINE PARAMETER DEFINITIONS:
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
LOGICAL, SAVE :: MyCoolOneTimeFlag = .TRUE.
LOGICAL, SAVE :: MyHeatOneTimeFlag = .TRUE.
SELECT CASE(CompTypeNum)
CASE (CoilDX_CoolingSingleSpeed)
IF (MyCoolOneTimeFlag) THEN
WRITE(OutputFileInits, 990)
MyCoolOneTimeFlag = .FALSE.
END IF
WRITE (OutputFileInits, 991) TRIM(CompType), TRIM(CompName),TRIM(RoundSigDigits(CoolCapVal,1)), &
TRIM(RoundSigDigits(EERValueSI,2)),TRIM(RoundSigDigits(EERValueIP,2)), &
TRIM(RoundSigDigits(SEERValueIP,2)), TRIM(RoundSigDigits(IEERValueIP,2))
CALL PreDefTableEntry(pdchDXCoolCoilType, TRIM(CompName),TRIM(CompType))
CALL PreDefTableEntry(pdchDXCoolCoilNetCapSI,TRIM(CompName),CoolCapVal,1)
CALL PreDefTableEntry(pdchDXCoolCoilCOP, TRIM(CompName),TRIM(RoundSigDigits(EERValueSI,2)))
CALL PreDefTableEntry(pdchDXCoolCoilEERIP, TRIM(CompName),TRIM(RoundSigDigits(EERValueIP,2)))
CALL PreDefTableEntry(pdchDXCoolCoilSEERIP, TRIM(CompName),TRIM(RoundSigDigits(SEERValueIP,2)))
CALL PreDefTableEntry(pdchDXCoolCoilIEERIP, TRIM(CompName),TRIM(RoundSigDigits(IEERValueIP,2)))
CALL addFootNoteSubTable(pdstDXCoolCoil, 'ANSI/AHRI ratings account for supply air fan heat and electric power.')
990 FORMAT('! <DX Cooling Coil Standard Rating Information>, Component Type, Component Name, ', &
'Standard Rating (Net) Cooling Capacity {W}, ', 'Standard Rated Net COP {W/W}, ', &
'EER {Btu/W-h}, ', 'SEER {Btu/W-h}, ', 'IEER {Btu/W-h}')
991 FORMAT(' DX Cooling Coil Standard Rating Information, ',A,', ',A,', ',A,', ',A,', ',A,', ',A,', ',A)
CASE (CoilDX_HeatingEmpirical, CoilDX_MultiSpeedHeating)
IF (MyHeatOneTimeFlag) THEN
WRITE(OutputFileInits, 992)
MyHeatOneTimeFlag = .FALSE.
END IF
WRITE (OutputFileInits, 993) TRIM(CompType), TRIM(CompName), TRIM(RoundSigDigits(HighHeatingCapVal,1)), &
TRIM(RoundSigDigits(LowHeatingCapVal,1)), &
TRIM(RoundSigDigits(HSPFValueIP,2)), &
TRIM(RoundSigDigits(RegionNum))
CALL PreDefTableEntry(pdchDXHeatCoilType,TRIM(CompName),TRIM(CompType))
CALL PreDefTableEntry(pdchDXHeatCoilHighCap,TRIM(CompName),HighHeatingCapVal,1)
CALL PreDefTableEntry(pdchDXHeatCoilLowCap,TRIM(CompName),LowHeatingCapVal,1)
CALL PreDefTableEntry(pdchDXHeatCoilHSPFIP,TRIM(CompName),TRIM(RoundSigDigits(HSPFValueIP,2)))
CALL PreDefTableEntry(pdchDXHeatCoilRegionNum,TRIM(CompName),TRIM(RoundSigDigits(RegionNum)))
CALL addFootNoteSubTable(pdstDXHeatCoil, 'ANSI/AHRI ratings account for supply air fan heat and electric power.')
992 FORMAT('! <DX Heating Coil Standard Rating Information>, Component Type, Component Name, ', &
'High Temperature Heating (net) Rating Capacity {W}, ', 'Low Temperature Heating (net) Rating Capacity {W}, ', &
'HSPF {Btu/W-h}, ', 'Region Number')
993 FORMAT(' DX Heating Coil Standard Rating Information, ',A,', ',A,', ',A,', ',A,', ',A,', ',A)
CASE (CoilDX_MultiSpeedCooling)
IF (MyCoolOneTimeFlag) THEN
WRITE(OutputFileInits, 994)
MyCoolOneTimeFlag = .FALSE.
END IF
WRITE (OutputFileInits, 995) TRIM(CompType), TRIM(CompName),TRIM(RoundSigDigits(CoolCapVal,1)), &
' ', ' ', TRIM(RoundSigDigits(SEERValueIP,2)), ' '
CALL PreDefTableEntry(pdchDXCoolCoilType,TRIM(CompName),TRIM(CompType))
CALL PreDefTableEntry(pdchDXCoolCoilNetCapSI,TRIM(CompName),CoolCapVal,1)
CALL PreDefTableEntry(pdchDXCoolCoilSEERIP,TRIM(CompName),TRIM(RoundSigDigits(SEERValueIP,2)))
CALL addFootNoteSubTable(pdstDXCoolCoil, 'ANSI/AHRI ratings account for supply air fan heat and electric power.')
994 FORMAT('! <DX Cooling Coil Standard Rating Information>, Component Type, Component Name, ', &
'Standard Rating (Net) Cooling Capacity {W}, ', 'Standard Rated Net COP {W/W}, ', &
'EER {Btu/W-h}, ', 'SEER {Btu/W-h}, ', 'IEER {Btu/W-h}')
995 FORMAT(' DX Cooling Coil Standard Rating Information, ',A,', ',A,', ',A,', ',A,', ',A,', ',A,', ',A)
CASE DEFAULT
END SELECT
RETURN
END SUBROUTINE ReportDXCoilRating