User Tools

Site Tools


vba:access:classes:xlsxeporter_101

[VBA][Access] XlsxExporter 1.0.1

Exporter MS Access nach Excel. Die Einfache Version.

Version 1.0.1 18.01.2015
Die Klasse hat versteckte Attribute. Damit diese aktiv übernommen werden reicht es nicht aus, den Code in ein neues Modul zu kopieren. Man muss das Modul aus der Datei nach VBA importieren.
Bild zum Import

Download xlsxexporter_101.cls (V-1.0.1)

Eine kleine Klasse um schnell Daten aus Access nach Excel zu exportieren. Sie bietet die Möglichkeit, dann gleich noch einige Excel-Formatierungen durchzuführen.

Die neue, ausgebaute und komplexere Version findest du hier: xlsxexporter

Referenzen

Im VBA musss eine Referenz auf 'MicrosoftExcel XY ObjectLibrary' gesetzt sein

Definitionen

Genauere Doumentaion folgt

Wird das Objekt terminiert, wird automatisch die Methode quit() ausgeführt. Die Änderungen werden dabei gespeichert und die internen Objekte (Excel-Instance,Workbook etc.) geschlossen und abgebaut.

Enumerator

xeParams

Diekombinierbaren Parameter für den Export Die Parameter können kompiniert werden. zB. xeReplaceExistFile+xeHasFieldNames

Public Enum xeParams
    xeNone = 0                  'Kein Parameter
    xeReplaceExistFile = 2 ^ 0  'Falls die Exportdatei bereits exisitert, kann diese ersetzt werden
    xeHasFieldNames = 2 ^ 1     'Feldnamen werden in die erste Zeile geschrieben
End Enum

Methoden

export()

object.export(source, filepath [,spreadsheettype [,params]])
Public Sub export( _
        ByRef iSource As Variant, _
        ByVal iFilePath As String, _
        Optional ByVal iSpreadSheetType As AcSpreadSheetType = acSpreadsheetTypeExcel12Xml, _
        Optional ByVal iParams As xeParams = xeReplaceExistFile + xeHasFieldNames _
)
  • iSource Quelle. Tabellenname oder View-Name oder SQL-String
  • iFilePath Export-Pfad. Pfad zur Datei dieerstellt werdn soll.
  • iSpreadSheetType Excel-Format. Typ des Spreadsheets. Standart: Excel-12 XML
  • iParams Parameters. verscheidene Parameter. Siehe Enumerator xeParams

Mit export()exportiert man eine Quelle in ein Excel-Sheet

instance()

Set object = XlsExporter.instance(source, filepath [,spreadsheettype [,params]])
Set object = XlsExporter(source, filepath [,spreadsheettype [,params]])

Eine neue Instanz der Klasse wird angelegt und der Export wird durchgeführt.

Die Parameter entsprechen denen der Methode export()

Die Methode instance() hat das versteckte Attribut Attribute instance.VB_UserMemId = 0. Dadurch lässt sie sich direkt aus der Klasse ausführen.

quit()

object.quit [save Yes/No]

Speicher das offene Workbook und schliesst die Datei und die Excelinstanz

Properties

range

range = object.range([Cell1 [,Cell2]])
range = object.sheet.range([Cell1 [,Cell2]])

Mit dem range-Property greifft man direkt auf das Worksheet mit den exporetierten Daten zu. Der Aufruf ist analog zu Excel. Mit dem Range kann man direkt Formatierungen etc. analog zu Excel-VBA im Excelsheet durchführen. Es ist identisch wie das .sheet.range. Aber da man den Range am meisten braucht, habe ich ihn extra hinzugefügt

sheet

sheet = object.sheet

Das sheet-Property gibt eine Referenz auf das Worksheet. Damit lassen sich ganz normale Worksheetbefehle absetzen


Beispiele

Erste Zeile und erste Spalte Fett setzen.

Dim exp As new XlsxExporter
exp.export "my_table", "c:\temp\__tt.xlsx"
exp.range("1:1").Font.Bold = True
exp.range("A:A").Font.Bold = True
exp.quit
Set exp=Nothing

Analog aber ohne feste Variablenzuordnung Da das Objekt nur temporär geöffnet ist (ist keiner Variable zugewiesen), wird am Ende des With das Objekt zerstört und somit quit() ausgeführt. Das muss also nicht expliziet gemacht werden

With XlsxExporter("my_table", "c:\temp\__tt.xlsx")
    .range("1:1").Font.Bold = True
    .range("A:A").Font.Bold = True
End With

Wenn man nur die Titelzeile formatieren will, gehts natrülich noch kürzer

XlsxExporter("my_table", "c:\temp\__tt.xlsx").range("1:1").Font.Bold = True

Code

xlsxexporter_101.cls
VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "XlsxExporter"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
'-------------------------------------------------------------------------------
'File         : XlsxExporter.cls
'               Copyright mpl by ERB software
'               All rights reserved
'               http://wiki.yaslaw.info/dokuwiki/doku.php/vba/access/xlsxexporter
'Environment  : VBA 2007+
'Required     : Referenz auf 'MicrosoftExcel XY ObjectLibrary'
'Version      : 1.0.1
'Name         : XlsxExporter
'Author       : Stefan Erb (ERS)
'History      : 27.01.2015 - ERS - Creation
'               28.01.2015 - ERS - Property Get sheet auf Public gewechselt
'-------------------------------------------------------------------------------
 
'-------------------------------------------------------------------------------
' Example:
' Datei Exportieren und die Erste Zeile Fett setzen
'   Public Sub exp()
'       With XlsxExporter("my_table", "c:\temp\__tt.xlsx")
'           .range("1:1").Font.Bold = True
'       End With
'   End Sub
'-------------------------------------------------------------------------------
Option Explicit
 
