FROM 子句 (Microsoft Access SQL)

适用于:Access 2013 | Access 2016

指定包含 SELECT 语句中所列字段的表或查询。

语法

SELECT fieldlist FROM tableexpression [IN externaldatabase ]

包含 FROM 子句的 SELECT 语句具有以下部分:

Part 说明
fieldlist 要检索的字段的名称,以及任何字段名别名、SQL 聚合函数、选择谓词(ALL、DISTINCT、DISTINCTROW 或 TOP)或其他 SELECT 语句选项。
tableexpression 一个表达式,标识从中检索数据的一个或多个表。 该表达式可以是单个表名、保存的查询名、或者是 INNER JOINLEFT JOINRIGHT JOIN 产生的组合结果。
externaldatabase 包含 tableexpression 中的所有表的外部数据库的完整路径。

备注

FROM 是必需的,可跟任何 SELECT 语句后面。

tableexpression 中,表名称的顺序无关紧要。

为了提高性能和便于使用,建议您使用链接表而不是 IN 子句来从外部数据库中检索数据。

以下示例演示如何从 Employees 表中检索数据:

SELECT LastName, FirstName 
FROM Employees;

示例

下面的一些示例假定 Employees 表中存在一个假想的 Salary 字段。 请注意,该字段实际并不存在于罗斯文数据库的 Employees 表中。

This example creates a dynaset-type Recordset based on an SQL statement that selects the LastName and FirstName fields of all records in the Employees table. 它调用 EnumFields 过程,该过程将 Recordset 对象的内容显示到调试窗口

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

以下示例计算 PostalCode 字段中有条目的记录数,并将返回的字段命名为 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

以下示例显示雇员数以及平均薪水和最高薪水。

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

The Sub procedure EnumFields is passed a Recordset object from the calling procedure. The procedure then formats and prints the fields of the Recordset to the Debug window. The variable is the desired printed field width. Some fields may be truncated.

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

另请参阅

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。