Calling property procedures

The following table lists the syntax for calling property procedures:

Property procedure Syntax
Property Get [Set ] varname = [ object.] propname [( [arguments] )]
Property Let [Let ] [ object.] propname [( [arguments] )] = argument
Property Set Set [ object.] propname [( [arguments] )] = objectArg

Property procedures calls require at least one argument, the assignment (=) operator, and the property procedure name.

  • In a call with the property name on the right-side of the assignment operator, Visual Basic calls Property Get to return information from the class/object.
  • In a call with the property name on the left-side of assignment operator, Visual Basic calls Property Let or Property Set to update information within the class object.

If a property procedure's declaration has multiple parameters, calling Property Let or Property Set, passes the argument on the right-side of the assignment operator to the last parameter to the Property Let or Property Set procedures.

For example, the following diagram uses Property Let to show how arguments in the property procedure call (on top) relate to parameters in the declaration (on bottom):

Property Let

The following code example demonstrates the relationship between property procedure arguments and parameters.

'DemoType class declaration
Private pW
Private pX
Private pY
Private pZ

Property Get DemoProperty(w, x, y)
    'Calling format is: `z = DemoProperty(w, x, y)`
    ' or `Set z = DemoProperty(w, x, y)`
    w = pW
    x = pX
    y = pY
    If IsObject(pZ) Then
        Set DemoProperty = pZ
    Else
        DemoProperty = pZ
    End If
End Property
Property Let DemoProperty(w, x, y, z)
    'Calling format is `DemoProperty(w, x, y) = z`
    pW = w
    pX = x
    pY = y
    pZ = z
End Property
Property Set DemoProperty(w, x, y, z As Object)
    'Calling format is `Set DemoProperty(w, x, y) = z`
    pW = w
    pX = x
    pY = y
    Set pZ = z
End Property
Sub DemoSub()
    Dim myDemo As Object
    Dim a, b, c, d
    Dim w, x, y, z

    Set myDemo = New DemoType

    a = "Hello"
    b = ", "
    c = "world"
    d = "!"

    Debug.Print Join(Array(a, b, c, d), "") ' Hello, world!a

    'Call Property Let DemoProperty(a, b, c, d)
    Let myDemo.DemoProperty(a, b, c) = d
    'Call Property Get
    d = myDemo.DemoProperty(a, b, c)

    Debug.Print Join(Array(a, b, c, d), "") ' Hello, world!
End Sub

In practice, the only use for property procedures with multiple arguments is to create arrays of properties.

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.