Application.Nz method (Access)

Use the Nz function to return zero (0), a zero-length string (""), or another specified value when a Variant is Null. For example, you can use this function to convert a Null value to another value and prevent it from propagating through an expression.

Syntax

expression.Nz (Value, ValueIfNull)

expression A variable that represents an Application object.

Parameters

Name Required/Optional Data type Description
Value Required Variant A variable of data type Variant.
ValueIfNull Optional Variant Optional. A Variant that supplies a value to be returned if the variant argument is Null. This argument enables you to return a value other than zero or a zero-length string.

NOTE: If you use the Nz function in an expression in a query without using the ValueIfNull argument, the results will be a zero-length string in the fields that contain Null values.

Return value

Variant

Remarks

If the Value of the variant argument is Null, the Nz function returns an unassigned Variant, the special value Empty. In VBA, when evaluated, Empty will result in either the number zero or a zero-length string, depending on whether the context indicates that the Value should be a number or a string. For example:

Nz(Null) + 2    ' returns 2
Nz(Null) & 2    ' returns "2"
Nz(Null) + "2"  ' returns "2"
Nz(Null) & "2"  ' returns "2"

When used in a query expression, Nz will return similar result values.

If the optional ValueIfNull argument is included, the Nz function will return the value specified by that argument if the variant argument is Null.

If the Value of Variant isn't Null, the Nz function returns the Value of Variant.

The Nz function is useful for expressions that may include Null values. To force an expression to evaluate to a non-Null value even when it contains a Null value, use the Nz function to return zero, a zero-length string, or a custom return value.

For example, the expression 2 + varX will always return a Null value when the Variant varX is Null. However, 2 + Nz(varX) returns 2.

You can often use the Nz function as an alternative to the IIf function. For example, in the following code, two expressions including the IIf function are necessary to return the desired result. The first expression including the IIf function is used to check the value of a variable and convert it to zero if it is Null.

varTemp = IIf(IsNull(varFreight), 0, varFreight) 
varResult = IIf(varTemp > 50, "High", "Low")

In the next example, the Nz function provides the same functionality as the first expression, and the desired result is achieved in one line rather than two.

varResult = IIf(Nz(varFreight) > 50, "High", "Low")

If you supply a value for the optional argument ValueIfNull, that value will be returned when Value is Null. By including this optional argument, you may be able to avoid the use of an expression containing the IIf function. For example, the following expression uses the IIf function to return a string if the value of varFreight is Null.

varResult = IIf(IsNull(varFreight), "No Freight Charge", varFreight)

In the next example, the optional argument supplied to the Nz function provides the string to be returned if varFreight is Null.

varResult = Nz(varFreight, "No Freight Charge")

Example

The following example evaluates a control on a form and returns one of two strings based on the control's value. If the value of the control is Null, the procedure uses the the IsNull function to select the message, next the Nz function to replace a Null value with a message.

Public Sub CheckValue() 
 
    Dim frm As Form 
    Dim ctl As Control 
    Dim varResult As Variant 
 
    ' Return Form object variable pointing to Orders form. 
    Set frm = Forms!Orders 
 
    ' Return Control object variable pointing to ShipRegion. 
    Set ctl = frm!ShipRegion 
 
    ' Choose result based on value of control using IsNull.
    varResult = IIf(IsNull(ctl.Value), _ 
        "No value.", "Value is " & ctl.Value & ".") 
 
    ' Display result using IsNull. 
    MsgBox varResult, vbExclamation, "Using IsNull" 

    ' Choose result based on value of control using Nz. 
    ' "Value is" + Str(Null) evaluates to Null.
    varResult = Nz("Value is" + Str(ctl.Value), "No value") & ".") 
 
    ' Display result using Nz. 
    MsgBox varResult, vbExclamation, "Using Nz"
 
End Sub

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.