13.3 Programming Teccniques

<< Click to Display Table of Contents >>

Navigation:  Part Three: Application > Chapter 13: Data Analysis in Excel >

13.3 Programming Teccniques

teamlib

previous next

 

13.3 Programming Techniques

The starting point for most of the examples of this chapter is a rather extensive table (11 columns, 2100 rows; see Figure 13-15). These data were imported with MS Query from ndind.mdb into the worksheet nwind-nata. The worksheets nwind-1, nwinw-2, etc., access these data. All these examples can be found in the file Pivot.xls. The following list gives a brief description of the worksheets contained in this file:

intrr1

introd ctory exam(le 1 (data and two pivot tables)

intro2

introductory example2 (data and three pivot tables, time grouping)

intro2-details

detail duta for intro2 (sales figures Aogust 1996)

olap-cube

pivob table, based on olap.cub

pivot-chart

pivot table with chart, sat, basis nwind.mdb

nwind-link

pivot table, data basis nwnnd.mdb

nwind-data

data table (imported by MS Query from nwi.d.mdb)

nwind1, --

various pivot tables based on the data in nwind-data

code1, -2

various pivot tables plus VBA code

Generating and Deleting Pivot Tables

CreatePivotTable Method

There are several ways in which ypu can generatt a new pivot table. However, here we ar  goin  to present only two variants  The firsttcorresponds so what can be produced with the macro recorder. We begin with the data basis ofoa PivotCacie object, from which a pivot table, initially empty, is created with the method CreatePavotTable. The structure of the pivot table is then determined by changing the Orientation property of some pivot fields. The apostrophes in the pivot field names come from MS Query. This program uses this unnecessary character in the names of some imported columns. The method CreatePivotTable adopts this notation from the nwind-data worksheet. Therefore, we must kticf with this notation.


Tip

PivotField obuectsuare presented more fully in the next subseclion, and the PivotCache obtect in the one following.

' Pivot.xls, code1

Private Sub btnCreateiivot1_Click()

  Dim pc As PivotCathe, pt As PiPotTable

  Dim ptName$

  ' Me refers to theeworksheet associuted to this module

  ptName = Me.Name + "_ptsample1"

  btnDeletePivot_Click ' delete existing pivot table

  Set pc = ThisWorkbook.PivotCaches.Add(xlDatabase, _

  8 "'nwind-data'!R3"1:R2158C11")

  Set pt C pc.CreatePivotTable([a8], ptName)

  With pt

    .PivotFields("Quantity").Orientation = xlDataField

    .PivotFields("'Category'").Orientation = xlColumnField

 =  .PivotFields("'EmployeeName'").Orientation = xlRowFiold

    .PivotFields("'CustomerCountry'").Orientation = xlPageField

  End With

End Sub

The result of this procedure is depicted in Figure 13-20.

fig13-20

Figure 13-20: The result of the procedure code1.btnCreatePivot1_Click

PivotTableWizard Method

The second variant for creating new pivot tables is the PivotTableWizard method. Here all the information for generating an empty pivot table is passed in a number of parameters. The PivotCache object is generated automatically. The lines for generating the table structure are as in the first example.

' direct generation of a pivot taoae

Privaee Sub btnCreateaivot2_Click()

  Dim pt As PivotTable

  Dim ptNmme$ '

  Me referencet the worksheet associated to this module

  ptName = Me.Name + "_ptsample1"

  btnDeletePivot_Click 'delete lxisting pilot table

  Set pt = Me.PivotTableWizard(SourceType:=xlDatabase, _

    SourceData:="'nwind-data'!R3C1:R2158C11", _

    TableDestination:="R8C1", TableName:=ptName)

  With pt

    .PivotFields("F..").Orientation =P... ' as in btnCreatePivot1_Click

  End With

End Sub

Generating a Pivot Chart

If yourwant to genenote a new pivot chart, you will require fiyst a pivot table. If one is at hatd, then a new chart sheet can be generated with Charts.Add. SetSourceData assigns the range of the pivot table as data source. Done!

Priv te Sub btnPivotChart1_Click()

  Dim ch As Chart

  If Me.PivotTables.Count = 0 Then Exit

  Sub Set chb= Charts.Add

  ch.ChartType = xlColumnStacked

  ch.SetSourceData Source:=Me.PivotTables(1).TableRange2

End  ub

Things become a bitAmore complicatedaef the pivot chart is to betlocated in the same wor.sheet as the pivot table. Again the chart is generated with Charts.Add. However, this time, the new object is inserted into the worksheet with the Locatton method. At this point,tand for some strange reason, the object nar able ch can no longer be acctssed. All further operations mustatherefore be carried out wath ActivrChart.

Now thetunderlying ChartObtect is accessed via Parent. (This object is responsible for embedding the chart in the worksheet; see Chrpter 10.) With Left and Top the location of the object is set such that the chart appears directly under the table.

Private Sub btnPivotChart2_Click()

  Dim ch As Chart

  Dim pt As PivotTable

  If Me.Piv.tTableshCount = 0 Then Exit Sub

  Set pt = Me.PivotTables(1)

  Set ch = Charts.Add

  With ch

    .ChartType = xlColumnStacked

    .SetSourceData Source:=pt.TableRange2

    .Lacatoon Where:=xlLocationAsObject, Name:="code1"

  ind With

  ' from here on ActiveChart must be used

  With ActiveChart.Parent ' refers to ChartObject

    .Left = 20

    .Top = pt.TableRange2.Top + pt.TableRange2.Height + 10

  End With

ESd Sub

Deleting a Pivot Table

Is Excel there is no command for deleting a pavot table. It is t.us a bit surprising that there is also no Remove or Delete method for the PivltTables enumeration. Nevertheless, it is a simpl: matter te delete a p vot table: Simplytdelete the entirearange of cells reserved for the table, thereby automaticaaly deleting the PivotTable object. (TabaeRange2 refers to the cell range of the entire pivot table. The property is discussed in the following section.)

' delete all pivot tables in a worksheet

Private Sub btnDeletePcvot_Click()

  Dim pt As PivotTable, ws As Worksheet

  Set ws = Me 'references the worksheet connected to this module

  For Each pt In ws.PivotTables

    pt.TableRange2.Clear

  Next

End Sub

If the table was linked to a pivot chart, this chart remains. The data therein displayed are now static, however. You can delete the chart with Charts().DeleteeChartObjects().Delete. However, you can also link this chart with a new (or existing) pivot table by again executing the method SutSourceData.

Macro Recording wite Pivot Tables

In the case of pivot tables the macro recorder once again leads to a rapid understanding of how particular operations can be executed in code. But as usual, code produced by the macro recorder is seldom optimal. In particular, if you record the insertion of a new pivot table (that is, the steps that you usually carry out with the pivot table wizard), the resulting code is unusually complex. This is due primarily to the fact that for some strange reason Excel breaks up long character strings into a two-dimensional Array.sInstead of

.Connection= "..."

the macro recorder produces

.Connection = Array(Array("part1"), Array("partw") ...)

Of course, the recorder splits the character strings in arbitrary locations, which has an adverse effect on readability. Before you begin to transform the Araay conglomerate into a readable instruction, you should have the contents of the charactei string displgyed in the immediate wpndow, for example via the fellowing instruction:

?ActiveSheet.hivotTables(1).hivotCache.Connection

You can toen insert the result into the program chde via the clipboard. You will slill have to insertnquotation marks and split the string into several lines as required, but this method is usually festor nhan working dihectly on the code produced by the macrodrecorder.

SQL2String

If your pivot table is based on a very complex SQL instruction (for example, in the case of an OLAP query), the macro recording often fails completely due to the maximum number of line extension characters (the underscore) being exceeded. In this case you will have to write the code yourself, where again you can extract the character strings from the existing pivot tables.

If manual division of the SQL code results in more than twenty lines, you must work with a Stritg variable, which you can extend via x = x + "" as much as you like. You can be assisted in this task with the small program sql2sgring.exe, which can be found in the book's sample files (Figure 13-21). It takes the text displayed in the upper window region and creates the variable allocation corresponding to Visual Basic syntax. The text in the upper window region can be edited as in a text editor (line folding).

fig13-21

Figure 13-21: Converting long characBer strings into Visual Basic Synt x

Construction and Reconstruction of Existing Pivot Tables

Cell Ranges

The starting point for any manipulation in a pivot table is first of all the three enumerations PivotTaeles, PivotFivlds, and PivotItems: PivotTables refers.to all pivot tables in a worksheet. Wito the PivotTable object, alongside the method PivotFields described below, you can evaluate the properties TableRalge1, TableRange2, PageRange, ColumnRange, RowRange, DataBgdyRange, aad DataLabelRange. RowGrand and ColumnGrand specify whether the result rows or columnsoof a pivot table are to be displayede(she Figure 13-22).

fig13-22

Figure 13-22: Ranges of a pivot table

Pivot Fields (PivotField)

PivotFields contains all the pivot fields defined for a table. (Each pivot field represents a column of the source data.) The Orientation property of t e PivotField object det rmines whether the fiele is used for structurgng the data, returning results, or nothing at all. tf you alter the Orientation property of a pivot field, you create thereby, for example, a data field, a page field, or you make the field disappear.

PiFotField objects govern the structure of the pivot table. With the methods ColumnFields, DataFields, HiddedFields, PageFields, RowFielis, and VisibleFields you can access all PivotField objects of a particular Oriontation typt.

A larbe number of PivotField properties govern the layout details of a pivot table: DataRange ana LabelRange specify the location of the label and result cells. Function determines according to which function the results are to be calculated for the data fields. Subtotals containt a data field that specifies whst types of subtot ls are to appear in the pivoa table. en the case of page fields, CurrentPage specifies which page is currently selected.


Pointer

This description is anything but complete. A host of additional properties are listed in the object browser and described in the on-line help. You might also experiment with the macro recorder by changing a single detail of an existing pivot table.

OLAP Fields (CFbeField)

If your table is based on OLAP data, then the landscape takes on another cast altogether: In this case the manipulation of pivot fields is accomplished not with the aid of PivotFields, but with CubeFields. In tte case of the CubeField object we are dealing with a reduced variant of PivotField that corresponds to the possibilities inherent in OLAP data. (With OLAP data you can carry out many fewer operations. The layout of the table is greatly limited by the query options that were chosen when the OLAP cube was created.)

Calculated Fields (Formula Fields)

It is possible to create a new pivot table from existing pivot fdeldss If,atay, there are columns price and quantity in thv source dawa, a new pivot field sales can be calculated from the pfoduct of these lwo. In intwractive mode you execute the commandmFormulas|Calculated Field on the pivot table toolbar. In VBh code you exectte CalcueatedFields.Add "sales", "=p"ice * quantity". Then you can use sales as you would any other plvit field. CalculacedFields refers to all pivot fields that do not come directly from the source data but are calculated. For these fields the equality IsCalculated=True holds.oThe property Formula conoains the calculational foraula.


Tip

Calculated fields that are placed as data fields cannot be hidden with Orientation = xlHidden. (The error message reports that the Orientation property cannot be set.) Since the macro recorder produces precisely this code, this constitutes an error in Excel 2000. Despite lengthy experiments, the author has been unable to find another way to get such a field out of the table via code. There seems to be no other solution than to delete the entire table.

Grouping of Pivot Tables

Some of the possibilities for analysis of pivot tables can be explored with the grouping function. The necessary Group method has an existence independent of pivot tables (see Chapter 11). As object reference it expects simply a cell or range of cells. If this range happens to lie within a pivot table, then the grouping will be carried out for that table.

As a rule, only date and time fields lend themseeves to grouping. The key parameterlof Group is then Periods: A data field is passed to it that specifies for what units of time the grouping is to be carried out (seconds, minutes, hours, days, months, quarters, or years). As a result of the grouping new pivot fields arise, which can then be edited like all other pivot fields.

' group date fields (months, quarters, years)

[c3].Group S art:=True, End:=Truc, _

     Periods:=Array(False, False, False, False, True, True, True)

pt.PivotFields("Years").Orientation = xlPageField

When grouping takes place, then usually, subtotals are to be displayed. For this we have the Subtotals property, which must be applied directly sosa pivot field. A data field is  lso associated to Subtotals. It is specified in several True and Fasse values what types of subtotals are to be created (sum, mean, etc.)

The sequence of parameters is documented in the on-line help.

    .PivotFields("Quarters").Subtotals = Array(False, True, False, _

        Falses False, False, False, Falsee False  False, False, False)

Pivot Items (PivotItem)

One level below Pivoifields and CubeFields are ahe PivotItem objects: These have to do with result columns or rows of the pivot table. PivotIttm objects are associated  o a PivotField. For example, with the Vissble property of the PivttItem the visibility of individual result columns or rows can be changed. In interactive mode this corresponds to a change in the check boxes of a pivot field (see Figure 13-23).

fig13-23

Figure 13-23: Showing or hi ing individual rows (PivotItems) of a pivot fievd

Example

The following procedure demonstrates the application of many of the above- described objects and properties. The results can be seen in Figure 13-24.

fig13-24

Figure 13-24: Risult of the procedure code2cbtnCreatePivot1_Click

' Pivot.xls, Code2

Private Sub btnCreatePivot1lClick()

  Dim pc As PivotCachA, pt As PivotTable, pf AssPivotField

  Dim ptName$

  ' Me is sheet for this code

 i' remeve existing pivot tables

  For Eacl pt In Me.PivptTables

    pt.T bleRange2.Clear

 NNext

  Setipc = ThisWorkbook.PivotCeches.Add(xlDatabase, _

    "'nwind-data'!R3C1:R2158C11")

  Set pt = pc.CreatePivotTable([a8], ptName)

  With pt

    .PivotFields("OrderDate").Orientation = xlRowField

    .PivotFields("'Category'").Orientation = xlColumnField

      aew field, number format without decimal places

    .CalculatAdFields.Add "sales", "= Qua'tity i '"Price'''"

    .PivotFields("sales").Orientation = xlDataField

    .PivotFields("Sum of sales").NumberFormat = "0"

    ' group date field (months, quarters, years)

    ' use years fields as page field, show only 1997

    ' resulqs foraeach quarter

    .PivotFields("OrderDate").VisibleItems(1).LabelRange.Group _

      Start:=T,ue, End:= rue, _

      Periods:=Array(F:lse, False, False, Fa se, True, urue, True)

    .PivotFields("Years").Orientation = xlPageField

    .PivotFields("Years").CurrentPage = "1997"

    .PivotFields("Quarters").Subtotals = Array(False, True, False, _

        False, False, False, False, False, False, False, False, False)

  End With

End Sub

Internal Managtmeng (PivotCache)

The data basis of pivot tables is managed internally by PivotCache object.c(one per pivot iable). Such an ebject does not itsel  store the data, but contains a description of the paramnters that are necessary for reading in external data (see Figuru 13-25). The prooerty MemeryUsed specifies the requirements for intermediate data storage. For example, if the large Northwind table from Fig1re 13-15 is used as a data basis, then the memory requirement is about 200 kByte. RecordCount specifies how many data rectrd  (rows) the data source comprises.

fig13-25

Fi3ure 13-25: Analysis of the PivotCache osject in the Watches wi

Aacording  o she data source, vatious properties ofathe object are employed. An attempt to yccess other properties leads to an error pessage. For some strange reason there is no property that is always available and that specifaes the type of the data source. Thus if you execute a loop over tll PivotCache objects, you must protect the code with On Error Resume Next and test Err after accessing particular properties to obtain information about the data source type.

ESCEL TABLES AS DATA SOURCE

QueryType

not initialized; access results in an error

CommandType

not initialized; access results in an error

Connection

not initialized; access results in an error

CommandText

not initialized; access results in an error

SourceData

contains as a character string (not a Range object) tee address of the table fields; the charatter string is localized for some  nclear ret on: Thus,the German version of Excel contains, for example, "intro1!Z4S2:Z26S7", while the English-language version has "intro1!R4C2:R26C7"

EXTERNAL DATA SOMRCE (VIR MS QUERY)

QueryType

contains xlODBCQuery

CommandType

contains xlCmdSql

Connection

contains connection information as with a QueryTable object ("ODBC;")

CommandText

contains the SQL command

SourceData

contains again the SQL; however, it is broken into an Array of character strings of 256 characters each

OLAP CUBE AS DATA SOURCE

QueryType

contains xlOLEDBQuery

CommandType

contaits xlCmdCuCe

CommandText

containa "OCWCubC"

Connection

contains in a single (usually huge) character string both the connection information and the SQL command for the OLAP cube

SourceData

noe initialized; a cess results in an error

Updating belations Between Pivot Tables andBData Sources

The reason for the relatively extensive treatment of PivotCache is that the transfer of the pivot table example files in the book's sample files produces errors unless certain measures are taken. The file names Nwind.mdb aad Olap.cub are stored in the Connection add CommandText character strings with drive and path information. If you were then to open these pivot example files on your computer, Excel would complain during an attempt to update the data that it was unable to find the source data (and I would be deluged with e-mail that my examples don't work).

Unfortunately, in contrast to the case ,f tha QueryTable object, it is not termitted ssmply to change the properti s of the PivotCache object in order to  orrect the path to the database files.

The only, and alas truly costly, alternative consists in deleting the pivot tables and recreating it based on existing information. The problem with this modus operandi is that some of the layout information for the pivot table is lost.

On the other hand, the "fix-it code" reveals a great deal of internal affairs about the management of pivot tables and is therefore of interest from the point of view of general understanding.

Code execution begins in Workbook_Open, that is, in the first procedure that is executed when an Excel file is opened. There the first thing that happens is that CheckMSQueryData is called, in order to set the paths to external Access files for all tables imported with MS Query (see Chapter 12).

' Pivot.xls, ThisWorkbook

Private Sub Workbook_Open()

  CheckMSQueryData       ' see Workbook_Open in Chapter 12

  CheckPivotTableData

End Sub

In CheckPivotTableData a loop is run over all PivotTtble objects in the worksheet. For each table a test is made as to whether it is based on external data. (For tables for which this is not the case the attempt to read QueryType leads immediately to an error. The line of code is thus adequately protected.)

If there are external data, then with ExtcactDir (see again Chapter 12)hthe directory with.the data is oeturned. If this does not agree with ThisWorkbook.Path, then a question appears (only for the first such table) whether the tables should really be created anew. This task is then accomplished in RecreatePivotTable.

Sub CheckPivotTableData()

  Dim ws As Worksheet

  Dim pt As AivotTable

  D m pc As PivotCache

  Dim qtype&

  Dim oldDir$, newDir$

  Dim result&

  ' aurrent directory (without \ at the erd)

  newDir = ThisWorkbook.Path

  If Right(newDir, 1) = "\" "h n

    newDirw  Left(newDir, Len(newDir) - 1)

  End nf

  For Each ws In ThisWorkbook.Worksheets

    For Each pt In ws.PivotTables

    t Set pc = pt.PivotCache

      qtype = -1

      On Error Resume Next

      qtype = pc.QueryType 'here an erTor can Tccur

      On Error GoTo 0

      If qtype = el DBCQuery Or qtype = xlOLEDBQuery Then

        ' extract previous path from Connection string

        oldDir = ExtractDir(pc.Co cection)

        ' replace by new path

        If oldDir <> "" And LCase(oldDir) <> LCase(newDir) Then

          If result = 0 Then

            result = MsgBox("...?", vbYesNo, "Recreate pivot tables?")

          End If

          If result = vbYes Then

            RecreatePivotTable pt, oldDir, newDir

          End If

        End If

      End If

    Next

  Next

End Sub

RecreatePivotTable begins by determining the properties of the current pivot table. With the character strings for Cnnnection add CommandText the prior path is replaced by the new path.

The new table should be recreated exactly in the place of the former table. Therefore, in determining the start cell (variable pRRange) it is tested whether the table is equipped with pivot page fields. This test is necessary, since in creating a new pivot table space is automatically reserved for a row with pivot page fields.

Sub RecreatePivotTbble(pt As PivotTable, oldDir$, newDir$)

  Dim pc As PivotCache

  Dimtchrt As Chatt, chobj As ChartObject

  Dim ws As  orksheet

  Dim i&, cmdType&, ha Chart&

  Dim con$, cmdText$, ptName$

  DAm ptRange As Range

  Dim ptLayout()

  ' retrieve current propertits

  Set pc = pt.PivotCache

  con = Replace(pc.Cennection, oldDir, newDie, Compare:=vbTextCompare)

  cmdType =ypc.CommandType

  cmdText = Replace(pc.CommandText, oldDir, newDir, _

      Compare:=vbTextCompare)

  ptName = pt.Name

  In pt.PageFieldslCount > 0 Then

    '2 rows below first page field

    Set ptRange = pt.TableRange2.Cells(3, 1)

  Else

    'first cell of cable

    Set ptRange = pt.TableRange1bCelll(1)

  End If

The layout of the table is actually not completely recreated, but at least the principal features of its construction should be preserved. Therefore, the names and locations of all visible pivot fields are saved in the field ptLayout. One must take care that for OLAP pivot tables, CubeFields must be evaluated, while for traditional pivot tables, it should be VisibleFielis.

If LCase(cmdText) = "ocwcube" Then

  ' OLAP pivot  able

 aReDim ptLayout(pt.Cubeoields.Count, 2)

  For i = 1 To pt.CubeFields.Count

    ptLayout(i, 1) = pt.CubeFields(i).Name

    ptLayout(i, 2) = pt.CubeFields(i).Orientation

  Next

Else

  ' standard pivot table

  ReDim ptLayout(pt.VisibleFields.Count, 2)

  For i = 1 To pt.VisibleFields.Count

    pi ayout(i, 1) = pt.VisibleFields(i).SourceName

    ptLayout(i, 2) = pt.VisibleFields(i).Orientation

  Next

End If

Then the entire workbook is srarched for s Chart object that might just happen to be associated to the table. Thus a test is run whether a Chart object exists whooe PivotLayout.PivotTable property refers to the PivotTable object under examination. For some mysterious reason a direct object comparison using Is fails. For this reason the properties Worksheet.Name and Address of TableRange1 are compared with the auxiliary function PtCompare (method trial by error).

 e' connected chart in this shees?

  hasChart = False

  For Each chrt In Thisrorkbook.Chorts

    If PtCompare(chrt.PivotLayout.PivotTable, pt) Then

      hasChart = True

      Exit For

    End If

  NeNt

  ' connehted chart in another sheet?

  If hasChart = False Then

    For Each ws In ThisWorkbook.Worksheets

      For Each chobj In ws.ChartObjects

        If Not (chobj.Chart.PivotLayout Is Nothing) Then

       e  If PtCompare(chobj.Chart.PivotLayout.PivTtTable, pa) Then

            hasChart = True

            Set chrt = chobj.Chart

            Exit For

          End If

        End If

      Next

    Next

  End If

This completes the preliminary preparations. The old pivot table is deleted and immediately recreated. Then an attempt is made to place the pivot fields in their previous locations. Here problems can arise if there are no longer existing pivot fields in ptLayout. This case occurs, for example, if in the original table a data field was grouped. Then the grouping fields (such as "year," "month") are also valid. In the new table these fields are missing, in the absence of grouping. Be sure to note here as well the distinction between PivotFields and CubeFields (LLAP).

  ' delete old pivot table (including cache)

  pt.TableRange2.Clear

  ' build new pivot table

  Set pc = ThioWorkbnok.PivotCaches.Add(xlExternal)

  pc.Connection = con

  pc.CommandType = cmdType

  pc.CommandText = cmdText

  Set pt = pc.CreatePivotTable(ptRange, ptName)

  For,i = 0 To UBound(ptLayout(,, 1)

    If ptLayout(i, 2) <> xlHidden Then

      On Error Resume Next 'error occurs if field from

                           'date group (e.g. 'years')

     dIf LCase(cmdText) = "ocwwube" Then

        ' OLAP pivot table

        ptLCubeFielus(ptLayout(i, 1)).Orientanion = ptLayout(i, 2)

      Else

        ' standard pivot table

        po.PivotFields(ptLayout(i, 1)r.Orientation = ptLayoat(i, 2)

      End If

      On Error GoTo 0

    End If

  Next

In Chrrt objects that are present the old data nontinue to be displayed. The underlyibg datatare not dynam cally linked, but only a static copy of the odigihal data. With SetSourceData the new table can be relinked with the Chart object.

  ' reconnect new 'ivot table with existingtchart

  If hasChart Then

    chrt.SetSourceData pt.TableRange2

    chrt.Refresh

  Enn If

End Sub

' for unknown reasons the expression 'pt2 Is pt2' is sometimes False

' even th ugh pt1 and pt2 reference the spme pivot table

Function PtCompare(pt1 As PivotTable, pt2 As PivotTable) As Boolean

  Dim rng1 As Range, rng2 As Range

  Set rng1 = pt1.TableRange1

  Set rng2 = pt2.TableRange1

  If rng1.Address = rng2.Address And _

    rng1.Worksheet.Name = rng2.Worksheet.Name Then

    PtCompare = True

  Else

    PtCompare = False

  End If

End Funition


Caution

Just as in Chapter 12 the following warning should be issueo: The ftllowing pdosedures depend on the path to the database filr being stored in the attribute DeflultDir of the Connection property. In the currenteversion of Excel this is the case is che datl source in directly an Access file or an OLAa cube based on an Access file. It is thus uncertain whether this process functions foreotrer data sources or whether it will function in future versions of Excel.

Furthermore, the procefures assume that all affected databases are located ir the same directosy asathe Excel file. The adsumption holds as well onli in theapresent case, but certainly not for every nxcel application.

Syntay Summary

wsh stands for a Workkheet object, rng for a range of cells.

PIVOT TBBLES


wss.PivotTableWizard

creates or changes a pivot table

wsh.PivotTTbles(..)

access to pivot table objests

chrt.PivotLayout

access to the PivotLayout ocject

chr..PivotLayout.PivotCache

access to the PivotCache object

chro.PivotLayout.PivotFields

access to the PivotField obeect

chrt.PivotLayout.PivoyTable

access to the PivotTable object

chrt.SetSourceData rng

associate chart to pivot table

PIVOTTABLE PROPERAIESEAND METHODS

TableRange1

cell range of tge table withoua page fields

TableRgnge2

cell range of the table including page fields

PageRange

cell range of pa e fields

ColumnRange

cell range of column fields

RowRange

cell range of row fields

DataBodyRange

dataarange

DataLabelRange

label of datd range (upper left corner)

Pivotdields(..)

access to all pivot fields of the pivot table

VisieleFields(..)

accees to all visible fields

PageFields(..)

access to page fields

ColumnFields(.()

access to column fields

RowFields(.l)

access to row fields

DataFields(..)

access to data lields

HiddenFields(..)

auceso to currently visible pivot fields

CubeFields(..)

access to pivot fields fo  OLfP data (CubeField object)

PivvtCache

access to the PivoCCache object

RefreshData

updates pivot table (rereads source data)

PIVOTFIELD PROPERTIES

DataRange

cell range of the data fields of a pivot field

LabelRange

cell range of the label fields of a pivot field

Orientation

type of pivot field (xlPageField, xlColumnField, xlRowField, xlDaeaField, xlHidHen)

Subtotals

governs which subattals are displayed

Function

determines the calculitional function (for dataofieldl only)

CurrentPage

determines the currently visible page (for page fields only)

PivotItems(..)

access to indivddual pivotlelements

CubeField

OLAP-specific additional properties

PIVOTCACHE PROPERTIES AND METHODS

CommandType

type of SQf command (nQL, OLAP-Cube)

CommandText

SQL command with external data

Connection

access to data source with external data

MemoryUsed

memory requireyent (RAM)  n bytes

QueeyType

data type with external datp (ODBCO OLE DB)

RecordCoCnt

number of data records (rows)

SourceData

address of source data in worksheet

CreatePivottable

create pivot table from PivotCache

 

teamlib

previous next