Share via


PivotCache.CreatePivotTable-Methode (Excel)

Erstellt einen PivotTable-Bericht basierend auf einem PivotCache-Objekt . Gibt ein PivotTable -Objekt zurück.

Syntax

Ausdruck. CreatePivotTable (TableDestination, TableName, ReadData, DefaultVersion)

Ausdruck Eine Variable, die ein PivotCache-Objekt darstellt.

Parameter

Name Erforderlich/Optional Datentyp Beschreibung
TableDestination Erforderlich Variant Die Zelle in der linken oberen Ecke des Zielbereichs des PivotTable-Berichts (der Bereich auf dem Arbeitsblatt, in dem der resultierende PivotTable-Bericht platziert wird). Der Zielbereich muss sich auf einem Arbeitsblatt in der Arbeitsmappe befinden, das das pivotCache-Objekt enthält, das durch expression angegeben wird.
TableName Optional Variant Der Name des neuen PivotTable-Berichts.
Readdata Optional Variant True , um einen PivotTable-Cache zu erstellen, der alle Datensätze aus der externen Datenbank enthält. Dieser Cache kann sehr groß sein. Mit False werden einige Felder als serverbasierte Seitenfelder festgelegt, bevor die Daten gelesen werden.
DefaultVersion Optional Variant Die Standardversion des PivotTable-Berichts.

Rückgabewert

PivotTable

HinwBemerkungeneise

Eine alternative Möglichkeit zum Erstellen eines PivotTable-Berichts basierend auf einem PivotTable-Cache finden Sie unter der Add-Methode des PivotTables-Objekts .

Beispiel

In diesem Beispiel wird ein neuer PivotTable-Cache basierend auf einem OLAP-Anbieter und anschließend ein neuer PivotTable-Bericht erstellt, der auf dem Cache in Zelle A3 des aktiven Arbeitsblatts basiert.

With ActiveWorkbook.PivotCaches.Add(SourceType:=xlExternal) 
 .Connection = _ 
 "OLEDB;Provider=MSOLAP;Location=srvdata;Initial Catalog=National" 
 .CommandType = xlCmdCube 
 .CommandText = Array("Sales") 
 .MaintainConnection = True 
 .CreatePivotTable TableDestination:=Range("A3"), _ 
 TableName:= "PivotTable1" 
End With 
With ActiveSheet.PivotTables("PivotTable1") 
 .SmallGrid = False 
 .PivotCache.RefreshPeriod = 0 
 With .CubeFields("[state]") 
 .Orientation = xlColumnField 
 .Position = 1 
 End With 
 With .CubeFields("[Measures].[Count Of au_id]") 
 .Orientation = xlDataField 
 .Position = 1 
 End With 
End With

In diesem Beispiel wird ein neuer PivotTable-Cache mithilfe einer ADO-Verbindung mit Microsoft Jet erstellt. Anschließend wird ein neuer PivotTable-Bericht erstellt, der auf dem Cache in Zelle A3 des aktiven Arbeitsblatts basiert.

Dim cnnConn As ADODB.Connection 
Dim rstRecordset As ADODB.Recordset 
Dim cmdCommand As ADODB.Command 
 
' Open the connection. 
Set cnnConn = New ADODB.Connection 
With cnnConn 
 .ConnectionString = _ 
 "Provider=Microsoft.Jet.OLEDB.4.0" 
 .Open "C:\perfdate\record.mdb" 
End With 
 
' Set the command text. 
Set cmdCommand = New ADODB.Command 
Set cmdCommand.ActiveConnection = cnnConn 
With cmdCommand 
 .CommandText = "Select Speed, Pressure, Time From DynoRun" 
 .CommandType = adCmdText 
 .Execute 
End With 
 
' Open the recordset. 
Set rstRecordset = New ADODB.Recordset 
Set rstRecordset.ActiveConnection = cnnConn 
rstRecordset.Open cmdCommand 
 
' Create a PivotTable cache and report. 
Set objPivotCache = ActiveWorkbook.PivotCaches.Add( _ 
 SourceType:=xlExternal) 
Set objPivotCache.Recordset = rstRecordset 
With objPivotCache 
 .CreatePivotTable TableDestination:=Range("A3"), _ 
 TableName:="Performance" 
End With 
 
With ActiveSheet.PivotTables("Performance") 
 .SmallGrid = False 
 With .PivotFields("Pressure") 
 .Orientation = xlRowField 
 .Position = 1 
 End With 
 With .PivotFields("Speed") 
 .Orientation = xlColumnField 
 .Position = 1 
 End With 
 With .PivotFields("Time") 
 .Orientation = xlDataField 
 .Position = 1 
 End With 
End With 
 
' Close the connections and clean up. 
cnnConn.Close 
Set cmdCommand = Nothing 
Set rstRecordSet = Nothing 
Set cnnConn = Nothing

In diesem Beispiel wird bereits vorhandene WorkbookConnection verwendet.

 
 'Get WorkbookConnection object
 Dim conn As WorkbookConnection
 Set conn =  ActiveWorkbook.Connections("MyConnectionName")
 
 'Declare temp variables
 Dim connStr As String
 Dim sqlStr As String
 
 'Store connection string and command text in variables depends on connection type
 If conn.Type = xlConnectionTypeODBC Then
   connStr = conn.ODBCConnection.Connection
   sqlStr = conn.ODBCConnection.CommandText
 End If
  
 If conn.Type = xlConnectionTypeOLEDB Then
   connStr = conn.OLEDBConnection.Connection
   sqlStr = conn.OLEDBConnection.CommandText
 End If
 
 'Create PivotCache
 Dim pcache As pivotCache
 Set pcache = ActiveWorkbook.PivotCaches.Create(xlExternal, conn)
 
 'Then we need to get recordset to create pivot table
 Dim adodb_conn As Object
 Dim rs As Object
 Set adodb_conn = CreateObject("ADODB.Connection")
 Set rs = CreateObject("ADODB.Recordset")
 adodb_conn.Open connStr
 rs.Open sqlStr, adodb_conn
 
 Set pcache.Recordset = rs
 'When CreatePivotTable method called the linked WorkbookConnection is losing connection string and command text
 Set pvt = pcache.CreatePivotTable(TableDestination:=Sheets("MySheetName").Cells(1, 1), TableName:="MyPivotTableName")
        
 rs.Close
 adodb_conn.Close
 
 'Restore CommandText and connection string
 pcache.CommandText = sqlStr
 pcache.Connection = connStr
 
 ' Now you have PivotTable that linked with yours WorkbookConnection
 
 

Support und Feedback

Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.