Constructors in twinBASIC

If you haven’t tried it already, download VSCode and get the twinBASIC extension, and be part of the next stage of the Visual Basic revolution. When it goes live (it’s still in preview, and vigorously maintained), twinBASIC will compile 100% VB6/VBA compatible code and completely redefine how VB6 and VBA solutions will be maintained and extended in the foreseeable future.

Among the many mind-blowing language-level enhancements twinBASIC brings to the table, are actual constructors – something Visual Basic developers that haven’t made the leap to VB.NET have only been able to simulate with factory methods.

Object Construction As We Know It

When we create a new instance of a class in VBA like this:

Dim thing As Something
Set thing = New Something

Several things appear to happen all at once, but in reality there’s a very specific sequence of events that unfolds when this Set assignment instruction is evaluated:

  • The right-hand side of the assignment is evaluated first; it’s a <new-expression>, so we’re spawning a New instance of the Something class.
  • As the object gets created and before the New operation returns to the caller, the Class_Initialize handler inside the Something class is invoked.
  • When the Class_Initialize handler returns, the New operation is completed and yields an object reference pointing to the new object.
  • The object reference gets copied to the thing variable, and member calls are now legal against it.

Classes in VBA/VB6 don’t really have a constructor – there’s this Class_Initialize handler where it’s appropriate to initialize private instance state, but it’s essentially a callback invoked from the actual “base class” constructor which is for a COM object and thus, without any parameters.

Default Instances & Factory Methods

Classes in VBA/VB6 have a hidden VB_PredeclaredId attribute that is False by default, but that can be set to True (either manually, or using Rubberduck’s @PredeclaredId annotation). Document modules like ThisWorkbook and Sheet1, but also UserForm modules, have that hidden attribute set to True.

Given a VB_PredeclaredId = True attribute, the runtime automatically creates an instance of the class that is named after the class itself, so the global UserForm1 identifier refers to the default instance of the UserForm1 class when it’s used as an object, and refers to the UserForm1 class type when it’s used as a type.

If you handle Class_Initialize in a class that has VB_PredeclaredId set to True, you’ll notice the handler is invoked the first time the class name is used as an object in code, i.e. just before the first reference to it. And if you handle Class_Terminate too, you’ll find the default instance gets destroyed as soon as it’s no longer needed (i.e. when nothing in-scope references it anymore).

We could treat default instances like global objects – that’s what they are. But globals and OOP don’t quite go hand-in-hand, for many reasons; there’s something icky about having magical implicit global objects spawned from the language runtime itself. However, if we treat this default instance as we would a type, then we can consider the members of a class’ default interface as members that belong to the type, and then we can define an explicit, separate interface that the class can implement to expose its actual intended instance functionality.

In many languages, members that belong to a type (rather than an instance of that type) are called “static”. In C# the static keyword is used for this, but in VBA/VB6 the Static keyword has a different meaning and there isn’t really anything “static” in Visual Basic. In .NET type-level members are identified with the Shared keyword, which was reserved in VB6 but never implemented. twinBASIC might end up changing that.

So by treating the default instance of a VBA/VB6 class as we would a static class (i.e. keeping the default instance stateless, that is, we don’t allow it to hold any state/variables), we can still adhere to OOP principles while leveraging language features that let us simulate static behavior, chiefly so by exposing factory methods that effectively simulate parameterized constructors – here for our Something example class module, with an added SomeProperty value being property-injected:

'@PredeclaredId
Option Explicit
Implements ISomething
Private mValue As Long

Public Function Create(ByVal Value As Long) As ISomething
    Dim Result As Something
    Set Result = New Something
    Result.SomeProperty = Value
    Set Create = Result
End Function

Public Property Let SomeProperty(ByVal RHS As Long)
    mValue = RHS
End Property

Private Property Get ISomething_SomeProperty() As Long
    ISomething_SomeProperty = mValue
End Property

