StDev, StDevP functions (Microsoft Access SQL)

Applies to: Access 2013 | Access 2016

Return estimates of the standard deviation for a population or a population sample represented as a set of values contained in a specified field on a query.

Syntax

StDev(expr)

StDevP(expr)

The expr placeholder represents a string expression identifying the field that contains the numeric data that 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

The StDevP function evaluates a population, and the StDev function evaluates a population sample.

If the underlying query contains fewer than two records (or no records, for the StDevP function), these functions return a Null value (which indicates that a standard deviation cannot be calculated).

Use the StDev and StDevP functions in a query expression. You can also use this expression 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 estimate the standard deviation of the 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 StDevX() 
 
    Dim dbs As Database, rst As Recordset 
 
    ' Modify this line to include the path to Northwind 
    ' on your computer. 
    Set dbs = OpenDatabase("Northwind.mdb") 
 
    ' Calculate the standard deviation of the freight 
    ' charges for orders shipped to the United Kingdom. 
    Set rst = dbs.OpenRecordset("SELECT " _ 
        & "StDev(Freight) " _ 
        & "AS [Freight Deviation] 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, 15 
     
    Debug.Print 
     
    Set rst = dbs.OpenRecordset("SELECT " _ 
        & "StDevP(Freight) " _ 
        & "AS [Freight DevP] 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, 15 
 
    dbs.Close 
 
End Sub 

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.