Training
Module
Handle variables in Power Automate for desktop - Training
In this module, we'll discuss how to create, access, edit and manipulate variables in Power Automate for desktop.
This browser is no longer supported.
Upgrade to Microsoft Edge to take advantage of the latest features, security updates, and technical support.
Applies to: Access 2013 | Access 2016
Return estimates of the variance for a population or a population sample represented as a set of values contained in a specified field on a query.
Var(expr)
VarP(expr)
The expr placeholder represents a string expression identifying the field that contains the numeric 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).
The VarP function evaluates a population, and the Var function evaluates a population sample.
If the underlying query contains fewer than two records, the Var and VarP functions return a Null value, which indicates that a variance cannot be calculated.
Use the Var and VarP functions in a query expression or in an SQL statement.
This example uses the Orders table to estimate the variance of freight costs for orders shipped to the United Kingdom.
This example calls the EnumFields procedure, which you can find in the SELECT statement example.
Sub VarX()
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 variance of freight costs for
' orders shipped to the United Kingdom.
Set rst = dbs.OpenRecordset("SELECT " _
& "Var(Freight) " _
& "AS [UK Freight Variance] " _
& "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, 20
Debug.Print
Set rst = dbs.OpenRecordset("SELECT " _
& "VarP(Freight) " _
& "AS [UK Freight VarianceP] " _
& "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, 20
dbs.Close
End Sub
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.
Training
Module
Handle variables in Power Automate for desktop - Training
In this module, we'll discuss how to create, access, edit and manipulate variables in Power Automate for desktop.