The ISomething interface is only exposing SomeProperty with a Property Get accessor, which makes it read-only. That’s great when the code is written against ISomething, but then several things feel wrong:

  • We must expose Property Let (or Property Set) mutators on the class’ default interface to support the property-injection that happens in the factory method.
  • Rubberduck will (appropriately) flag the write-only properties and suggest to also expose a Property Get accessor, because it makes no sense to be able to write to a property when we can’t read back the value we just wrote.
  • Properties visible on the default interface look like mutable state that is accessible from the default instance. If nothing is done to actively prevent it, the default instance can easily become stateful… and then we’re looking at dreadful global state living in some class.
  • In order to have a clean interface without the Create member (and without the Property Let mutator), we must implement an explicit, non-default interface to expose the members we intend the calling code to work with.

Actual Constructors

With twinBASIC we get actual constructors, that can be parameterized (for classes we’re not making visible to COM clients, like VBA or VB6). A constructor is a special procedure named New (like the operator) whose sole purpose is to initialize the state of an object, so that the client code creating the object receives a fully-initialized object: the very same purpose as a default instance factory method.

We don’t need default instance factory methods in twinBASIC because we get to define actual constructors. This has several interesting and snowballing implications we’ll go over in a moment, but first we need to establish certain things about what constructors should and generally shouldn’t do.

  • DO take a constructor parameter for instance state that should be initialized by the caller.
  • DO initialize private instance fields from constructor parameters.
  • DO invoke any private initialization procedures that must be invoked for the object instance to be valid when the constructor returns.
  • DO validate all parameters and raise a run-time error given any invalid parameter value.
  • AVOID doing any kind of non-initialization work in a constructor.
  • AVOID invoking any procedure that performs non-initialization work from a constructor.
  • AVOID raising run-time errors in a constructor (other than from guard clauses validating parameter values).

For example, a DbConnection class might take a ConnectionString constructor parameter; the constructor stores the ConnectionString as instance-level state into a private field, then returns. Another method invoked by the consumer of the object invokes an Open method that reads the ConnectionString and proceeds to open the database connection. The DbConnection constructor could open the connection itself and that would probably be convenient for a lot of use cases… but it also couples constructing a DbConnection object with the action of connecting to a database. Problem is, when most people read this instruction:

Dim db As DbConnection = New DbConnection(connString)

…they expect to have simply instantiated a new DbConnection object – nothing less, nothing more. If merely creating an instance of an object can raise a run-time error because some network cable is unplugged, we’re looking at the consequences of having a badly side-effecting constructor.

Inline initialization notice the initial assignment is on the same line as the declaration? This syntax is legal in VB.NET, and twinBASIC adopted it as well. In VBA/VB6, we must separate the declaration (Dim) from the instruction performing the instantiation and assignment.

When we create a New object, we expect a new object to get created, and we expect that to be a very boring thing: it wouldn’t even occur to us that there’s the slightest chance anything could possibly go wrong with just spawning a new instance of a class.

That is why constructors should adhere as much as possible to the KISS principle: Keep It Stupid Simple. If something more complicated than creating objects and setting their properties happens in a constructor, consider refactoring it so that the actual work is triggered after the object is constructed.

Implications

The constructor is operating on the instance that’s in the process of being created. This makes them much simpler to reason about and to implement than, say, a Create factory method on the default interface of the class, because now we have access to the internal state of the object we’re constructing.

The implication of this, is that we no longer need to expose any Property Let mutators to property-inject the parameter values; instead we can now do constructor injection and directly assign the private fields, without needing to pollute the class’ default interface with members we don’t need.

Since we’re no longer polluting the class’ default interface with members we don’t need, we don’t have to extract an explicit interface to hide them anymore. And since constructors are invoked using the New operator, there’s no need to have a predeclared default instance of the class for a Create method to be accessible to the calling code.

Let’s see how tremendously twinBASIC constructors change everything, by contrasting a simple scenario in Classic VB with the same identical scenario in twinBASIC.

Simulating Constructors in Classic VB (VBA/VB6)

Here’s an example of how I’d write a class named Example, simulating a parameterized constructor:

