259
Addressing Issues with Two or More Data Fields
always done at the summary level. If you define a calculated field for average price as
Revenue divided by Units Sold, Excel first adds the total revenue and total quantity, and
then it does the division of these totals to get the result. In many cases, this is exactly what
you need. If your calculation does not follow the associative law of mathematics, it might
not work as you expect.
To set up a calculated field, use the
Add method with the CalculatedFields object. You have
to specify a field name and a formula. Note that if you create a field called Average Price,
the default pivot table produces a field called Sum of Average Price. This title is misleading
and downright silly. What you have is actually the average of the sums of prices. The solu-
tion is to use the
Name property when defining the data field to replace Sum of Average Price
with something such as Avg Price. Note that this name must be different from the name for
the calculated field.
Listing 11.4 produces the report shown in Figure 11.14.
Listing 11.4 Code That Calculates an Average Price Field as a Second Data Field
Sub TwoDataFields()
‘ Listing 11.4
Dim WSD As Worksheet
Dim PTCache As PivotCache
Dim PT As PivotTable
Dim PRange As Range
Dim FinalRow As Long
Set WSD = Worksheets(“PivotTable”)
Dim WSR As Worksheet
Dim WBO As Workbook
Dim WBN As Workbook
Set WBO = ActiveWorkbook
‘ Delete any prior pivot tables
For Each PT In WSD.PivotTables
PT.TableRange2.Clear
Next PT
WSD.Range(“R1:AZ1”).EntireColumn.Clear
‘ Define input area and set up a Pivot Cache
FinalRow = WSD.Cells(Rows.Count, 1).End(xlUp).Row
FinalCol = WSD.Cells(1, Columns.Count). _
End(xlToLeft).Column
Set PRange = WSD.Cells(1, 1).Resize(FinalRow, FinalCol)
Set PTCache = ActiveWorkbook.PivotCaches.Add(SourceType:= _
xlDatabase, SourceData:=PRange.Address)
‘ Create the Pivot Table from the Pivot Cache
Set PT = PTCache.CreatePivotTable(TableDestination:=WSD. _
Cells(2, FinalCol + 2), TableName:=”PivotTable1”)
‘ Turn off updating while building the table
PT.ManualUpdate = True
11
continues
12_0789736012_CH11.qxd 12/11/06 6:26 PM Page 259