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 WriteTabularLifeCycleCostReport
          ! SUBROUTINE INFORMATION:
          !    AUTHOR         Jason Glazer of GARD Analytics, Inc.
          !    DATE WRITTEN   June 2010
          !    MODIFIED       na
          !    RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          !    Write the output report related to life-cycle costing
          !    to the tabular output file.
          ! METHODOLOGY EMPLOYED:
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
USE OutputReportTabular, ONLY: WriteReportHeaders, WriteSubtitle, WriteTable, RealToStr, IntToStr
USE SQLiteProcedures, ONLY: CreateSQLiteTabularDataRecords
IMPLICIT NONE    ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
          ! na
          ! SUBROUTINE PARAMETER DEFINITIONS:
          ! na
          ! 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
INTEGER :: month
INTEGER :: numColumns
INTEGER :: iYear
INTEGER :: jObj
INTEGER :: kMonth
INTEGER :: curCashFlow
INTEGER :: numRows
INTEGER :: offset
INTEGER :: numYears
REAL(r64) :: totalPV
IF (LCCparamPresent) THEN
  !---------------------------------
  ! Life-Cycle Cost Verification and Results Report
  !---------------------------------
  CALL WriteReportHeaders('Life-Cycle Cost Report','Entire Facility',1)
  !
  !---- Life-Cycle Cost Parameters
  !
  ALLOCATE(rowHead(11))
  ALLOCATE(columnHead(1))
  ALLOCATE(columnWidth(1))
  ALLOCATE(tableBody(11,1))
  tableBody = ''
  rowHead(1) = 'Name'
  rowHead(2) = 'Discounting Convention'
  rowHead(3) = 'Inflation Approach'
  rowHead(4) = 'Real Discount Rate'
  rowHead(5) = 'Nominal Discount Rate'
  rowHead(6) = 'Inflation'
  rowHead(7) = 'Base Date'
  rowHead(8) = 'Service Date'
  rowHead(9) = 'Length of Study Period in Years'
  rowHead(10) = 'Tax rate'
  rowHead(11) = 'Depreciation Method'
  columnHead(1) = 'Value'
  tableBody(1,1) = LCCname
  IF (discountConvension .EQ. disConvEndOfYear) THEN
    tableBody(2,1) = 'EndOfYear'
  ELSEIF (discountConvension .EQ. disConvMidYear) THEN
    tableBody(2,1) = 'MidYear'
  ELSEIF (discountConvension .EQ. disConvBeginOfYear) THEN
    tableBody(2,1) = 'BeginningOfYear'
  ENDIF
  IF (inflationApproach .EQ. inflAppConstantDollar) THEN
    tableBody(3,1) = 'ConstantDollar'
  ELSEIF (inflationApproach .EQ. inflAppCurrentDollar) THEN
    tableBody(3,1) = 'CurrentDollar'
  ENDIF
  IF (inflationApproach .EQ. inflAppConstantDollar) THEN
    tableBody(4,1) = TRIM(RealToStr(realDiscountRate, 4))
  ELSE
    tableBody(4,1) = '-- N/A --'
  END IF
  IF (inflationApproach .EQ. inflAppCurrentDollar) THEN
    tableBody(5,1) = TRIM(RealToStr(nominalDiscountRate, 4))
  ELSE
    tableBody(5,1) = '-- N/A --'
  END IF
  IF (inflationApproach .EQ. inflAppCurrentDollar) THEN
    tableBody(6,1) = TRIM(RealToStr(inflation, 4))
  ELSE
    tableBody(6,1) = '-- N/A --'
  END IF
  tableBody(7,1) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear)
  tableBody(8,1) = MonthNames(serviceDateMonth) // ' ' // IntToStr(serviceDateYear)
  tableBody(9,1) = TRIM(IntToStr(lengthStudyYears))
  tableBody(10,1) = TRIM(RealToStr(taxRate, 4))
  SELECT CASE (depreciationMethod)
    CASE(depMethMACRS3)
      tableBody(11,1) = 'ModifiedAcceleratedCostRecoverySystem-3year'
    CASE(depMethMACRS5)
      tableBody(11,1) = 'ModifiedAcceleratedCostRecoverySystem-5year'
    CASE(depMethMACRS7)
      tableBody(11,1) = 'ModifiedAcceleratedCostRecoverySystem-7year'
    CASE(depMethMACRS10)
      tableBody(11,1) = 'ModifiedAcceleratedCostRecoverySystem-10year'
    CASE(depMethMACRS15)
      tableBody(11,1) = 'ModifiedAcceleratedCostRecoverySystem-15year'
    CASE(depMethMACRS20)
      tableBody(11,1) = 'ModifiedAcceleratedCostRecoverySystem-20year'
    CASE(depMethStraight27)
      tableBody(11,1) = 'StraightLine-27year'
    CASE(depMethStraight31)
      tableBody(11,1) = 'StraightLine-31year'
    CASE(depMethStraight39)
      tableBody(11,1) = 'StraightLine-39year'
    CASE(depMethStraight40)
      tableBody(11,1) = 'StraightLine-40year'
    CASE(depMethNone)
      tableBody(11,1) = 'None'
  END SELECT
  columnWidth = 14 !array assignment - same for all columns
  CALL WriteSubtitle('Life-Cycle Cost Parameters')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Life-Cycle Cost Parameters')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Use Price Escalation
  !
  numColumns = MAX(1,numUsePriceEscalation)
  ALLOCATE(rowHead(lengthStudyYears + 2))
  ALLOCATE(columnHead(numColumns))
  ALLOCATE(columnWidth(numColumns))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears + 2,numColumns))
  tableBody = ''
  columnHead = 'none'
  rowHead(1) = 'Resource'
  rowHead(2) = 'Start Date'
  DO iYear = 1,lengthStudyYears
    rowHead(iYear+2) = IntToStr(iYear)
  END DO
  DO jObj = 1,numUsePriceEscalation !loop through objects not columns to add names
    columnHead(jObj) = UsePriceEscalation(jObj)%name
    tableBody(1,jObj) = TRIM(GetResourceTypeChar(UsePriceEscalation(jObj)%resource))
    tableBody(2,jObj) = MonthNames(UsePriceEscalation(jObj)%escalationStartMonth) // ' ' //   &
       IntToStr(UsePriceEscalation(jObj)%escalationStartYear)
  END DO
  DO jObj = 1,numUsePriceEscalation
    DO iYear = 1,lengthStudyYears
      tableBody(iYear+2,jObj) = TRIM(RealToStr(UsePriceEscalation(jObj)%Escalation(iYear),6))
    END DO
  END DO
  CALL WriteSubtitle('Use Price Escalation')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Use Price Escalation')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Use Adjustment
  !
  IF (numUseAdjustment .GE. 1) THEN !only create table if objects used
    numColumns = MAX(1,numUseAdjustment)
    numYears = lengthStudyYears - (serviceDateYear - BaseDateYear)
    ALLOCATE(rowHead(numYears+1))
    ALLOCATE(columnHead(numColumns))
    ALLOCATE(columnWidth(numColumns))
    columnWidth = 14 !array assignment - same for all columns
    ALLOCATE(tableBody(numYears+1,numColumns))
    tableBody = ''
    columnHead = 'none'
    rowHead(1) = ''
    DO iYear = 1,numYears
      rowHead(iYear+1) = MonthNames(serviceDateMonth) // ' ' // IntToStr(serviceDateYear + iYear - 1)
    END DO
    DO jObj = 1,numUseAdjustment !loop through objects not columns to add names
      columnHead(jObj) = UseAdjustment(jObj)%Name
      tableBody(1,jObj) = TRIM(GetResourceTypeChar(UseAdjustment(jObj)%resource))
    END DO
    DO jObj = 1,numUseAdjustment
      DO iYear = 1,numYears
        tableBody(iYear + 1,jObj) = TRIM(RealToStr(UseAdjustment(jObj)%Adjustment(iYear),6))
      END DO
    END DO
    CALL WriteSubtitle('Use Adjustment')
    CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
    CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                        'Life-Cycle Cost Report',&
                                        'Entire Facility',&
                                        'Use Adjustment')
    DEALLOCATE(columnHead)
    DEALLOCATE(rowHead)
    DEALLOCATE(columnWidth)
    DEALLOCATE(tableBody)
  END IF
  !
  !---- Cash Flow for Recurring and Nonrecurring Costs
  !
  numColumns = MAX(1,numRecurringCosts + numNonrecurringCost)
  ALLOCATE(rowHead(lengthStudyYears + 1))
  ALLOCATE(columnHead(numColumns))
  ALLOCATE(columnWidth(numColumns))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears + 1,numColumns))
  tableBody = ''
  rowHead(1) = ''
  DO iYear = 1,lengthStudyYears
    rowHead(iYear+1) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear + iYear - 1)
  END DO
  DO jObj = 1,(numRecurringCosts + numNonrecurringCost)
    curCashFlow = countOfCostCat + jObj
    columnHead(jObj) = CashFlow(curCashFlow)%Name
    SELECT CASE (CashFlow(curCashFlow)%SourceKind)
      CASE (skNonrecurring)
        tableBody(1,jObj) = 'Nonrecurring'
      CASE (skRecurring)
        tableBody(1,jObj) = 'Recurring'
    END SELECT
    DO iYear = 1,lengthStudyYears
       tableBody(iYear + 1,jObj) = TRIM(RealToStr(CashFlow(curCashFlow)%yrAmount(iYear),2))
    END DO
  END DO
  CALL WriteSubtitle('Cash Flow for Recurring and Nonrecurring Costs (Without Escalation)')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Cash Flow for Recurring and Nonrecurring Costs (Without Escalation)')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Energy Cost Cash Flows
  !
  numColumns = MAX(1,numResourcesUsed)
  ALLOCATE(rowHead(lengthStudyYears))
  ALLOCATE(columnHead(numColumns))
  ALLOCATE(columnWidth(numColumns))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears ,numColumns))
  tableBody = ''
  DO iYear = 1,lengthStudyYears
    rowHead(iYear) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear + iYear - 1)
  END DO
  DO jObj = 1,numResourcesUsed
    curCashFlow = countOfCostCat + numRecurringCosts + numNonrecurringCost + jObj
    columnHead(jObj) = CashFlow(curCashFlow)%Name
    DO iYear = 1,lengthStudyYears
      tableBody(iYear,jObj) = TRIM(RealToStr(CashFlow(curCashFlow)%yrAmount(iYear),2))
    END DO
  END DO
  CALL WriteSubtitle('Energy Cost Cash Flows (Without Escalation)')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Energy Cost Cash Flows (Without Escalation)')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Capital Cash Flow by Category
  !
  ALLOCATE(rowHead(lengthStudyYears))
  ALLOCATE(columnHead(4))
  ALLOCATE(columnWidth(4))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears ,4))
  tableBody = ''
  columnHead(1) = 'Construction'
  columnHead(2) = 'Salvage'
  columnHead(3) = 'OtherCapital'
  columnHead(4) = 'Total'
  DO iYear = 1,lengthStudyYears
    rowHead(iYear) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear + iYear - 1)
    tableBody(iYear,1) = TRIM(RealToStr(CashFlow(costCatConstruction)%yrAmount(iYear),2))
    tableBody(iYear,2) = TRIM(RealToStr(CashFlow(costCatSalvage)%yrAmount(iYear),2))
    tableBody(iYear,3) = TRIM(RealToStr(CashFlow(costCatOtherCapital)%yrAmount(iYear),2))
    tableBody(iYear,4) = TRIM(RealToStr(CashFlow(costCatTotCaptl)%yrAmount(iYear),2))
  END DO
  CALL WriteSubtitle('Capital Cash Flow by Category (Without Escalation)')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Capital Cash Flow by Category (Without Escalation)')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Operating Cash Flow by Category
  !
  ALLOCATE(rowHead(lengthStudyYears))
  ALLOCATE(columnHead(10))
  ALLOCATE(columnWidth(10))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears ,10))
  tableBody = ''
  columnHead(1) = 'Energy'
  columnHead(2) = 'Water'
  columnHead(3) = 'Maintenance'
  columnHead(4) = 'Repair'
  columnHead(5) = 'Operation'
  columnHead(6) = 'Replacement'
  columnHead(7) = 'MinorOverhaul'
  columnHead(8) = 'MajorOverhaul'
  columnHead(9) = 'OtherOperational'
  columnHead(10) = 'Total'
  DO iYear = 1,lengthStudyYears
    rowHead(iYear) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear + iYear - 1)
    tableBody(iYear,1) = TRIM(RealToStr(CashFlow(costCatEnergy)%yrAmount(iYear),2))
    tableBody(iYear,2) = TRIM(RealToStr(CashFlow(costCatWater)%yrAmount(iYear),2))
    tableBody(iYear,3) = TRIM(RealToStr(CashFlow(costCatMaintenance)%yrAmount(iYear),2))
    tableBody(iYear,4) = TRIM(RealToStr(CashFlow(costCatRepair)%yrAmount(iYear),2))
    tableBody(iYear,5) = TRIM(RealToStr(CashFlow(costCatOperation)%yrAmount(iYear),2))
    tableBody(iYear,6) = TRIM(RealToStr(CashFlow(costCatReplacement)%yrAmount(iYear),2))
    tableBody(iYear,7) = TRIM(RealToStr(CashFlow(costCatMinorOverhaul)%yrAmount(iYear),2))
    tableBody(iYear,8) = TRIM(RealToStr(CashFlow(costCatMajorOverhaul)%yrAmount(iYear),2))
    tableBody(iYear,9) = TRIM(RealToStr(CashFlow(costCatOtherOperational)%yrAmount(iYear),2))
    tableBody(iYear,10) = TRIM(RealToStr(CashFlow(costCatTotOper)%yrAmount(iYear),2))
  END DO
  CALL WriteSubtitle('Operating Cash Flow by Category (Without Escalation)')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Operating Cash Flow by Category (Without Escalation)')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- DEBUG ONLY - Monthly Cash Flows
  !
  ! This table is not usually produced but was used as a debugging aid. The code
  ! was kept for future debugging efforts related to cashflows but should generally
  ! be commented out.
  !