'@PredeclaredId
Option Explicit
Implements IExample

Private Type TState
    Value1 As Long
    Value2 As String
End Type

Private This As TState

Public Function Create(ByVal Value1 As Long, ByVal Value2 As String) As IExample
    Dim Result As Example
    Set Result = New Example
    Result.Value1 = Value1
    Result.Value2 = Value2
    Set Create = Result
End Function

Public Property Get Value1() As Long
    Value1 = This.Value1
End Property
Public Property Let Value1(ByVal RHS As Long)
    This.Value1 = RHS
End Property

Public Property Get Value2() As String
    This.Value2 = RHS
End Property
Public Property Let Value2(ByVal RHS As String)
    This.Value2 = RHS
End Property

Private Property Get IExample_Value1() As Long
    IExample_Value1 = This.Value1
End Property

Private Property Get IExample_Value2() As String
    IExample_Value2 = This.Value2
End Property

Where IExample is another class module that only exposes Public Property Get Value1() As Long and Public Property Get Value2() As String. The calling code might look like this:

Dim x As IExample
Set x = Example.Create(42, "Test")
Debug.Print x.Value1, x.Value2

The x variable could legally be cast to an Example, and then x.Value = 10 would be legal too. But we code against abstract interfaces so we get IExample.Value1 and IExample.Value2 as get-only properties, and that’s the standard pattern I’ve now been using for several years in classic VB, to perform dependency injection and initialize objects with properties before they’re returned to the code that consumes them.

It works pretty nicely, with relatively few caveats (like casting to concrete /default interface being allowed, or Example.Value1 = 42 making the default instance stateful unless we actively guard against it) but it’s robust enough and makes a rather clean API that’s very suitable for OOP and testable code.

Are we in the default instance? Using the Is operator together with Me, we can test whether Me Is Example and determine whether we’re currently in the default instance of the Example class. So adding If Me Is Example Then Err.Raise 5 could raise a run-time error as a guard clause in the Property Let members, effectively protecting against misuse of the class/design.

Rubberduck has tooling that makes writing most of this code pretty much entirely automatic, but at the end of the day it’s still quite a lot of code – and the only reason we need it is because we can’t parameterize an actual constructor.

What if we could though?

Constructors in twinBASIC

The legacy-VB example above should compile just fine and work identically in twinBASIC, but the language offers new opportunities and it would be silly to ignore them. Now a twinBASIC executable doesn’t necessarily have the same concerns as a twinBASIC ActiveX DLL; in a standalone .exe project we can do anything we want, but if we’re making a library that’s intended to be used by legacy VB code we have to keep our intended COM-based client in mind.

COM clients (like VBA) don’t support parameterized constructors, so public/exposed classes (with VB_Exposed attribute set to True) should define a parameterless constructor. Either the legacy way, with a Class_Initialize handler:

Private Sub Class_Initialize()
End Sub

Or the twinBASIC way with an explicit, parameterless constructor:

Public Sub New()
End Sub

Similar to VB.NET, a constructor in twinBASIC is a Sub procedure named New in a class module. Ideally you want your constructor near the top of the module, as the first member of the class. Not for any technical reason really, but instinctively that’s where you expect a constructor to be.

A class’ parameterless constructor is dubbed a default constructor, because if no constructor is specified for a class, then an implicit one necessarily exists. If a class defines a parameterized constructor, it is understood as a class that requires the constructor arguments, and there is no implicit default/parameterless constructor then: a COM client could not create a new instance of such a class.

In twinBASIC, I’d write the above Example clas like this – note the absence of an IExample interface:

Class Example

    Private Type TState
        Value1 As Long
        Value2 As String
    End Type

    Private This As TState

    Public Sub New(ByVal Value1 As Long, ByVal Value2 As String)
        This.Value1 = Value1
        This.Value2 = Value2
    End Sub

    Public Property Get Value1() As Long
        Return This.Value1
    End Property

    Public Property Get Value2() As String
        Return This.Value2
    End Property

End Class