'-------------------------------------------------------------------------------
' -- Public Members
'-------------------------------------------------------------------------------
Public Enum xeParams
    xeNone = 0                  'Kein Parameter
    xeReplaceExistFile = 2 ^ 0  'Falls die Exportdatei bereits exisitert, kann diese ersetzt werden
    xeHasFieldNames = 2 ^ 1     'Feldnamen werden in die erste Zeile geschrieben
End Enum
 
'-------------------------------------------------------------------------------
' -- Public Members
'-------------------------------------------------------------------------------
Private pFilePath    As String
Private pSource     As String
Private pXlsx       As Excel.application
Private pWb         As Excel.Workbook
Private pSheet      As Excel.Worksheet
Private pParams     As xeParams
 
'-------------------------------------------------------------------------------
' -- Public Methodes
'-------------------------------------------------------------------------------
'/**
' * Exportiert die Quelle in eine Excel-Datei und gibt eine Instance dieser Klasse zurück
' * @param  Variant             Quelle
' * @param  String              Export-Pfad
' * @param  AcSpreadSheetType   Excel-Format
' * @param  iParams             Parameters
' */
Public Function instance( _
        ByVal iSource As String, _
        ByVal iFilePath As String, _
        Optional ByVal iSpreadSheetType As AcSpreadSheetType = acSpreadsheetTypeExcel12Xml, _
        Optional ByVal iParams As xeParams = xeReplaceExistFile + xeHasFieldNames _
) As XlsxExporter
Attribute instance.VB_UserMemId = 0
'Attribute instance.VB_UserMemId = 0
    Set instance = New XlsxExporter
    instance.export iSource, iFilePath, iSpreadSheetType, iParams
End Function
 
'/**
' * Exportiert die Quelle in eine Excel-Datei
' * @param  Variant             Quelle
' * @param  String              Export-Pfad
' * @param  AcSpreadSheetType   Excel-Format
' * @param  iParams             Parameters
' */
Public Sub export( _
        ByRef iSource As Variant, _
        ByVal iFilePath As String, _
        Optional ByVal iSpreadSheetType As AcSpreadSheetType = acSpreadsheetTypeExcel12Xml, _
        Optional ByVal iParams As xeParams = xeReplaceExistFile + xeHasFieldNames _
)
    pFilePath = iFilePath
    pSource = iSource
    pParams = iParams
    If (pParams And xeReplaceExistFile) And cFso.FileExists(pFilePath) Then cFso.DeleteFile (pFilePath)
    DoCmd.TransferSpreadsheet acExport, iSpreadSheetType, pSource, pFilePath, (pParams And xeHasFieldNames)
End Sub
 
'/**
' * Seichert und schliesst die Datei
' * Diese Methode wird beim Abbauen des Objektes ebenfalls ausgeführt
' * @param  Boolean     Flag ob gespeichert werden soll
' */
Public Sub quit(Optional ByVal iSave As Boolean = True)
    wb.Close iSave: Set wb = Nothing
    xlsx.quit:      Set xlsx = Nothing
End Sub
 
'-------------------------------------------------------------------------------
' -- Public Properties
'-------------------------------------------------------------------------------
 
'/**
' * gibt ein Range des Sheetes zurück
' * @params Analog zu Range() in Excel
' * @return Range
' */
Public Property Get range(ByRef iCell1 As Variant, Optional ByRef iCell2 As Variant = Null) As Excel.range
    If IsNull(iCell2) Then
        Set range = sheet.range(iCell1)
    Else
        Set range = sheet.range(iCell1, iCell2)
    End If
End Property
 
'/**
' * Das Worksheet mit den exportierten Daten
' */
Public Property Get sheet() As Excel.Worksheet
    If pSheet Is Nothing Then Set pSheet = wb.Worksheets(pSource)
    Set sheet = pSheet
End Property
 
'-------------------------------------------------------------------------------
' -- Private Properties
'-------------------------------------------------------------------------------
 
'/**
' * DieExcel-Instance
' */
Private Property Get xlsx() As Excel.application
    If pXlsx Is Nothing Then Set pXlsx = New Excel.application
    Set xlsx = pXlsx
End Property
Private Property Set xlsx(ByRef iXlsx As Excel.application)
    Set pXlsx = iXlsx
End Property
 
'/**
' * Das Workbook mitden Exportierten Daten
' */
Private Property Get wb() As Excel.Workbook
    If pWb Is Nothing Then Set pWb = xlsx.Workbooks.Open(pFilePath)
    Set wb = pWb
End Property
Private Property Set wb(ByRef iWb As Excel.Workbook)
    Set pWb = iWb
End Property
 
'/**
' * Das Worksheet mit den exportierten Daten
' * Det Getter ist in den Public Properties
' */
Private Property Set sheet(ByRef iSheet As Excel.Worksheet)
    Set pSheet = iSheet
End Property
 
'-------------------------------------------------------------------------------
' -- Private Event
'-------------------------------------------------------------------------------
Private Sub Class_Terminate()
    If Not pWb Is Nothing Then quit
End Sub
 
'-------------------------------------------------------------------------------
' -- Private Libraries
'-------------------------------------------------------------------------------
 
'/**
' * Gibt ein FileSystemObject zurück
' * @return FileSystemObject
' */
Private Property Get cFso() As Object
    Static cachedObj As Object
    If cachedObj Is Nothing Then Set cachedObj = CreateObject("Scripting.FileSystemObject")
    Set cFso = cachedObj
End Property
 
vba/access/classes/xlsxeporter_101.txt · Last modified: 29.04.2015 12:46:40 by yaslaw