Método PivotCache.CreatePivotTable (Excel)

Cria um relatório de tabela dinâmica baseado em um objeto PivotCache. Retorna um objeto de Tabela Dinâmica .

Sintaxe

expressão. CreatePivotTable (TableDestination, TableName, ReadData, DefaultVersion)

Expressão Uma variável que representa um objeto PivotCache .

Parâmetros

Nome Obrigatório/Opcional Tipo de dados Descrição
TableDestination Obrigatório Variantes A célula no canto superior esquerdo do intervalo de destino do relatório de Tabela Dinâmica (o intervalo na planilha em que o relatório de Tabela Dinâmica resultante será colocado). O intervalo de destino deve estar em uma planilha na pasta de trabalho que contém o objeto PivotCache especificado pela expressão.
TableName Opcional Variantes O nome do novo relatório de tabela dinâmica.
Readdata Opcional Variantes True para criar um cache de Tabela Dinâmica que contém todos os registros do banco de dados externo; esse cache pode ser muito grande. False para habilitar a configuração de alguns dos campos como campos de página com base em servidor antes dos dados serem lidos.
DefaultVersion Opcional Variantes A versão padrão do relatório de tabela dinâmica.

Valor de retorno

PivotTable

Comentários

Para obter uma maneira alternativa de criar um relatório de Tabela Dinâmica com base em um cache de Tabela Dinâmica, consulte o método Adicionar do objeto Tabela Dinâmica .

Exemplo

Este exemplo cria um novo cache de Tabela Dinâmica com base em um provedor OLAP e cria um novo relatório de Tabela Dinâmica com base no cache na célula A3 na planilha ativa.

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

Este exemplo cria um novo cache de Tabela Dinâmica usando uma conexão ADO com o Microsoft Jet e cria um novo relatório de Tabela Dinâmica com base no cache na célula A3 na planilha ativa.

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

Este exemplo usa a WorkbookConnection já existente.

 
 '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
 
 

Suporte e comentários

Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.