Min, Max functions (Microsoft Access SQL)

Applies to: Access 2013 | Access 2016

Return the minimum or maximum of a set of values contained in a specified field on a query.

Syntax

Min(expr)

Max(expr)

The expr placeholder represents a string expression identifying the field that contains the data you want to evaluate or an expression that performs a calculation using the data in that field. Operands in expr can include the name of a table field, a constant, or a function (which can be either intrinsic or user-defined but not one of the other SQL aggregate functions).

Remarks

Use Min and Max to determine the smallest and largest values in a field based on the specified aggregation, or grouping. For example, you could use these functions to return the lowest and highest freight cost. If there is no aggregation specified, the entire table is used.

Use Min and Max in a query expression and in the SQL property of a QueryDef object or when creating a Recordset object based on an SQL query.

Example

This example uses the Orders table to return the lowest and highest freight charges for orders shipped to the United Kingdom.

This example calls the EnumFields procedure, which you can find in the SELECT statement example.

Sub MinMaxX() 
 
    Dim dbs As Database, rst As Recordset 
 
    ' Modify this line to include the path to Northwind 
    ' on your computer. 
    Set dbs = OpenDatabase("Northwind.mdb") 
     
    ' Return the lowest and highest freight charges for  
    ' orders shipped to the United Kingdom. 
    Set rst = dbs.OpenRecordset("SELECT " _  
        & "Min(Freight) AS [Low Freight], " _ 
        & "Max(Freight)AS [High Freight] " _ 
        & "FROM Orders WHERE ShipCountry = 'UK';") 
     
    ' Populate the Recordset. 
    rst.MoveLast 
     
    ' Call EnumFields to print the contents of the  
    ' Recordset. Pass the Recordset object and desired 
    ' field width. 
    EnumFields rst, 12 
 
    dbs.Close 
 
End Sub 

About the contributors

Link provided by Community Member Icon the UtterAccess community.

UtterAccess is the premier Microsoft Access wiki and help forum.

See also

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.