Pass arguments to Constructor in VBA Pass arguments to Constructor in VBA vba vba

Pass arguments to Constructor in VBA


Here's a little trick I'm using lately and brings good results. I would like to share with those who have to fight often with VBA.

1.- Implement a public initiation subroutine in each of your custom classes. I call it InitiateProperties throughout all my classes. This method has to accept the arguments you would like to send to the constructor.

2.- Create a module called factory, and create a public function with the word "Create" plus the same name as the class, and the same incoming arguments as the constructor needs. This function has to instantiate your class, and call the initiation subroutine explained in point (1), passing the received arguments. Finally returned the instantiated and initiated method.

Example:

Let's say we have the custom class Employee. As the previous example, is has to be instantiated with name and age.

This is the InitiateProperties method. m_name and m_age are our private properties to be set.

Public Sub InitiateProperties(name as String, age as Integer)    m_name = name    m_age = ageEnd Sub

And now in the factory module:

Public Function CreateEmployee(name as String, age as Integer) as Employee    Dim employee_obj As Employee    Set employee_obj = new Employee    employee_obj.InitiateProperties name:=name, age:=age    set CreateEmployee = employee_objEnd Function

And finally when you want to instantiate an employee

Dim this_employee as EmployeeSet this_employee = factory.CreateEmployee(name:="Johnny", age:=89)

Especially useful when you have several classes. Just place a function for each in the module factory and instantiate just by calling factory.CreateClassA(arguments), factory.CreateClassB(other_arguments), etc.

EDIT

As stenci pointed out, you can do the same thing with a terser syntax by avoiding to create a local variable in the constructor functions. For instance the CreateEmployee function could be written like this:

Public Function CreateEmployee(name as String, age as Integer) as Employee    Set CreateEmployee = new Employee    CreateEmployee.InitiateProperties name:=name, age:=ageEnd Function

Which is nicer.


I use one Factory module that contains one (or more) constructor per class which calls the Init member of each class.

For example a Point class:

Class PointPrivate X, YSub Init(X, Y)  Me.X = X  Me.Y = YEnd Sub

A Line class

Class LinePrivate P1, P2Sub Init(Optional P1, Optional P2, Optional X1, Optional X2, Optional Y1, Optional Y2)  If P1 Is Nothing Then    Set Me.P1 = NewPoint(X1, Y1)    Set Me.P2 = NewPoint(X2, Y2)  Else    Set Me.P1 = P1    Set Me.P2 = P2  End IfEnd Sub

And a Factory module:

Module FactoryFunction NewPoint(X, Y)  Set NewPoint = New Point  NewPoint.Init X, YEnd FunctionFunction NewLine(Optional P1, Optional P2, Optional X1, Optional X2, Optional Y1, Optional Y2)  Set NewLine = New Line  NewLine.Init P1, P2, X1, Y1, X2, Y2End FunctionFunction NewLinePt(P1, P2)  Set NewLinePt = New Line  NewLinePt.Init P1:=P1, P2:=P2End FunctionFunction NewLineXY(X1, Y1, X2, Y2)  Set NewLineXY = New Line  NewLineXY.Init X1:=X1, Y1:=Y1, X2:=X2, Y2:=Y2End Function

One nice aspect of this approach is that makes it easy to use the factory functions inside expressions. For example it is possible to do something like:

D = Distance(NewPoint(10, 10), NewPoint(20, 20)

or:

D = NewPoint(10, 10).Distance(NewPoint(20, 20))

It's clean: the factory does very little and it does it consistently across all objects, just the creation and one Init call on each creator.

And it's fairly object oriented: the Init functions are defined inside the objects.

EDIT

I forgot to add that this allows me to create static methods. For example I can do something like (after making the parameters optional):

NewLine.DeleteAllLinesShorterThan 10

Unfortunately a new instance of the object is created every time, so any static variable will be lost after the execution. The collection of lines and any other static variable used in this pseudo-static method must be defined in a module.


When you export a class module and open the file in Notepad, you'll notice, near the top, a bunch of hidden attributes (the VBE doesn't display them, and doesn't expose functionality to tweak most of them either). One of them is VB_PredeclaredId:

Attribute VB_PredeclaredId = False

Set it to True, save, and re-import the module into your VBA project.

Classes with a PredeclaredId have a "global instance" that you get for free - exactly like UserForm modules (export a user form, you'll see its predeclaredId attribute is set to true).

A lot of people just happily use the predeclared instance to store state. That's wrong - it's like storing instance state in a static class!

Instead, you leverage that default instance to implement your factory method:

[Employee class]

'@PredeclaredIdOption ExplicitPrivate Type TEmployee    Name As String    Age As IntegerEnd TypePrivate this As TEmployeePublic Function Create(ByVal emplName As String, ByVal emplAge As Integer) As Employee    With New Employee        .Name = emplName        .Age = emplAge        Set Create = .Self 'returns the newly created instance    End WithEnd FunctionPublic Property Get Self() As Employee    Set Self = MeEnd PropertyPublic Property Get Name() As String    Name = this.NameEnd PropertyPublic Property Let Name(ByVal value As String)    this.Name = valueEnd PropertyPublic Property Get Age() As String    Age = this.AgeEnd PropertyPublic Property Let Age(ByVal value As String)    this.Age = valueEnd Property

With that, you can do this:

Dim empl As EmployeeSet empl = Employee.Create("Johnny", 69)

Employee.Create is working off the default instance, i.e. it's considered a member of the type, and invoked from the default instance only.

Problem is, this is also perfectly legal:

Dim emplFactory As New EmployeeDim empl As EmployeeSet empl = emplFactory.Create("Johnny", 69)

And that sucks, because now you have a confusing API. You could use '@Description annotations / VB_Description attributes to document usage, but without Rubberduck there's nothing in the editor that shows you that information at the call sites.

Besides, the Property Let members are accessible, so your Employee instance is mutable:

empl.Name = "Jane" ' Johnny no more!

The trick is to make your class implement an interface that only exposes what needs to be exposed:

[IEmployee class]

Option ExplicitPublic Property Get Name() As String : End PropertyPublic Property Get Age() As Integer : End Property

And now you make Employee implement IEmployee - the final class might look like this:

[Employee class]

'@PredeclaredIdOption ExplicitImplements IEmployeePrivate Type TEmployee    Name As String    Age As IntegerEnd TypePrivate this As TEmployeePublic Function Create(ByVal emplName As String, ByVal emplAge As Integer) As IEmployee    With New Employee        .Name = emplName        .Age = emplAge        Set Create = .Self 'returns the newly created instance    End WithEnd FunctionPublic Property Get Self() As IEmployee    Set Self = MeEnd PropertyPublic Property Get Name() As String    Name = this.NameEnd PropertyPublic Property Let Name(ByVal value As String)    this.Name = valueEnd PropertyPublic Property Get Age() As String    Age = this.AgeEnd PropertyPublic Property Let Age(ByVal value As String)    this.Age = valueEnd PropertyPrivate Property Get IEmployee_Name() As String    IEmployee_Name = NameEnd PropertyPrivate Property Get IEmployee_Age() As Integer    IEmployee_Age = AgeEnd Property

Notice the Create method now returns the interface, and the interface doesn't expose the Property Let members? Now calling code can look like this:

Dim empl As IEmployeeSet empl = Employee.Create("Immutable", 42)

And since the client code is written against the interface, the only members empl exposes are the members defined by the IEmployee interface, which means it doesn't see the Create method, nor the Self getter, nor any of the Property Let mutators: so instead of working with the "concrete" Employee class, the rest of the code can work with the "abstract" IEmployee interface, and enjoy an immutable, polymorphic object.