The calling code would now look like this:

Dim x As Example = New Example(42, "Test")
Debug.Print x.Value1, x.Value2

And it would have the exact same compile-time restrictions as the code written against the read-only IExample VBA/VB6 interface, only now thanks to parameterized construction we get to constructor-inject values and make the default interface of the Example class read-only, as we intended all along.

With twinBASIC we can still implement interfaces, but here an IExample get-only interface would be redundant. In a sense that brings most useful interfaces in twinBASIC closer to “pure” abstract interfaces, the kind that gets implemented by multiple classes: it would be suspicious to see a Thing class implement an IThing interface, for example, whereas in VBA/VB6 IThing would be an interface to work with a Thing instance when Thing is only used as a type as in myThing = Thing.Create(42).

Constructor Injection

In VBA/VB6 with factory methods we can achieve property injection – that is, using properties to “inject” dependencies into a class instance: the factory method invokes Property Let/Set procedures to do this. An example of property injection is how we set an ADODB.Connection‘s ConnectionString after instantiating the Connection object.

Dim Conn As Connection
Set Conn = New Connection
Conn.ConnectionString = "..."
Conn.Open

That works, but then it’s not ideal because it induces temporal coupling in the client code: the caller must remember to set the ConnectionString property before they invoke the Open method.

In VBA/VB6 we can also do method injection by taking dependencies in as Sub or Function parameters. To stick with the ConnectionString example, method injection would be the Open method taking the connection string as a parameter:

Dim Conn As Connection
Set Conn = New Connection
Conn.Open "..."

That’s much better: it’s now impossible for the calling code to “forget” to supply a connection string. The Property Let ConnectionString member becomes somewhat of a wart, and should be removed.

Now method injection is great for something like a connection string and nothing needs it other than an Open method. If many members of a class seem to need the same parameters, there’s a good chance we can remove that parameter from all these members by promoting the dependency to instance level. In VBA/VB6 that would have to be through property injection. Say you have a class and many of its members require a Connection parameter: ask yourself whether it would make sense for that Connection to be a dependency of the class rather than a dependency of each one of its methods.

With twinBASIC we can now do constructor injection, and create objects that are valid as soon as they come into existence:

Dim Conn As Connection = New Connection("...")
Conn.Open

If a Connection class takes a ByVal ConnectionString As String constructor argument, then the constructor can store that string in Private instance state, and we only need to expose a ConnectionString property (which would be get-only) if we have a reason to do so. The object is immediately usable, and there’s no temporal coupling anymore.

Eventually, twinBASIC could support ReadOnly modifiers for instance fields, that could enforce and guarantee immutability: the role of a constructor then boils down to assigning all the ReadOnly private instance fields.

By writing classes that take their instance-level dependencies as constructor arguments, we throw consumers of these classes into a pit of success where doing things wrong is much harder than doing them correctly – and that is the single best reason to leverage constructors when we can.

1 thought on “Constructors in twinBASIC”

  1. I would write the “Simulating Constructors in Classic VB (VBA/VB6)” like this:

    “`vba
    ‘@PredeclaredId
    Option Explicit
    Implements IExample

    Private Type TState
    Value1 As Long
    Value2 As String
    End Type

    Private This As TState

    Public Function Create(ByVal Value1 As Long, ByVal Value2 As String) As IExample
    Dim Result As Example
    Set Result = New Example
    Result.Init Value1, Value2
    Set Create = Result
    End Function

    Public Sub Init(ByVal Value1 As Long, ByVal Value2 As String)
    Result.Value1 = Value1
    Result.Value2 = Value2
    End Sub
    “`
    While the factory returns IExample, inside the factory Result has the default interface, so no need to worry about the non-default interface. This code is essentially identical to the twinBasic example.

    Like

Leave a Reply

Fill in your details below or click an icon to log in:

WordPress.com Logo

You are commenting using your WordPress.com account. Log Out /  Change )

Facebook photo

You are commenting using your Facebook account. Log Out /  Change )

Connecting to %s