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.
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 WriteDemandEndUseSummary
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer
! DATE WRITTEN January 2009
! MODIFIED January 2010, Kyle Benne
! Added SQLite output
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Take the gathered total and enduse meter data and structure
! the results into a tabular report for output.
! METHODOLOGY EMPLOYED:
! Create arrays for the call to writeTable and then call it.
! This report actually consists of many sub-tables each with
! its own call to writeTable.
! REFERENCES:
! na
! USE STATEMENTS:
USE OutputProcessor, ONLY: MaxNumSubcategories, EndUseCategory
USE DataWater , ONlY: WaterStorage
USE ManageElectricPower , ONLY: ElecStorage, NumElecStorageDevices
USE SQLiteProcedures, ONLY: CreateSQLiteTabularDataRecords
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, parameter :: colElectricity = 1
INTEGER, parameter :: colGas = 2
INTEGER, parameter :: colAdditionalFuel = 3
INTEGER, parameter :: colPurchCool = 4
INTEGER, parameter :: colPurchHeat = 5
INTEGER, parameter :: colWater = 6
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! all arrays are in the format: (row, column)
CHARACTER(len=MaxNameLength),ALLOCATABLE, DIMENSION(:) :: columnHead
INTEGER,ALLOCATABLE,DIMENSION(:) :: columnWidth
CHARACTER(len=MaxNameLength),ALLOCATABLE, DIMENSION(:) :: rowHead
CHARACTER(len=MaxNameLength),ALLOCATABLE, DIMENSION(:,:) :: tableBody
! all arrays are in the format: (row, columnm)
REAL(r64),DIMENSION(15,6) :: useVal
REAL(r64),DIMENSION(6) :: collapsedTotal
REAL(r64),DIMENSION(numEndUses,6) :: collapsedEndUse
INTEGER, DIMENSION(6) :: collapsedTimeStep
REAL(r64),DIMENSION(6,numEndUses,MaxNumSubcategories) :: collapsedEndUseSub
INTEGER :: iResource
INTEGER :: jEndUse
INTEGER :: kEndUseSub
INTEGER :: i
INTEGER :: numRows
CHARACTER(len=100) :: footnote = ''
REAL(r64) :: additionalFuelMax
INTEGER :: additionalFuelSelected
INTEGER :: additionalFuelNonZeroCount
INTEGER :: distrHeatSelected
LOGICAL :: bothDistrHeatNonZero
REAL(r64) :: powerConversion
REAL(r64) :: flowConversion
REAL(r64),DIMENSION(6) :: leedFansParkFromFan
REAL(r64),DIMENSION(6) :: leedFansParkFromExtFuelEquip
REAL(r64),DIMENSION(6) :: leedIntLightProc
REAL(r64),DIMENSION(6) :: leedCook
REAL(r64),DIMENSION(6) :: leedIndProc
REAL(r64),DIMENSION(6) :: leedElevEsc
REAL(r64) :: unconvert
CHARACTER(len=MaxNameLength) :: subCatName
IF (displayDemandEndUse) THEN
! show the headers of the report
CALL WriteReportHeaders('Demand End Use Components Summary','Entire Facility',isAverage)
! totals - select which additional fuel to display and which other district heating
collapsedTotal=0.0d0
collapsedTotal(1) = gatherDemandTotal(1) !electricity
collapsedTimeStep(1) = gatherDemandTimeStamp(1)
collapsedTotal(2) = gatherDemandTotal(2) !natural gas
collapsedTimeStep(2) = gatherDemandTimeStamp(2)
collapsedTotal(4) = gatherDemandTotal(3) !district cooling <- purchased cooling
collapsedTimeStep(4) = gatherDemandTimeStamp(3)
collapsedTotal(6) = gatherDemandTotal(7) !water
collapsedTimeStep(6) = gatherDemandTimeStamp(7)
! select which of the additional fuels should be displayed based on which has the highest
! demand. This is usually likely to be the only additional fuel that is actually being used.
! If an additional fuel is non-zero, a footnote to the table is added.
! First step is to see if any additional fuels are non-zero
additionalFuelNonZeroCount = 0
IF (gatherDemandTotal(6) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(8) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(9) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(10) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(11) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(12) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(13) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (gatherDemandTotal(14) .GT. 0.0d0) additionalFuelNonZeroCount = additionalFuelNonZeroCount + 1
IF (additionalFuelNonZeroCount .GT. 1) THEN
footnote = 'Additional fuels have non-zero demand but are not shown on this report.'
END IF
!assuming that at least one of these is non-zero
additionalFuelSelected = 12 !default is propane if no other given
additionalFuelMax = gatherDemandTotal(12)
IF (additionalFuelNonZeroCount .GT. 0) THEN
IF (gatherDemandTotal(6) .GT. additionalFuelMax) THEN ! gasoline
additionalFuelSelected = 6
additionalFuelMax = gatherDemandTotal(6)
END IF
IF (gatherDemandTotal(8) .GT. additionalFuelMax) THEN ! diesel
additionalFuelSelected = 8
additionalFuelMax = gatherDemandTotal(8)
END IF
IF (gatherDemandTotal(9) .GT. additionalFuelMax) THEN ! coal
additionalFuelSelected = 9
additionalFuelMax = gatherDemandTotal(9)
END IF
IF (gatherDemandTotal(10) .GT. additionalFuelMax) THEN ! fuel oil #1
additionalFuelSelected = 10
additionalFuelMax = gatherDemandTotal(10)
END IF
IF (gatherDemandTotal(11) .GT. additionalFuelMax) THEN ! fuel oil #2
additionalFuelSelected = 11
additionalFuelMax = gatherDemandTotal(11)
END IF
IF (gatherDemandTotal(12) .GT. additionalFuelMax) THEN ! propane
additionalFuelSelected = 12
additionalFuelMax = gatherDemandTotal(12)
END IF
IF (gatherDemandTotal(13) .GT. additionalFuelMax) THEN ! otherfuel1
additionalFuelSelected = 13
additionalFuelMax = gatherDemandTotal(13)
END IF
IF (gatherDemandTotal(14) .GT. additionalFuelMax) THEN ! otherfuel2
additionalFuelSelected = 14
additionalFuelMax = gatherDemandTotal(14)
END IF
END IF
!set the time of peak demand and total demand for the additinoal fuel selected
collapsedTimeStep(3) = gatherDemandTimeStamp(additionalFuelSelected)
collapsedTotal(3) = gatherDemandTotal(additionalFuelSelected)
!set flag if both puchased heating and steam both have positive demand
bothDistrHeatNonZero = (gatherDemandTotal(4) .GT. 0.0d0) .AND. (gatherDemandTotal(5) .GT. 0.0d0)
!select the district heating source that has a larger demand
IF (gatherDemandTotal(4) .GT. gatherDemandTotal(5)) THEN
distrHeatSelected = 4 ! purchased heating
IF (bothDistrHeatNonZero) THEN
footnote = TRIM(footnote) // ' Steam has non-zero demand but is not shown on this report.'
END IF
ELSE
distrHeatSelected = 5 ! steam
IF (bothDistrHeatNonZero) THEN
footnote = TRIM(footnote) // ' District heating has non-zero demand but is not shown on this report.'
END IF
END IF
!set the time of peak demand and total demand for the purchased heating/steam
collapsedTimeStep(5) = gatherDemandTimeStamp(distrHeatSelected)
collapsedTotal(5) = gatherDemandTotal(distrHeatSelected)
!establish unit conversion factors
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
powerConversion = getSpecificUnitMultiplier('W','kBtuh')
flowConversion = getSpecificUnitMultiplier('m3/s','gal/min')
ELSE
powerConversion = 1.0d0
flowConversion = 1.0d0
END IF
! collapse the gatherEndUseBEPS array to the resource groups displayed
collapsedEndUse=0.0d0
DO jEndUse=1,numEndUses
collapsedEndUse(jEndUse,1) = gatherDemandEndUse(jEndUse,1) * powerConversion !electricity
collapsedEndUse(jEndUse,2) = gatherDemandEndUse(jEndUse,2) * powerConversion !natural gas
collapsedEndUse(jEndUse,3) = gatherDemandEndUse(jEndUse,additionalFuelSelected) * powerConversion !additional fuel
collapsedEndUse(jEndUse,4) = gatherDemandEndUse(jEndUse,3) * powerConversion ! purchased cooling
collapsedEndUse(jEndUse,5) = gatherDemandEndUse(jEndUse,distrHeatSelected) * powerConversion !district heating
collapsedEndUse(jEndUse,6) = gatherDemandEndUse(jEndUse,7) * flowConversion !water
END DO
DO jEndUse=1,numEndUses
DO kEndUseSub = 1, EndUseCategory(jEndUse)%NumSubcategories
collapsedEndUseSub(1,jEndUse,kEndUseSub) = &
gatherDemandEndUseSub(1,jEndUse,kEndUseSub) * powerConversion !electricity
collapsedEndUseSub(2,jEndUse,kEndUseSub) = &
gatherDemandEndUseSub(2,jEndUse,kEndUseSub) * powerConversion !natural gas
collapsedEndUseSub(3,jEndUse,kEndUseSub) = &
gatherDemandEndUseSub(additionalFuelSelected,jEndUse,kEndUseSub) * powerConversion !additional fuel
collapsedEndUseSub(4,jEndUse,kEndUseSub) = &
gatherDemandEndUseSub(3,jEndUse,kEndUseSub) * powerConversion !purch cooling
collapsedEndUseSub(5,jEndUse,kEndUseSub) = &
gatherDemandEndUseSub(distrHeatSelected,jEndUse,kEndUseSub) * powerConversion !district heating
collapsedEndUseSub(6,jEndUse,kEndUseSub) = &
gatherDemandEndUseSub(7,jEndUse,kEndUseSub) * flowConversion !water
END DO
END DO
!convert totals
collapsedTotal(1) = collapsedTotal(1) * powerConversion !electricity
collapsedTotal(2) = collapsedTotal(2) * powerConversion !natural gas
collapsedTotal(3) = collapsedTotal(3) * powerConversion !additional fuel
collapsedTotal(4) = collapsedTotal(4) * powerConversion !purchased cooling
collapsedTotal(5) = collapsedTotal(5) * powerConversion !district heating
collapsedTotal(6) = collapsedTotal(6) * flowConversion !water
!
!---- End Use Sub-Table
!
ALLOCATE(rowHead(17))
ALLOCATE(columnHead(6))
ALLOCATE(columnWidth(6))
columnWidth = 14 !array assignment - same for all columns
ALLOCATE(tableBody(17,6))
DO iResource= 1,6
useVal(1,iResource) = collapsedEndUse(endUseHeating,iResource)
useVal(2,iResource) = collapsedEndUse(endUseCooling,iResource)
useVal(3,iResource) = collapsedEndUse(endUseInteriorLights,iResource)
useVal(4,iResource) = collapsedEndUse(endUseExteriorLights,iResource)
useVal(5,iResource) = collapsedEndUse(endUseInteriorEquipment,iResource)
useVal(6,iResource) = collapsedEndUse(endUseExteriorEquipment,iResource)
useVal(7,iResource) = collapsedEndUse(endUseFans,iResource)
useVal(8,iResource) = collapsedEndUse(endUsePumps,iResource)
useVal(9,iResource) = collapsedEndUse(endUseHeatRejection,iResource)
useVal(10,iResource) = collapsedEndUse(endUseHumidification,iResource)
useVal(11,iResource) = collapsedEndUse(endUseHeatRecovery,iResource)
useVal(12,iResource) = collapsedEndUse(endUseWaterSystem,iResource)
useVal(13,iResource) = collapsedEndUse(endUseRefrigeration,iResource)
useVal(14,iResource) = collapsedEndUse(endUseCogeneration,iResource)
useVal(15,iResource) = collapsedTotal(iResource) ! totals
END DO
rowHead(1) = 'Time of Peak'
rowHead(2) = 'Heating'
rowHead(3) = 'Cooling'
rowHead(4) = 'Interior Lighting'
rowHead(5) = 'Exterior Lighting'
rowHead(6) = 'Interior Equipment'
rowHead(7) = 'Exterior Equipment'
rowHead(8) = 'Fans'
rowHead(9) = 'Pumps'
rowHead(10) = 'Heat Rejection'
rowHead(11) = 'Humidification'
rowHead(12) = 'Heat Recovery'
rowHead(13) = 'Water Systems'
rowHead(14) = 'Refrigeration'
rowHead(15) = 'Generators'
rowHead(16) = ''
rowHead(17) = 'Total End Uses'
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
columnHead(1) = 'Electricity [kBtuh]'
columnHead(2) = 'Natural Gas [kBtuh]'
SELECT CASE (additionalFuelSelected)
CASE(6) ! gasoline
columnHead(3) = 'Gasoline [kBtuh]'
CASE(8) ! Diesel
columnHead(3) = 'Diesel [kBtuh]'
CASE(9) ! Coal
columnHead(3) = 'Coal [kBtuh]'
CASE(10) ! Fuel Oil #1
columnHead(3) = 'Fuel Oil #1 [kBtuh]'
CASE(11) ! Fuel Oil #2
columnHead(3) = 'Fuel Oil #2 [kBtuh]'
CASE(12) ! Propane
columnHead(3) = 'Propane [kBtuh]'
CASE(13) ! OtherFuel1
columnHead(3) = 'Other Fuel 1 [kBtuh]'
CASE(14) ! OtherFuel2
columnHead(3) = 'Other Fuel 2 [kBtuh]'
END SELECT
columnHead(4) = 'District Cooling [kBtuh]'
SELECT CASE (distrHeatSelected)
CASE (4)
columnHead(5) = 'District Heating [kBtuh]'
CASE (5)
columnHead(5) = 'Steam [kBtuh]'
END SELECT
columnHead(6) = 'Water [gal/min]'
ELSE
columnHead(1) = 'Electricity [W]'
columnHead(2) = 'Natural Gas [W]'
SELECT CASE (additionalFuelSelected)
CASE(6) ! gasoline
columnHead(3) = 'Gasoline [W]'
CASE(8) ! Diesel
columnHead(3) = 'Diesel [W]'
CASE(9) ! Coal
columnHead(3) = 'Coal [W]'
CASE(10) ! Fuel Oil #1
columnHead(3) = 'Fuel Oil #1 [W]'
CASE(11) ! Fuel Oil #2
columnHead(3) = 'Fuel Oil #2 [W]'
CASE(12) ! Propane
columnHead(3) = 'Propane [W]'
CASE(13) ! OtherFuel1
columnHead(3) = 'Other Fuel 1 [W]'
CASE(14) ! OtherFuel2
columnHead(3) = 'Other Fuel 2 [W]'
END SELECT
columnHead(4) = 'District Cooling [W]'
SELECT CASE (distrHeatSelected)
CASE (4)
columnHead(5) = 'District Heating [W]'
CASE (5)
columnHead(5) = 'Steam [W]'
END SELECT
columnHead(6) = 'Water [m3/s]'
END IF
tableBody = ''
DO iResource= 1,6
DO jEndUse=1,14
tableBody(1 + jEndUse,iResource) = TRIM(RealToStr(useVal(jEndUse,iResource),2))
END DO
tableBody(1,iResource) = TRIM(DateToString(collapsedTimeStep(iResource)))
tableBody(17,iResource) = TRIM(RealToStr(collapsedTotal(iResource),2))
END DO
!complete the LEED end use table using the same values
! for certain rows in the LEED table the subcategories are necessary so first compute those values
leedFansParkFromFan = 0.0d0
leedFansParkFromExtFuelEquip = 0.0d0
leedIntLightProc = 0.0d0
leedCook = 0.0d0
leedIndProc = 0.0d0
leedElevEsc = 0.0d0
DO iResource = 1, 5 ! don't bother with water
DO jEndUse = 1, NumEndUses
IF (EndUseCategory(jEndUse)%NumSubcategories > 0) THEN
DO kEndUseSub = 1, EndUseCategory(jEndUse)%NumSubcategories
subCatName = EndUseCategory(jEndUse)%SubcategoryName(kEndUseSub)
IF (SameString(subCatName,'Fans - Parking Garage')) THEN
IF (jEndUse .EQ. 7) THEN !fans
leedFansParkFromFan(iResource) = leedFansParkFromFan(iResource) + collapsedEndUseSub(iResource,jEndUse,kEndUseSub)
ELSE
leedFansParkFromExtFuelEquip(iResource) = leedFansParkFromExtFuelEquip(iResource) &
+ collapsedEndUseSub(iResource,jEndUse,kEndUseSub)
END IF
ELSEIF (SameString(subCatName,'Interior Lighting - Process')) THEN
leedIntLightProc(iResource) = leedIntLightProc(iResource) + collapsedEndUseSub(iResource,jEndUse,kEndUseSub)
ELSEIF (SameString(subCatName,'Cooking')) THEN
leedCook(iResource) = leedCook(iResource) + collapsedEndUseSub(iResource,jEndUse,kEndUseSub)
ELSEIF (SameString(subCatName,'Industrial Process')) THEN
leedIndProc(iResource) = leedIndProc(iResource) + collapsedEndUseSub(iResource,jEndUse,kEndUseSub)
ELSEIF (SameString(subCatName,'Elevators and Escalators')) THEN
leedElevEsc(iResource) = leedElevEsc(iResource) + collapsedEndUseSub(iResource,jEndUse,kEndUseSub)
END IF
END DO
END IF
END DO
END DO
!complete the LEED end use table using the same values
unconvert = 1/powerConversion
CALL PreDefTableEntry(pdchLeedPerfElDem,'Interior Lighting',unconvert * (useVal(3,colElectricity) &
- leedIntLightProc(colElectricity)),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Exterior Lighting',unconvert * useVal(4,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Space Heating',unconvert * useVal(1,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Space Cooling',unconvert * useVal(2,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Pumps',unconvert * useVal(8,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Heat Rejection',unconvert * useVal(9,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Fans-Interior',unconvert * (useVal(7,colElectricity) &
- leedFansParkFromFan(colElectricity)),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Fans-Parking Garage',unconvert * (leedFansParkFromFan(colElectricity) &
+ leedFansParkFromExtFuelEquip(colElectricity)),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Service Water Heating',unconvert * useVal(12,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Receptacle Equipment',unconvert * useVal(5,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Interior Lighting (process)',unconvert * leedIntLightProc(colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Refrigeration Equipment',unconvert * useVal(13,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Cooking',unconvert * leedCook(colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Industrial Process',unconvert * leedIndProc(colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfElDem,'Elevators and Escalators',unconvert * leedElevEsc(colElectricity),2)
!CALL PreDefTableEntry(pdchLeedPerfElDem,'Total',useVal(15,colElectricity),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Interior Lighting',unconvert * (useVal(3,colGas) - leedIntLightProc(colGas)),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Exterior Lighting',unconvert * useVal(4,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Space Heating',unconvert * useVal(1,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Space Cooling',unconvert * useVal(2,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Pumps',unconvert * useVal(8,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Heat Rejection',unconvert * useVal(9,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Fans-Interior',unconvert * (useVal(7,colGas)- leedFansParkFromFan(colGas)),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Fans-Parking Garage',unconvert * (leedFansParkFromFan(colGas) &
+ leedFansParkFromExtFuelEquip(colGas)),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Service Water Heating',unconvert * useVal(12,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Receptacle Equipment',unconvert * useVal(5,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Interior Lighting (process)',unconvert * leedIntLightProc(colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Refrigeration Equipment',unconvert * useVal(13,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Cooking',unconvert * leedCook(colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Industrial Process',unconvert * leedIndProc(colGas),2)
CALL PreDefTableEntry(pdchLeedPerfGasDem,'Elevators and Escalators',unconvert * leedElevEsc(colGas),2)
!CALL PreDefTableEntry(pdchLeedPerfGasDem,'Total',useVal(15,colGas),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Interior Lighting',unconvert * (useVal(3,colAdditionalFuel) + useVal(3,colPurchCool) &
+ useVal(3,colPurchHeat) - (leedIntLightProc(colAdditionalFuel) + leedIntLightProc(colPurchCool) &
+ leedIntLightProc(colPurchHeat))) ,2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Exterior Lighting',unconvert * (useVal(4,colAdditionalFuel) + useVal(4,colPurchCool) &
+ useVal(4,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Space Heating',unconvert * (useVal(1,colAdditionalFuel) + useVal(1,colPurchCool) &
+ useVal(1,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Space Cooling',unconvert * (useVal(2,colAdditionalFuel) + useVal(2,colPurchCool) &
+ useVal(2,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Pumps',unconvert * (useVal(8,colAdditionalFuel) + useVal(8,colPurchCool) &
+ useVal(8,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Heat Rejection',unconvert * (useVal(9,colAdditionalFuel) + useVal(9,colPurchCool) &
+ useVal(9,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Fans-Interior',unconvert * (useVal(7,colAdditionalFuel) + useVal(7,colPurchCool) &
+ useVal(7,colPurchHeat) - (leedFansParkFromFan(colAdditionalFuel) &
+ leedFansParkFromFan(colPurchCool) &
+ leedFansParkFromFan(colPurchHeat))),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Fans-Parking Garage',unconvert * (leedFansParkFromFan(colAdditionalFuel) &
+ leedFansParkFromFan(colPurchCool) + leedFansParkFromFan(colPurchHeat) &
+ leedFansParkFromExtFuelEquip(colAdditionalFuel) + leedFansParkFromExtFuelEquip(colPurchCool) &
+ leedFansParkFromExtFuelEquip(colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Service Water Heating',unconvert * (useVal(12,colAdditionalFuel) &
+ useVal(12,colPurchCool) + useVal(12,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Receptacle Equipment',unconvert * &
(useVal(5,colAdditionalFuel) + useVal(5,colPurchCool) &
+ useVal(5,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Interior Lighting (process)',unconvert * (leedIntLightProc(colAdditionalFuel) &
+ leedIntLightProc(colPurchCool) + leedIntLightProc(colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Refrigeration Equipment',unconvert * (useVal(13,colAdditionalFuel) &
+ useVal(13,colPurchCool) + useVal(13,colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Cooking',unconvert * (leedCook(colAdditionalFuel) + leedCook(colPurchCool) &
+ leedCook(colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Industrial Process',unconvert * (leedIndProc(colAdditionalFuel) &
+ leedIndProc(colPurchCool) + leedIndProc(colPurchHeat)),2)
CALL PreDefTableEntry(pdchLeedPerfOthDem,'Elevators and Escalators',unconvert * (leedElevEsc(colAdditionalFuel) &
+ leedElevEsc(colPurchCool) + leedElevEsc(colPurchHeat)),2)
!CALL PreDefTableEntry(pdchLeedPerfOthDem,'Total',useVal(15,colAdditionalFuel) + useVal(15,colPurchCool) + useVal(15,colPurchHeat),2)
CALL writeSubtitle('End Uses')
CALL writeTable(tableBody,rowHead,columnHead,columnWidth,.false.,footnote)
CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
'DemandEndUseComponentsSummary',&
'Entire Facility',&
'End Uses')
DEALLOCATE(columnHead)
DEALLOCATE(rowHead)
DEALLOCATE(columnWidth)
DEALLOCATE(tableBody)
!
!---- End Uses By Subcategory Sub-Table
!
numRows = 0
DO jEndUse = 1, NumEndUses
IF (EndUseCategory(jEndUse)%NumSubcategories > 0) THEN
DO kEndUseSub = 1, EndUseCategory(jEndUse)%NumSubcategories
numRows = numRows + 1
END DO
ELSE
numRows = numRows + 1
END IF
END DO
ALLOCATE(rowHead(numRows))
ALLOCATE(columnHead(7))
ALLOCATE(columnWidth(7))
columnWidth = 14 !array assignment - same for all columns
ALLOCATE(tableBody(numRows,7))
rowHead = ''
tableBody = ''
! Build row head and subcategories columns
i = 1
DO jEndUse = 1, NumEndUses
rowHead(i) = EndUseCategory(jEndUse)%DisplayName
IF (EndUseCategory(jEndUse)%NumSubcategories > 0) THEN
DO kEndUseSub = 1, EndUseCategory(jEndUse)%NumSubcategories
tableBody(i,1) = EndUseCategory(jEndUse)%SubcategoryName(kEndUseSub)
i = i + 1
END DO
ELSE
tableBody(i,1) = 'General'
i = i + 1
END IF
END DO
IF (unitsStyle .EQ. unitsStyleInchPound) THEN
columnHead(1) = 'Subcategory'
columnHead(2) = 'Electricity [kBtuh]'
columnHead(3) = 'Natural Gas [kBtuh]'
SELECT CASE (additionalFuelSelected)
CASE(6) ! gasoline
columnHead(4) = 'Gasoline [kBtuh]'
CASE(8) ! Diesel
columnHead(4) = 'Diesel [kBtuh]'
CASE(9) ! Coal
columnHead(4) = 'Coal [kBtuh]'
CASE(10) ! Fuel Oil #1
columnHead(4) = 'Fuel Oil #1 [kBtuh]'
CASE(11) ! Fuel Oil #2
columnHead(4) = 'Fuel Oil #2 [kBtuh]'
CASE(12) ! Propane
columnHead(4) = 'Propane [kBtuh]'
CASE(13) ! OtherFuel1
columnHead(4) = 'Other Fuel 1 [kBtuh]'
CASE(14) ! OtherFuel2
columnHead(4) = 'Other Fuel 2 [kBtuh]'
END SELECT
columnHead(5) = 'District Cooling [kBtuh]'
SELECT CASE (distrHeatSelected)
CASE (4)
columnHead(6) = 'District Heating [kBtuh]'
CASE (5)
columnHead(6) = 'Steam [kBtuh]'
END SELECT
columnHead(7) = 'Water [gal/min]'
ELSE
columnHead(1) = 'Subcategory'
columnHead(2) = 'Electricity [W]'
columnHead(3) = 'Natural Gas [W]'
SELECT CASE (additionalFuelSelected)
CASE(6) ! gasoline
columnHead(4) = 'Gasoline [W]'
CASE(8) ! Diesel
columnHead(4) = 'Diesel [W]'
CASE(9) ! Coal
columnHead(4) = 'Coal [W]'
CASE(10) ! Fuel Oil #1
columnHead(4) = 'Fuel Oil #1 [W]'
CASE(11) ! Fuel Oil #2
columnHead(4) = 'Fuel Oil #2 [W]'
CASE(12) ! Propane
columnHead(4) = 'Propane [W]'
CASE(13) ! OtherFuel1
columnHead(4) = 'Other Fuel 1 [W]'
CASE(14) ! OtherFuel2
columnHead(4) = 'Other Fuel 2 [W]'
END SELECT
columnHead(5) = 'District Cooling [W]'
SELECT CASE (distrHeatSelected)
CASE (4)
columnHead(6) = 'District Heating [W]'
CASE (5)
columnHead(6) = 'Steam [W]'
END SELECT
columnHead(7) = 'Water [m3/s]'
END IF
DO iResource = 1, 6
i = 1
DO jEndUse = 1, NumEndUses
IF (EndUseCategory(jEndUse)%NumSubcategories > 0) THEN
DO kEndUseSub = 1, EndUseCategory(jEndUse)%NumSubcategories
tableBody(i,iResource+1) = TRIM(RealToStr(collapsedEndUseSub(iResource,jEndUse,kEndUseSub),2))
i = i + 1
END DO
ELSE
tableBody(i,iResource+1) = TRIM(RealToStr(collapsedEndUse(jEndUse,iResource),2))
i = i + 1
END IF
END DO
END DO
! heading for the entire sub-table
CALL writeSubtitle('End Uses By Subcategory')
CALL writeTable(tableBody,rowHead,columnHead,columnWidth,.false.,footnote)
CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
'DemandEndUseComponentsSummary',&
'Entire Facility',&
'End Uses By Subcategory')
DEALLOCATE(columnHead)
DEALLOCATE(rowHead)
DEALLOCATE(columnWidth)
DEALLOCATE(tableBody)
END IF
END SUBROUTINE WriteDemandEndUseSummary