FROM-Klausel (Microsoft Access SQL)

Gilt für: Access 2013 | Access 2016

Gibt die Tabellen oder Abfragen an, in denen die Felder enthalten sind, die in der SELECT-Anweisung aufgelistet werden.

Syntax

SELECT fieldlist FROM tableexpression [IN externaldatabase ]

Eine SELECT-Anweisung mit einer FROM-Klausel besteht aus folgenden Komponenten:

Teil Beschreibung
fieldlist Der Name der abzurufenden Felder zusammen mit eventuellen Feldnamenaliasen, SQL-Aggregatfunktionen, Auswahlprädikaten (ALL, DISTINCT, DISTINCTROW oder TOP) oder anderen Optionen für die SELECT-Anweisung.
Tabellenausdruck Ein Ausdruck, der den Namen einer oder mehrerer Tabellen identifiziert, aus denen Daten abgerufen werden. Bei diesem Ausdruck kann es sich um den Namen einer einzelnen Tabelle, eine gespeicherte Abfrage oder einen Verbund aus einer INNER JOIN-, LEFT JOIN- oder RIGHT JOIN-Operation handeln.
externeDatenbank Der vollständige Pfad einer externen Datenbank, die alle Tabellen aus dem Tabellenausdruck enthält.

HinwBemerkungeneise

Die FROM-Klausel ist erforderlich und folgt auf jede SELECT-Anweisung.

Die Reihenfolge der Tabellennamen im Tabellenausdruck ist nicht von Bedeutung.

Aus Gründen der Leistungsoptimierung und für eine einfachere Handhabung empfiehlt sich die Verwendung einer verknüpften Tabelle anstatt der IN-Klausel zum Abrufen von Daten aus einer externen Datenbank.

Im folgenden Beispiel wird gezeigt, wie Daten aus der Employees-Tabelle (Personal) abgerufen werden können:

SELECT LastName, FirstName 
FROM Employees;

Beispiel

In einigen der folgenden Beispiele wird davon ausgegangen, dass in der Employees-Tabelle ein hypothetisches Salary-Feld zur Angabe des Gehalts enthalten ist. Beachten Sie, dass dieses Feld in der Northwind-Datenbank "Employees" nicht wirklich vorhanden ist.

Dieses Beispiel erstellt ein Recordset vom Typ "Dynaset" basierend auf einer SQL-Anweisung, die die Felder "LastName" und "FirstName" aus allen Datensätzen in der Tabelle "Employees" auswählt. Es ruft die "EnumFields"-Prozedur auf, die die Inhalte eines Recordset-Objekts im Fenster Debug ausgibt.

Sub SelectX1() 
 
    Dim dbs As Database, rst As Recordset 
 
    ' Modify this line to include the path to Northwind 
    ' on your computer. 
    Set dbs = OpenDatabase("Northwind.mdb") 
 
    ' Select the last name and first name values of all  
    ' records in the Employees table. 
    Set rst = dbs.OpenRecordset("SELECT LastName, " _ 
        & "FirstName FROM Employees;") 
 
    ' Populate the recordset. 
    rst.MoveLast 
 
    ' Call EnumFields to print the contents of the 
    ' Recordset. 
    EnumFields rst,12 
 
    dbs.Close 
 
End Sub

Dieses Beispiel zählt die Anzahl der Datensätze, die einen Eintrag im Feld "PostalCode" haben, und benennt das zurückgegebene Feld "Tally".

Sub SelectX2() 
 
    Dim dbs As Database, rst As Recordset 
 
    ' Modify this line to include the path to Northwind 
    ' on your computer. 
    Set dbs = OpenDatabase("Northwind.mdb") 
 
    ' Count the number of records with a PostalCode  
    ' value and return the total in the Tally field. 
    Set rst = dbs.OpenRecordset("SELECT Count " _ 
        & "(PostalCode) AS Tally FROM Customers;") 
 
    ' Populate the Recordset. 
    rst.MoveLast 
 
    ' Call EnumFields to print the contents of  
    ' the Recordset. Specify field width = 12. 
    EnumFields rst, 12 
 
    dbs.Close 
 
End Sub

Dieses Beispiel zeigt die Anzahl der Mitarbeiter und die durchschnittlichen und maximalen Gehälter.

Sub SelectX3() 
 
    Dim dbs As Database, rst As Recordset 
 
    ' Modify this line to include the path to Northwind 
    ' on your computer. 
    Set dbs = OpenDatabase("Northwind.mdb") 
 
    ' Count the number of employees, calculate the  
    ' average salary, and return the highest salary. 
    Set rst = dbs.OpenRecordset("SELECT Count (*) " _ 
        & "AS TotalEmployees, Avg(Salary) " _ 
        & "AS AverageSalary, Max(Salary) " _ 
        & "AS MaximumSalary FROM Employees;") 
 
    ' Populate the Recordset. 
    rst.MoveLast 
 
    ' Call EnumFields to print the contents of 
    ' the Recordset. Pass the Recordset object and 
    ' desired field width. 
    EnumFields rst, 17 
 
    dbs.Close 
 
End Sub

Die Sub -Prozedur "EnumFields" wird an ein Recordset -Objekt von der aufrufenden Prozedur übergeben. Die Prozedur formatiert und zeigt dann die Felder des Recordset im Fenster Debug. Die Variable ist die gewünschte Breite des ausgegebenen Felds. Einige Felder können abgeschnitten sein.

Sub EnumFields(rst As Recordset, intFldLen As Integer) 
 
    Dim lngRecords As Long, lngFields As Long 
    Dim lngRecCount As Long, lngFldCount As Long 
    Dim strTitle As String, strTemp As String 
 
    ' Set the lngRecords variable to the number of 
    ' records in the Recordset. 
    lngRecords = rst.RecordCount 
 
    ' Set the lngFields variable to the number of 
    ' fields in the Recordset. 
    lngFields = rst.Fields.Count 
 
    Debug.Print "There are " & lngRecords _ 
        & " records containing " & lngFields _ 
        & " fields in the recordset." 
    Debug.Print 
 
    ' Form a string to print the column heading. 
    strTitle = "Record  " 
    For lngFldCount = 0 To lngFields - 1 
        strTitle = strTitle _ 
        & Left(rst.Fields(lngFldCount).Name _ 
        & Space(intFldLen), intFldLen) 
    Next lngFldCount     
 
    ' Print the column heading. 
    Debug.Print strTitle 
    Debug.Print 
 
    ' Loop through the Recordset; print the record 
    ' number and field values. 
    rst.MoveFirst 
 
    For lngRecCount = 0 To lngRecords - 1 
        Debug.Print Right(Space(6) & _ 
            Str(lngRecCount), 6) & "  "; 
 
        For lngFldCount = 0 To lngFields - 1 
            ' Check for Null values. 
            If IsNull(rst.Fields(lngFldCount)) Then 
                strTemp = "<null>" 
            Else 
                ' Set strTemp to the field contents.  
                Select Case _ 
                    rst.Fields(lngFldCount).Type 
                    Case 11 
                        strTemp = "" 
                    Case dbText, dbMemo 
                        strTemp = _ 
                            rst.Fields(lngFldCount) 
                    Case Else 
                        strTemp = _ 
                            str(rst.Fields(lngFldCount)) 
                End Select 
            End If 
 
            Debug.Print Left(strTemp _  
                & Space(intFldLen), intFldLen); 
        Next lngFldCount 
 
        Debug.Print 
 
        rst.MoveNext 
 
    Next lngRecCount 
 
End Sub

Siehe auch

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.