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 GatherForPredefinedReport
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Jason Glazer
          !       DATE WRITTEN   August 2006
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This subroutine reports the information for the predefined reports
          ! related to envelope components.
          ! METHODOLOGY EMPLOYED:
          ! na
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
  USE OutputReportPredefined
  USE WindowManager, ONLY: CalcNominalWindowCond
  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:
  CHARACTER(len=MaxNameLength) :: surfName
  INTEGER                      :: curCons
  INTEGER                      :: zonePt
  REAL(r64)                    :: mult
  REAL(r64)                    :: curAzimuth
  REAL(r64)                    :: curTilt
  INTEGER                      :: iSurf
  REAL(r64)                    :: windowArea
  REAL(r64)                    :: frameWidth
  REAL(r64)                    :: frameArea
  REAL(r64)                    :: dividerArea
  !counts for object count report
  INTEGER, DIMENSION(20)       :: numSurfaces
  INTEGER, DIMENSION(20)       :: numExtSurfaces
  INTEGER                      :: frameDivNum
  LOGICAL                      :: isExterior
  ! the following variables are for the CalcNominalWindowCond call but only SHGCSummer is needed
  REAL(r64) :: nomCond
  REAL(r64) :: SHGCSummer
  REAL(r64) :: TransSolNorm
  REAL(r64) :: TransVisNorm
  REAL(r64) :: nomUfact
  INTEGER :: ErrFlag
  INTEGER :: curWSC
  !following variables are totals for fenestration table
  REAL(r64) :: windowAreaWMult = 0.0d0
  REAL(r64) :: fenTotArea = 0.0d0
  REAL(r64) :: fenTotAreaNorth = 0.0d0
  REAL(r64) :: fenTotAreaNonNorth = 0.0d0
  REAL(r64) :: ufactArea = 0.0d0
  REAL(r64) :: ufactAreaNorth = 0.0d0
  REAL(r64) :: ufactAreaNonNorth = 0.0d0
  REAL(r64) :: shgcArea = 0.0d0
  REAL(r64) :: shgcAreaNorth = 0.0d0
  REAL(r64) :: shgcAreaNonNorth   = 0.0d0
  REAL(r64) :: vistranArea = 0.0d0
  REAL(r64) :: vistranAreaNorth = 0.0d0
  REAL(r64) :: vistranAreaNonNorth   = 0.0d0
  REAL(r64) :: intFenTotArea = 0.0d0
  REAL(r64) :: intUfactArea = 0.0d0
  REAL(r64) :: intShgcArea = 0.0d0
  REAL(r64) :: intVistranArea = 0.0d0
  LOGICAL   :: isNorth
  numSurfaces=0
  numExtSurfaces=0
  DO iSurf = 1, TotSurfaces
    zonePt = Surface(iSurf)%Zone
    !only exterior surfaces including underground
    IF ((Surface(iSurf)%ExtBoundCond .EQ. ExternalEnvironment) .OR. (Surface(iSurf)%ExtBoundCond .EQ. Ground) &
     .OR. (Surface(iSurf)%ExtBoundCond .EQ. GroundFCfactorMethod)) THEN
      isExterior = .TRUE.
      SELECT CASE (Surface(iSurf)%Class)
        CASE (SurfaceClass_Wall,SurfaceClass_Floor,SurfaceClass_Roof)
          surfName = Surface(iSurf)%Name
          curCons = Surface(iSurf)%Construction
          CALL PreDefTableEntry(pdchOpCons,surfName,Construct(curCons)%Name)
          CALL PreDefTableEntry(pdchOpRefl,surfName,1 - Construct(curCons)%OutsideAbsorpSolar)
          CALL PreDefTableEntry(pdchOpUfactNoFilm,surfName,NominalU(Surface(iSurf)%Construction),3)
          mult = Zone(zonePt)%Multiplier * Zone(zonePt)%ListMultiplier
          CALL PreDefTableEntry(pdchOpGrArea,surfName,Surface(iSurf)%GrossArea * mult)
          curAzimuth = Surface(iSurf)%Azimuth
          CALL PreDefTableEntry(pdchOpAzimuth,surfName,curAzimuth)
          curTilt = Surface(iSurf)%Tilt
          CALL PreDefTableEntry(pdchOpTilt,surfName,curTilt)
          IF ((curTilt >= 60.d0) .AND. (curTilt < 180.d0)) THEN
            IF ((curAzimuth >= 315.d0) .OR. (curAzimuth < 45.d0)) THEN
              CALL PreDefTableEntry(pdchOpDir,surfName,'N')
            ELSE IF ((curAzimuth >= 45.d0) .AND. (curAzimuth < 135.d0)) THEN
              CALL PreDefTableEntry(pdchOpDir,surfName,'E')
            ELSE IF ((curAzimuth >= 135.d0) .AND. (curAzimuth < 225.d0)) THEN
              CALL PreDefTableEntry(pdchOpDir,surfName,'S')
            ELSE IF ((curAzimuth >= 225.d0) .AND. (curAzimuth < 315.d0)) THEN
              CALL PreDefTableEntry(pdchOpDir,surfName,'W')
            ENDIF
          END IF
        CASE (SurfaceClass_Window,SurfaceClass_TDD_Dome)
          surfName = Surface(iSurf)%Name
          curCons = Surface(iSurf)%Construction
          CALL PreDefTableEntry(pdchFenCons,surfName,Construct(curCons)%Name)
          zonePt = Surface(iSurf)%Zone
          mult = Zone(zonePt)%Multiplier * Zone(zonePt)%ListMultiplier * Surface(iSurf)%Multiplier
          !include the frame area if present
          windowArea = Surface(iSurf)%GrossArea
          frameArea = 0.0d0
          dividerArea = 0.0d0
          frameDivNum = Surface(iSurf)%FrameDivider
          IF  (frameDivNum /= 0) THEN
            frameWidth = FrameDivider(frameDivNum)%FrameWidth
            frameArea = (Surface(iSurf)%Height + 2.0d0*frameWidth)*(Surface(iSurf)%Width + 2.0d0*frameWidth) &
                        - (Surface(iSurf)%Height * Surface(iSurf)%Width)
            windowArea = windowArea + frameArea
            dividerArea = FrameDivider(frameDivNum)%DividerWidth * &
             (FrameDivider(frameDivNum)%HorDividers * Surface(iSurf)%Width + &
              FrameDivider(frameDivNum)%VertDividers * Surface(iSurf)%Height - &
              FrameDivider(frameDivNum)%HorDividers * FrameDivider(frameDivNum)%VertDividers * &
              FrameDivider(frameDivNum)%DividerWidth)
            CALL PreDefTableEntry(pdchFenFrameConductance,surfName,FrameDivider(frameDivNum)%FrameConductance,3)
            CALL PreDefTableEntry(pdchFenDividerConductance,surfName,FrameDivider(frameDivNum)%DividerConductance,3)
          END IF
          windowAreaWMult = windowArea * mult
          CALL PreDefTableEntry(pdChFenAreaOf1,surfName,windowArea)
          CALL PreDefTableEntry(pdchFenFrameAreaOf1,surfName,frameArea)
          CALL PreDefTableEntry(pdchFenDividerAreaOf1,surfName,dividerArea)
          CALL PreDefTableEntry(pdchFenGlassAreaOf1,surfName, windowArea - (frameArea + dividerArea))
          CALL PreDefTableEntry(pdchFenArea,surfName,windowAreaWMult)
          nomUfact = NominalU(Surface(iSurf)%Construction)
          CALL PreDefTableEntry(pdchFenUfact,surfName,nomUfact,3)
          !if the construction report is requested the SummerSHGC is already calculated
          IF (Construct(curCons)%SummerSHGC /= 0) THEN
            SHGCSummer = Construct(curCons)%SummerSHGC
            TransVisNorm = Construct(curCons)%VisTransNorm
          ELSE
            !must calculate Summer SHGC
            IF (.NOT. Construct(curCons)%WindowTypeEQL) THEN
              CALL CalcNominalWindowCond(curCons,2,nomCond,SHGCSummer,TransSolNorm,TransVisNorm,ErrFlag)
            ENDIF
          END IF
          CALL PreDefTableEntry(pdchFenSHGC,surfName,SHGCSummer,3)
          CALL PreDefTableEntry(pdchFenVisTr,surfName,TransVisNorm,3)
          CALL PreDefTableEntry(pdchFenParent,surfName,Surface(iSurf)%BaseSurfName)
          curAzimuth = Surface(iSurf)%Azimuth
          CALL PreDefTableEntry(pdchFenAzimuth,surfName,curAzimuth)
          isNorth = .FALSE.
          curTilt = Surface(iSurf)%Tilt
          CALL PreDefTableEntry(pdchFenTilt,surfName,curTilt)
          IF ((curTilt >= 60.d0) .AND. (curTilt < 180.d0)) THEN
            IF ((curAzimuth >= 315.d0) .OR. (curAzimuth < 45.d0)) THEN
              CALL PreDefTableEntry(pdchFenDir,surfName,'N')
              isNorth = .TRUE.
            ELSE IF ((curAzimuth >= 45.d0) .AND. (curAzimuth < 135.d0)) THEN
              CALL PreDefTableEntry(pdchFenDir,surfName,'E')
            ELSE IF ((curAzimuth >= 135.d0) .AND. (curAzimuth < 225.d0)) THEN
              CALL PreDefTableEntry(pdchFenDir,surfName,'S')
            ELSE IF ((curAzimuth >= 225.d0) .AND. (curAzimuth < 315.d0)) THEN
              CALL PreDefTableEntry(pdchFenDir,surfName,'W')
            ENDIF
          END IF
          curWSC = Surface(iSurf)%WindowShadingControlPtr
          !compute totals for area weighted averages
          fenTotArea = fenTotArea + windowAreaWMult
          ufactArea = ufactArea + nomUfact * windowAreaWMult
          shgcArea = shgcArea + SHGCSummer * windowAreaWMult
          vistranArea = vistranArea + TransVisNorm * windowAreaWMult
          IF (isNorth) THEN
            fenTotAreaNorth = fenTotAreaNorth + windowAreaWMult
            ufactAreaNorth = ufactAreaNorth + nomUfact * windowAreaWMult
            shgcAreaNorth = shgcAreaNorth + SHGCSummer * windowAreaWMult
            vistranAreaNorth = vistranAreaNorth + TransVisNorm * windowAreaWMult
          ELSE
            fenTotAreaNonNorth = fenTotAreaNonNorth + windowAreaWMult
            ufactAreaNonNorth = ufactAreaNonNorth + nomUfact * windowAreaWMult
            shgcAreaNonNorth = shgcAreaNonNorth + SHGCSummer * windowAreaWMult
            vistranAreaNonNorth = vistranAreaNonNorth + TransVisNorm * windowAreaWMult
          END IF
          ! shading
          IF (curWSC /= 0) THEN
            CALL PreDefTableEntry(pdchFenSwitchable,surfName,'Yes')
            !shading report
            CALL PreDefTableEntry(pdchWscName,surfName,WindowShadingControl(curWsc)%name)
            SELECT CASE (WindowShadingControl(curWsc)%ShadingType)
              CASE (WSC_ST_NoShade)
                CALL PreDefTableEntry(pdchWscShading,surfName,'No Shade')
              CASE (WSC_ST_InteriorShade)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Interior Shade')
              CASE (WSC_ST_SwitchableGlazing)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Switchable Glazing')
              CASE (WSC_ST_ExteriorShade)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Exterior Shade')
              CASE (WSC_ST_InteriorBlind)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Interior Blind')
              CASE (WSC_ST_ExteriorBlind)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Exterior Blind')
              CASE (WSC_ST_BetweenGlassShade)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Between Glass Shade')
              CASE (WSC_ST_BetweenGlassBlind)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Between Glass Blind')
              CASE (WSC_ST_ExteriorScreen)
                CALL PreDefTableEntry(pdchWscShading,surfName,'Exterior Screen')
            END SELECT
            SELECT CASE (WindowShadingControl(curWsc)%ShadingControlType)
              CASE (WSCT_AlwaysOn)
                CALL PreDefTableEntry(pdchWscControl,surfName,'AlwaysOn')
              CASE (WSCT_AlwaysOff)
                CALL PreDefTableEntry(pdchWscControl,surfName,'AlwaysOff')
              CASE (WSCT_OnIfScheduled)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfScheduleAllows')
              CASE (WSCT_HiSolar)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighSolarOnWindow')
              CASE (WSCT_HiHorzSolar)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighHorizontalSolar')
              CASE (WSCT_HiOutAirTemp)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighOutdoorAirTemperature')
              CASE (WSCT_HiZoneAirTemp)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighZoneAirTemperature')
              CASE (WSCT_HiZoneCooling)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighZoneCooling')
              CASE (WSCT_HiGlare)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighGlare')
              CASE (WSCT_MeetDaylIlumSetp)
                CALL PreDefTableEntry(pdchWscControl,surfName,'MeetDaylightIlluminanceSetpoint')
              CASE (WSCT_OnNightLoOutTemp_OffDay)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnNightIfLowOutdoorTempAndOffDay')
              CASE (WSCT_OnNightLoInTemp_OffDay)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnNightIfLowInsideTempAndOffDay')
              CASE (WSCT_OnNightIfHeating_OffDay)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnNightIfHeatingAndOffDay')
              CASE (WSCT_OnNightLoOutTemp_OnDayCooling)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnNightIfLowOutdoorTempAndOnDayIfCooling')
              CASE (WSCT_OnNightIfHeating_OnDayCooling)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnNightIfHeatingAndOnDayIfCooling')
              CASE (WSCT_OffNight_OnDay_HiSolarWindow)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OffNightAndOnDayIfCoolingAndHighSolarOnWindow')
              CASE (WSCT_OnNight_OnDay_HiSolarWindow)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnNightAndOnDayIfCoolingAndHighSolarOnWindow')
              CASE (WSCT_OnHiOutTemp_HiSolarWindow)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighOutdoorAirTempAndHighSolarOnWindow')
              CASE (WSCT_OnHiOutTemp_HiHorzSolar)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighOutdoorAirTempAndHighHorizontalSolar')
              CASE (WSCT_OnHiZoneTemp_HiSolarWindow)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighZoneAirTempAndHighSolarOnWindow')
              CASE (WSCT_OnHiZoneTemp_HiHorzSolar)
                CALL PreDefTableEntry(pdchWscControl,surfName,'OnIfHighZoneAirTempAndHighHorizontalSolar')
            END SELECT
            IF (WindowShadingControl(curWsc)%ShadedConstruction /= 0) THEN
              CALL PreDefTableEntry(pdchWscShadCons,surfName,Construct(WindowShadingControl(curWsc)%ShadedConstruction)%Name)
            END IF
            IF (WindowShadingControl(curWsc)%GlareControlIsActive) THEN
              CALL PreDefTableEntry(pdchWscGlare,surfName,'Yes')
            ELSE
              CALL PreDefTableEntry(pdchWscGlare,surfName,'No')
            END IF
          ELSE
            CALL PreDefTableEntry(pdchFenSwitchable,surfName,'No')
          END IF
       CASE (SurfaceClass_Door)
          surfName = Surface(iSurf)%Name
          curCons = Surface(iSurf)%Construction
          CALL PreDefTableEntry(pdchDrCons,surfName,Construct(curCons)%Name)
          CALL PreDefTableEntry(pdchDrUfactNoFilm,surfName,NominalU(Surface(iSurf)%Construction),3)
          mult = Zone(zonePt)%Multiplier * Zone(zonePt)%ListMultiplier
          CALL PreDefTableEntry(pdchDrGrArea,surfName,Surface(iSurf)%GrossArea * mult)
          CALL PreDefTableEntry(pdchDrParent,surfName,Surface(iSurf)%BaseSurfName)
     END SELECT
    ELSE
      isExterior = .FALSE.
      !interior window report
      IF (Surface(iSurf)%Class .EQ. SurfaceClass_Window) THEN
        IF (Surface(iSurf)%Name(1:3) .NE. 'iz-') THEN !don't count created interzone surfaces that are mirrors of other surfaces
          surfName = Surface(iSurf)%Name
          curCons = Surface(iSurf)%Construction
          CALL PreDefTableEntry(pdchIntFenCons,surfName,Construct(curCons)%Name)
          zonePt = Surface(iSurf)%Zone
          mult = Zone(zonePt)%Multiplier * Zone(zonePt)%ListMultiplier * Surface(iSurf)%Multiplier
          !include the frame area if present
          windowArea = Surface(iSurf)%GrossArea
          IF  (Surface(iSurf)%FrameDivider /= 0) THEN
            frameWidth = FrameDivider(Surface(iSurf)%FrameDivider)%FrameWidth
            frameArea = (Surface(iSurf)%Height + 2*frameWidth)*(Surface(iSurf)%Width + 2*frameWidth) &
                        - (Surface(iSurf)%Height * Surface(iSurf)%Width)
            windowArea = windowArea + frameArea
          END IF
          windowAreaWMult = windowArea * mult
          CALL PreDefTableEntry(pdchIntFenAreaOf1,surfName,windowArea)
          CALL PreDefTableEntry(pdchIntFenArea,surfName,windowAreaWMult)
          nomUfact = NominalU(Surface(iSurf)%Construction)
          CALL PreDefTableEntry(pdchIntFenUfact,surfName,nomUfact,3)
          !if the construction report is requested the SummerSHGC is already calculated
          IF (Construct(curCons)%SummerSHGC /= 0) THEN
            SHGCSummer = Construct(curCons)%SummerSHGC
            TransVisNorm = Construct(curCons)%VisTransNorm
          ELSE
            !must calculate Summer SHGC
            IF (.NOT. Construct(curCons)%WindowTypeEQL) THEN
                CALL CalcNominalWindowCond(curCons,2,nomCond,SHGCSummer,TransSolNorm,TransVisNorm,ErrFlag)
            ENDIF
          END IF
          CALL PreDefTableEntry(pdchIntFenSHGC,surfName,SHGCSummer,3)
          CALL PreDefTableEntry(pdchIntFenVisTr,surfName,TransVisNorm,3)
          CALL PreDefTableEntry(pdchIntFenParent,surfName,Surface(iSurf)%BaseSurfName)
          !compute totals for area weighted averages
          intFenTotArea = intFenTotArea + windowAreaWMult
          intUfactArea = intUfactArea + nomUfact * windowAreaWMult
          intShgcArea = intShgcArea + SHGCSummer * windowAreaWMult
          intVistranArea = intVistranArea + TransVisNorm * windowAreaWMult
        END IF
      END IF
    END IF
    ! do counts - use classification (note using numeric.  if class assignments change, this won't work)
    IF ((Surface(iSurf)%Class <= 20) .AND. (Surface(iSurf)%Class >= 1)) THEN
      numSurfaces(Surface(iSurf)%Class) = numSurfaces(Surface(iSurf)%Class) + 1
      IF (isExterior) THEN
        numExtSurfaces(Surface(iSurf)%Class) = numExtSurfaces(Surface(iSurf)%Class) + 1
      END IF
    END IF
  END DO
  ! total
  CALL PreDefTableEntry(pdchFenArea,"Total or Average",fenTotArea)
  IF (fenTotArea > 0.0d0) THEN
    CALL PreDefTableEntry(pdchFenUfact,"Total or Average",ufactArea / fenTotArea,3)
    CALL PreDefTableEntry(pdchFenSHGC,"Total or Average",shgcArea / fenTotArea,3)
    CALL PreDefTableEntry(pdchFenVisTr,"Total or Average",vistranArea / fenTotArea,3)
  ELSE
    CALL PreDefTableEntry(pdchFenUfact,"Total or Average","-")
    CALL PreDefTableEntry(pdchFenSHGC,"Total or Average","-")
    CALL PreDefTableEntry(pdchFenVisTr,"Total or Average","-")
  ENDIF
  ! north
  CALL PreDefTableEntry(pdchFenArea,"North Total or Average",fenTotAreaNorth)
  IF (fenTotAreaNorth > 0.0d0) THEN
    CALL PreDefTableEntry(pdchFenUfact,"North Total or Average",ufactAreaNorth / fenTotAreaNorth,3)
    CALL PreDefTableEntry(pdchFenSHGC,"North Total or Average",shgcAreaNorth / fenTotAreaNorth,3)
    CALL PreDefTableEntry(pdchFenVisTr,"North Total or Average",vistranAreaNorth / fenTotAreaNorth,3)
  ELSE
    CALL PreDefTableEntry(pdchFenUfact,"North Total or Average","-")
    CALL PreDefTableEntry(pdchFenSHGC,"North Total or Average","-")
    CALL PreDefTableEntry(pdchFenVisTr,"North Total or Average","-")
  ENDIF
  ! non-north
  CALL PreDefTableEntry(pdchFenArea,"Non-North Total or Average",fenTotAreaNonNorth)
  IF (fenTotAreaNonNorth > 0.0d0) THEN
    CALL PreDefTableEntry(pdchFenUfact,"Non-North Total or Average",ufactAreaNonNorth / fenTotAreaNonNorth,3)
    CALL PreDefTableEntry(pdchFenSHGC,"Non-North Total or Average",shgcAreaNonNorth / fenTotAreaNonNorth,3)
    CALL PreDefTableEntry(pdchFenVisTr,"Non-North Total or Average",vistranAreaNonNorth / fenTotAreaNonNorth,3)
  ELSE
    CALL PreDefTableEntry(pdchFenUfact,"Non-North Total or Average","-")
    CALL PreDefTableEntry(pdchFenSHGC,"Non-North Total or Average","-")
    CALL PreDefTableEntry(pdchFenVisTr,"Non-North Total or Average","-")
  ENDIF
  !interior fenestration totals
  CALL PreDefTableEntry(pdchIntFenArea,"Total or Average",intFenTotArea)
  IF (intFenTotArea > 0.0d0) THEN
    CALL PreDefTableEntry(pdchIntFenUfact,"Total or Average",intUfactArea / intFenTotArea,3)
    CALL PreDefTableEntry(pdchIntFenSHGC,"Total or Average",intShgcArea / intFenTotArea,3)
    CALL PreDefTableEntry(pdchIntFenVisTr,"Total or Average",intVistranArea / intFenTotArea,3)
  ELSE
    CALL PreDefTableEntry(pdchIntFenUfact,"Total or Average","-")
    CALL PreDefTableEntry(pdchIntFenSHGC,"Total or Average","-")
    CALL PreDefTableEntry(pdchIntFenVisTr,"Total or Average","-")
  ENDIF
  !counts
  CALL PreDefTableEntry(pdchSurfCntTot,'Wall',numSurfaces(SurfaceClass_Wall))
  CALL PreDefTableEntry(pdchSurfCntExt,'Wall',numExtSurfaces(SurfaceClass_Wall))
  CALL PreDefTableEntry(pdchSurfCntTot,'Floor',numSurfaces(SurfaceClass_Floor))
  CALL PreDefTableEntry(pdchSurfCntExt,'Floor',numExtSurfaces(SurfaceClass_Floor))
  CALL PreDefTableEntry(pdchSurfCntTot,'Roof',numSurfaces(SurfaceClass_Roof))
  CALL PreDefTableEntry(pdchSurfCntExt,'Roof',numExtSurfaces(SurfaceClass_Roof))
  CALL PreDefTableEntry(pdchSurfCntTot,'Internal Mass',numSurfaces(SurfaceClass_IntMass))
  CALL PreDefTableEntry(pdchSurfCntExt,'Internal Mass',numExtSurfaces(SurfaceClass_IntMass))
  CALL PreDefTableEntry(pdchSurfCntTot,'Building Detached Shading',numSurfaces(SurfaceClass_Detached_B))
  CALL PreDefTableEntry(pdchSurfCntExt,'Building Detached Shading',numExtSurfaces(SurfaceClass_Detached_B))
  CALL PreDefTableEntry(pdchSurfCntTot,'Fixed Detached Shading',numSurfaces(SurfaceClass_Detached_F))
  CALL PreDefTableEntry(pdchSurfCntExt,'Fixed Detached Shading',numExtSurfaces(SurfaceClass_Detached_F))
  CALL PreDefTableEntry(pdchSurfCntTot,'Window',numSurfaces(SurfaceClass_Window))
  CALL PreDefTableEntry(pdchSurfCntExt,'Window',numExtSurfaces(SurfaceClass_Window))
  CALL PreDefTableEntry(pdchSurfCntTot,'Door',numSurfaces(SurfaceClass_Door))
  CALL PreDefTableEntry(pdchSurfCntExt,'Door',numExtSurfaces(SurfaceClass_Door))
  CALL PreDefTableEntry(pdchSurfCntTot,'Glass Door',numSurfaces(SurfaceClass_GlassDoor))
  CALL PreDefTableEntry(pdchSurfCntExt,'Glass Door',numExtSurfaces(SurfaceClass_GlassDoor))
  CALL PreDefTableEntry(pdchSurfCntTot,'Shading',numSurfaces(SurfaceClass_Shading))
  CALL PreDefTableEntry(pdchSurfCntExt,'Shading',numExtSurfaces(SurfaceClass_Shading))
  CALL PreDefTableEntry(pdchSurfCntTot,'Overhang',numSurfaces(SurfaceClass_Overhang))
  CALL PreDefTableEntry(pdchSurfCntExt,'Overhang',numExtSurfaces(SurfaceClass_Overhang))
  CALL PreDefTableEntry(pdchSurfCntTot,'Fin',numSurfaces(SurfaceClass_Fin))
  CALL PreDefTableEntry(pdchSurfCntExt,'Fin',numExtSurfaces(SurfaceClass_Fin))
  CALL PreDefTableEntry(pdchSurfCntTot,'Tubular Daylighting Device Dome',numSurfaces(SurfaceClass_TDD_Dome))
  CALL PreDefTableEntry(pdchSurfCntExt,'Tubular Daylighting Device Dome',numExtSurfaces(SurfaceClass_TDD_Dome))
  CALL PreDefTableEntry(pdchSurfCntTot,'Tubular Daylighting Device Diffuser',numSurfaces(SurfaceClass_TDD_Diffuser))
  CALL PreDefTableEntry(pdchSurfCntExt,'Tubular Daylighting Device Diffuser',numExtSurfaces(SurfaceClass_TDD_Diffuser))
END SUBROUTINE GatherForPredefinedReport