!  ALLOCATE(rowHead(lengthStudyTotalMonths))
!  ALLOCATE(columnHead(numCashFlow))
!  ALLOCATE(columnWidth(numCashFlow))
!  ALLOCATE(tableBody(lengthStudyTotalMonths,numCashFlow))
!  tableBody = ''
!  columnHead(1) = 'mnt'
!  columnHead(2) = 'rpr'
!  columnHead(3) = 'opr'
!  columnHead(4) = 'repl'
!  columnHead(5) = 'mOvhl'
!  columnHead(6) = 'MOvhl'
!  columnHead(7) = 'oOpr'
!  columnHead(8) = 'cons'
!  columnHead(9) = 'slvg'
!  columnHead(10) = 'oCap'
!  columnHead(11) = 'H20'
!  columnHead(12) = 'ene'
!  columnHead(13) = 'tEne'
!  columnHead(14) = 'tOpr'
!  columnHead(15) = 'tCap'
!  columnHead(16) = 'Totl'
!  DO jObj = countOfCostCat + 1, numCashFlow
!    columnHead(jObj) = CashFlow(jObj)%name
!  END DO
!  DO kMonth = 1,lengthStudyTotalMonths
!    rowHead(kMonth) = MonthNames(1 + MOD((kMonth + baseDateMonth - 2),12)) &
!                      // ' ' // IntToStr(baseDateYear + INT((kMonth - 1) / 12))
!  END DO
!  DO kMonth = 1,lengthStudyTotalMonths
!    DO jObj = 1,numCashFlow
!      tableBody(kMonth,jObj) = TRIM(RealToStr(CashFlow(jObj)%mnAmount(kMonth),2))
!    END DO
!  END DO
!  columnWidth = 14 !array assignment - same for all columns
!  CALL WriteSubtitle('DEBUG ONLY - Monthly Cash Flows')
!  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
!  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
!                                      'Life-Cycle Cost Report',&
!                                      'Entire Facility',&
!                                      'DEBUG ONLY - Monthly Cash Flows')
!  DEALLOCATE(columnHead)
!  DEALLOCATE(rowHead)
!  DEALLOCATE(columnWidth)
!  DEALLOCATE(tableBody)
  !
  !---- Monthly Total Cash Flow
  !
  ALLOCATE(rowHead(lengthStudyYears))
  ALLOCATE(columnHead(12))
  ALLOCATE(columnWidth(12))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears,12))
  tableBody = ''
  DO kMonth = 1,12
    columnHead(kMonth) = MonthNames(kMonth)
  END DO
  DO iYear = 1,lengthStudyYears
    rowHead(iYear) = IntToStr(baseDateYear + iYear - 1)
  END DO
  DO iYear = 1,lengthStudyYears
    DO kMonth = 1,12
      tableBody(iYear,kMonth) = TRIM(RealToStr(CashFlow(costCatTotGrand)%mnAmount((iYear - 1) * 12 + kMonth),2))
    END DO
  END DO
  CALL WriteSubtitle('Monthly Total Cash Flow (Without Escalation)')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Monthly Total Cash Flow (Without Escalation)')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Present Value for Recurring, Nonrecurring and Energy Costs
  !
  numRows = MAX(1,numRecurringCosts + numNonrecurringCost + numResourcesUsed)
  ALLOCATE(rowHead(numRows + 1))
  ALLOCATE(columnHead(5))
  ALLOCATE(columnWidth(5))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(numRows + 1 ,5))
  tableBody = ''
  columnHead(1) = 'Category'
  columnHead(2) = 'Kind'
  columnHead(3) = 'Cost'
  columnHead(4) = 'Present Value'
  columnHead(5) = 'Present Value Factor'
  totalPV = 0.0d0
  rowHead(numRows + 1) = 'TOTAL'
  DO jObj = 1,(numRecurringCosts + numNonrecurringCost + numResourcesUsed)
    offset = countOfCostCat
    rowHead(jObj) = CashFlow(offset + jObj)%name
    SELECT CASE (CashFlow(offset + jObj)%Category)
      CASE (costCatMaintenance)
        tableBody(jObj,1) = 'Maintenance'
      CASE (costCatRepair)
        tableBody(jObj,1) = 'Repair'
      CASE (costCatOperation)
        tableBody(jObj,1) = 'Operation'
      CASE (costCatReplacement)
        tableBody(jObj,1) = 'Replacement'
      CASE (costCatMinorOverhaul)
        tableBody(jObj,1) = 'Minor Overhaul'
      CASE (costCatMajorOverhaul)
        tableBody(jObj,1) = 'Major Overhaul'
      CASE (costCatOtherOperational)
        tableBody(jObj,1) = 'Other Operational'
      CASE (costCatConstruction)
        tableBody(jObj,1) = 'Construction'
      CASE (costCatSalvage)
        tableBody(jObj,1) = 'Salvage'
      CASE (costCatOtherCapital)
        tableBody(jObj,1) = 'Other Capital'
      CASE (costCatWater)
        tableBody(jObj,1) = 'Water'
      CASE (costCatEnergy)
        tableBody(jObj,1) = 'Energy'
      CASE DEFAULT
        tableBody(jObj,1) = '-'
    END SELECT
    SELECT CASE (CashFlow(offset + jObj)%SourceKind)
      CASE (skNonrecurring)
        tableBody(jObj,2) = 'Nonrecurring'
      CASE (skRecurring)
        tableBody(jObj,2) = 'Recurring'
      CASE (skResource)
        tableBody(jObj,2) = 'Energy Cost'
      CASE DEFAULT
        tableBody(jObj,2) = '-'
    END SELECT
    tableBody(jObj,3) = TRIM(RealToStr(CashFlow(offset + jObj)%orginalCost,2))
    tableBody(jObj,4) = TRIM(RealToStr(CashFlow(offset + jObj)%presentValue,2))
    totalPV = totalPV + CashFlow(offset + jObj)%presentValue
    IF (CashFlow(offset + jObj)%orginalCost .NE. 0.0d0) THEN
      tableBody(jObj,5) = TRIM(RealToStr(CashFlow(offset + jObj)%presentValue / CashFlow(offset + jObj)%orginalCost,4))
    ELSE
      tableBody(jObj,5) = '-'
    END IF
  END DO
  tableBody(numRows + 1,4) = TRIM(RealToStr(totalPV,2))
  CALL WriteSubtitle('Present Value for Recurring, Nonrecurring and Energy Costs (Before Tax)')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Present Value for Recurring, Nonrecurring and Energy Costs (Before Tax)')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Present Value by Category
  !
  ALLOCATE(rowHead(16))
  ALLOCATE(columnHead(1))
  ALLOCATE(columnWidth(1))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(16 ,1))
  tableBody = ''
  rowHead(1) = 'Construction'
  rowHead(2) = 'Salvage'
  rowHead(3) = 'Other Capital'
  rowHead(4) = 'Energy'
  rowHead(5) = 'Water'
  rowHead(6) = 'Maintenance'
  rowHead(7) = 'Repair'
  rowHead(8) = 'Operation'
  rowHead(9) = 'Replacement'
  rowHead(10) = 'Minor Overhaul'
  rowHead(11) = 'Major Overhaul'
  rowHead(12) = 'Other Operational'
  rowHead(13) = 'Total Energy'
  rowHead(14) = 'Total Operation'
  rowHead(15) = 'Total Capital'
  rowHead(16) = 'Grand Total'
  columnHead(1) = 'Present Value'
  tableBody(1,1) = TRIM(RealToStr(CashFlow(costCatConstruction)%presentValue,2))
  tableBody(2,1) = TRIM(RealToStr(CashFlow(costCatSalvage)%presentValue,2))
  tableBody(3,1) = TRIM(RealToStr(CashFlow(costCatOtherCapital)%presentValue,2))
  tableBody(4,1) = TRIM(RealToStr(CashFlow(costCatEnergy)%presentValue,2))
  tableBody(5,1) = TRIM(RealToStr(CashFlow(costCatWater)%presentValue,2))
  tableBody(6,1) = TRIM(RealToStr(CashFlow(costCatMaintenance)%presentValue,2))
  tableBody(7,1) = TRIM(RealToStr(CashFlow(costCatRepair)%presentValue,2))
  tableBody(8,1) = TRIM(RealToStr(CashFlow(costCatOperation)%presentValue,2))
  tableBody(9,1) = TRIM(RealToStr(CashFlow(costCatReplacement)%presentValue,2))
  tableBody(10,1) = TRIM(RealToStr(CashFlow(costCatMinorOverhaul)%presentValue,2))
  tableBody(11,1) = TRIM(RealToStr(CashFlow(costCatMajorOverhaul)%presentValue,2))
  tableBody(12,1) = TRIM(RealToStr(CashFlow(costCatOtherOperational)%presentValue,2))
  tableBody(13,1) = TRIM(RealToStr(CashFlow(costCatTotEnergy)%presentValue,2))
  tableBody(14,1) = TRIM(RealToStr(CashFlow(costCatTotOper)%presentValue,2))
  tableBody(15,1) = TRIM(RealToStr(CashFlow(costCatTotCaptl)%presentValue,2))
  tableBody(16,1) = TRIM(RealToStr(CashFlow(costCatTotGrand)%presentValue,2))
  CALL WriteSubtitle('Present Value by Category')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Present Value by Category')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- Present Value by Year
  !
  ALLOCATE(rowHead(lengthStudyYears + 1))
  ALLOCATE(columnHead(2))
  ALLOCATE(columnWidth(2))
  columnWidth = 14 !array assignment - same for all columns
  ALLOCATE(tableBody(lengthStudyYears + 1,2))
  tableBody = ''
  columnHead(1) = 'Total Cost'
  columnHead(2) = 'Present Value of Costs'
  totalPV = 0.0d0
  DO iYear = 1,lengthStudyYears
    rowHead(iYear) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear + iYear - 1)
    tableBody(iYear,1) = TRIM(RealToStr(CashFlow(costCatTotGrand)%yrAmount(iYear),2))
    tableBody(iYear,2) = TRIM(RealToStr(CashFlow(costCatTotGrand)%yrPresVal(iYear),2))
    totalPV = totalPV + CashFlow(costCatTotGrand)%yrPresVal(iYear)
  END DO
  rowHead(lengthStudyYears + 1) = 'TOTAL'
  tableBody(lengthStudyYears + 1,2) = TRIM(RealToStr(totalPV,2))
  CALL WriteSubtitle('Present Value by Year')
  CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
  CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                      'Life-Cycle Cost Report',&
                                      'Entire Facility',&
                                      'Present Value by Year')
  DEALLOCATE(columnHead)
  DEALLOCATE(rowHead)
  DEALLOCATE(columnWidth)
  DEALLOCATE(tableBody)
  !
  !---- After Tax Estimate
  !
  IF (taxRate .NE. 0.0d0) THEN
    ALLOCATE(rowHead(lengthStudyYears + 1))
    ALLOCATE(columnHead(5))
    ALLOCATE(columnWidth(5))
    columnWidth = 14 !array assignment - same for all columns
    ALLOCATE(tableBody(lengthStudyYears + 1,5))
    tableBody = ''
    columnHead(1) = 'Depreciated Capital'
    columnHead(2) = 'Taxable Income'
    columnHead(3) = 'Income Taxes'
    columnHead(4) = 'After Tax Cash Flow'
    columnHead(5) = 'After Tax Present Value'
    totalPV = 0.0d0
    DO iYear = 1,lengthStudyYears
      rowHead(iYear) = MonthNames(baseDateMonth) // ' ' // IntToStr(baseDateYear + iYear - 1)
      tableBody(iYear,1) = TRIM(RealToStr(DepreciatedCapital(iYear),2))
      tableBody(iYear,2) = TRIM(RealToStr(TaxableIncome(iYear),2))
      tableBody(iYear,3) = TRIM(RealToStr(Taxes(iYear),2))
      tableBody(iYear,4) = TRIM(RealToStr(AfterTaxCashFlow(iYear),2))
      tableBody(iYear,5) = TRIM(RealToStr(AfterTaxPresentValue(iYear),2))
      totalPV = totalPV + AfterTaxPresentValue(iYear)
    END DO
    rowHead(lengthStudyYears + 1) = 'TOTAL'
    tableBody(lengthStudyYears + 1,5) = TRIM(RealToStr(totalPV,2))
    CALL WriteSubtitle('After Tax Estimate')
    CALL writeTable(tableBody,rowHead,columnHead,columnWidth)
    CALL CreateSQLiteTabularDataRecords(tableBody,rowHead,columnHead,&
                                        'Life-Cycle Cost Report',&
                                        'Entire Facility',&
                                        'After Tax Estimate')
    DEALLOCATE(columnHead)
    DEALLOCATE(rowHead)
    DEALLOCATE(columnWidth)
    DEALLOCATE(tableBody)
  END IF
END IF
END SUBROUTINE WriteTabularLifeCycleCostReport