共用方式為


Excel) (PivotCache.CreatePivotTable 方法

建立一個以 PivotCache 物件為基礎的樞紐分析表。 會傳回 PivotTable 物件。

語法

運算式CreatePivotTable (TableDestinationTableNameReadDataDefaultVersion)

表達 代表 PivotCache 物件的變數。

參數

名稱 必要/選用 資料類型 描述
TableDestination 必要 Variant 樞紐分析表目的地範圍左上角的儲存格 (工作表上將產生的樞紐分析表放置) 範圍。 目的範圍必須位於活頁簿的工作表中 (此活頁簿應包含由 expression 所指定的 PivotCache 物件)。
TableName 選用 Variant 新的資料樞紐分析表的名稱。
ReadData 選用 Variant True 是表示 建立包含外部資料庫中所有記錄的樞紐分析表快取;這個快取可能非常大。 False,允許在實際讀取資料前將部分欄位設定為伺服器型態的頁面欄位。
DefaultVersion 選用 Variant 樞紐分析表的預設版本。

傳回值

樞紐分析表

註解

如需根據樞紐分析表快取建立樞紐分析表的替代方式,請參閱樞紐分析表物件的Add方法。

範例

此範例會根據 OLAP 提供者建立新的樞紐分析表快取,然後根據使用中工作表上 A3 儲存格的快取建立新的樞紐分析表報表。

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

此範例會使用 Microsoft Jet 的 ADO 連線來建立新的樞紐分析表快取,然後根據使用中工作表上 A3 儲存格的快取建立新的樞紐分析表報表。

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

此範例使用現有的 WorkbookConnection。

 
 '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
 
 

支援和意見反應

有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應