Self-Closing Pairs: Dancing with the VBE

A few months ago I merrily announced the first Rubberduck feature that actively interfered with typing code in the VBE. It wasn’t the first opportunity though: a rather long time ago, I flirted with the idea of triggering a parse task at every keypress, so that Rubberduck’s parse trees would always be up-to-date – but back then the parse task cancellation mechanics weren’t as fine-tuned as they are now, and it ended up being a bad idea. Interfering with typing in any way that introduces any kind of lag, or exacerbates a memory leak, can only be a bad idea.

But auto-completion was different. If done right, it would be the single best thing to happen to the VBE since Smart Indenter came along, two decades ago. So in less than two weeks I whipped up something I thought would work, got ecstatic over how awesome seeing blocks automatically completing, I announced the feature… and as feedback from the pre-release builds started coming in as bug reports, I started to realize the reason why no other VBE add-in offered a feature like this: the feature is far from trivial, and any mistake or oversight means interfering with typing code in an utterly annoying and disrupting way – the margin for error is very thin, as is the fine line between being incredibly intuitive & helpful, and being a complete pain in the neck.

The VBIDE API wasn’t made for this. The VBE wasn’t made to be extended that way.

But I’m not letting that stop me.

So I scrapped most of my hasty work, went back to the drawing board, rolled up my sleeves, and started over. At the time of this writing, block completion still hasn’t gotten the attention it deserves, for I decided to start round 2 with self-closing pairs.

As of this writing, I can confidently say that the feature is going to be rock-solid.

Fighting the VBE

The Visual Basic Editor has a soul of its own. And when you twist its arm, it slaps you back at every chance it has. To fight it, you need to know how it moves. You can’t prevent its mischievous deeds; to win, you need to embrace them, anticipate them. The extensibility API won’t let us inject a single character on the current line of code: we need to replace the entire line – and then dance with the devil.

man doing boxing
Photo by Pixabay on Pexels.com

Warm-Up

With the code panes subclassed to pick up keystrokes, VBENativeServices fires up an event that the AutoCompleteService handles (assuming settings have autocompletion enabled – failing which the event isn’t even fired). At this point if the IntelliSense drop-down is shown or the current selection isn’t at a single-character position, we immediately bail out. Otherwise, we run the self-closing pairs feature proper.

Cue Eye of the Tiger backing track…

Know where you are

We need to get the integral text of the current logical line of code (i.e. accounting for line continuations), take note of the caret position relative to the beginning of this logical line of code; take note of the line position relative to line 1 of the module as well – we encapsulate this data into a CodeString – a class that represents a logical line of code, a caret position in that logical line, with the position of this logical line in the module: that’s the original, and only the first real punch…

Know where the VBE is

The original is a trap though. If you don’t tread carefully here, you’ll take a serious one in the ribs. The problem is that because the original code is currently being edited, it’s e.g. “msgbox|” (where | would be the caret), if the keypress was " then when you mean to write “msgbox"|"” by replacing the entire current line of code, the VBE inserts that string but then the caret is now on the next line and you need to explicitly set the ICodePane.Selection value. Now dodge this: between the moment you replace the current line msgbox with msgbox"" and by the next moment you want to place the caret back to msgbox"|", if you skipped a step you have an uppercut to dodge, for at that point what’s really in the VBE is MsgBox "", so the caret ends up here: MsgBox |"". If you counter with offsetting the caret position by one, you just broke the case where the user would have typed that whitespace: msgbox "" would be off by one also: MsgBox ""|.

The solution is Judoesque: let the VBE come at you with everything it can. Embrace the flames. Fight fire with fire. The whole “prettification” trick is encapsulated in a specialized ICodeStringPrettifier object, whose role is to tell the VBE to bring it.

At the core of the prettifier, this:

module.DeleteLines(original.SnippetPosition);
module.InsertLines(original.SnippetPosition.StartLine, original.Code);

Hit me with your best shot. To work out the “prettified” version of the code, we determine the original caret position in terms of non-whitespace character count. Then we make the VBE modify the code, get the new prettifiedCode, and the caret position we want  to be at should be at the index of the nth non-whitespace character, where n is the original count. And that should get us out of trouble.

The only problem is that we don’t know which self-closing pair we’re dealing with, so it’s too early do intervene now – now that we know where the VBE stands, we need to know if we want to deliver a left or a right.

Find an opening

Once we know which SelfClosingPair to test for a result, it’s still too early to pull the prettifier trick – first we need to be sure our pair produces an output given the input, so we Execute it once, against the original code. If the pair returns a result, then we get the prettified original caret position… that way we don’t ruin the show by swinging into the void 3 times for every one time we land a hit.

One-Two

If we just hit once with everything we’ve got, the VBE will beat us again. We need a combo. First we replace the current logical line (“snippet”) with the result we got from the second Execute of the pair, which ran off the prettifier code:

result = scpService.Execute(selfClosingPair, prettified, e.Character);

module.DeleteLines(result.SnippetPosition);
module.InsertLines(result.SnippetPosition.StartLine, result.Code);

Here the VBE will prettify again, so you need to take it by surprise with a second blow – if the re-prettified code isn’t the code we’ve just written to the code pane, then we’re likely off by one and the final Selection will have to be offset:

var reprettified = module.GetLines(result.SnippetPosition);
var offByOne = result.Code != reprettified;
var finalSelection = new Selection(result.SnippetPosition.StartLine, 
                                   result.CaretPosition.StartColumn + 1)
                     .ShiftRight(offByOne ? 1 : 0);
pane.Selection = finalSelection;

If we dodged every bullet up to this point, we win… round 1.

Round 2: Backspace

Handling the pair-opening character is one thing, handling the pair-closing character is trivial. Handling backspace is fun though: we get to locate the matching character for our pair, and make both the opening and closing characters to be removed from the logical code line that we write back. Round 2 is just as riveting as round 1!

So if you have this:

foo = (| _
    (2 + 2) + 42
)

If the next keypress is BACKSPACE then you get this:

foo = | _
(2 + 2) + 42

Or given this:

foo = ( _
    (|2 + 2) + 42
)

You’d get:

foo = ( _
    2 + 2 + 42
)

We won’t be handling the DELETE key, but we’re not done yet: we can deliver another blow.

Round 3: Smart Concatenation

By handling the ENTER key and knowing whether the CTRL key was also pressed, we can turn this:

MsgBox "Lorem ipsum dolor sit amet,|"

if the next keypress is ENTER, into this:

MsgBox "Lorem ipsum dolor sit amet," & _
       "|"

and if the next keypress is CTRL+ENTER, into this:

MsgBox "Lorem ipsum dolor sit amet," & vbNewLine & _
       "|"

The VBE will only fight back with a compile error if the logical line of code contains too many line continations. We don’t have anything to do: the VBIDE API will throw an error, but Rubberduck’s wrappers simply catch that COM exception, making the line-insert operation no-op: the new line ends up not being added, no annoying message box, and the caret ends up on the next line, at the same indent.

Ding Ding Ding!

Rubberduck wins this fight for self-closing pairs, but the VBE will be back for more soon enough: it is anticipated to put up a good fight for block completion as well…

Lazy Object / Weak Reference

Sometimes a class needs to hold a reference to the object that “owns” it – i.e. the object that created it. When this happens, the owner object often needs to hold a reference to all the “child” objects it creates. If we say Class1 is the “parent” and Class2 is the “child”, we get something like this:

'Class1
Option Explicit
Private children As VBA.Collection

Public Sub Add(ByVal child As Class2)
    Set child.Owner = Me
    children.Add child
End Sub

Private Sub Class_Initialize()
    Set children = New VBA.Collection
End Sub

Private Sub Class_Terminate()
    Debug.Print TypeName(Me) & " is terminating"
End Sub

And Class2 might look like this:

'Class2
Option Explicit
Private parent As Class1

Public Property Get Owner() As Class1
    Set Owner = parent
End Property

Public Property Set Owner(ByVal value As Class1)
    Set parent = value
End Property

Private Sub Class_Terminate()
    Debug.Print TypeName(Me) & " is terminating"
End Sub

The problem might not be immediately apparent to untrained eyes, but this is a memory leak bug – this code produces no debug output, despite the Class_Terminate handlers:

'Module1
Option Explicit

Public Sub Test()
    Dim foo As Class1
    Set foo = New Class1
    foo.Add New Class2
    Set foo = Nothing
End Sub

Both objects remain in memory and outlive the Test procedure scope! Depending on what the code does, this could easily go from “accidental sloppy object management” to a serious bug leaving a ghost process running, with Task Manager being the only way to kill it! How do we fix this?

Not keeping a reference to Class1 in Class2 would fix it, but then Class2 might not be working properly. Surely there’s another way.

Suppose we abstract away the very notion of holding a reference to an object. Suppose we don’t hold an object reference anymore, instead we hold a Long integer that represents the address at which we’ll find the object pointer we’re referencing. To put it in simpler words, instead of holding the object itself, we hold a ticket that tells us where to go find it when we need to use it. We can do this in VBA.

First we define an interface that encapsulates the idea of an object reference – IWeakReference, that simply exposes an Object get-only property:

'@Description("Describes an object that holds the address of a pointer to another object.")
'@Interface
Option Explicit

'@Description("Gets the object at the held pointer address.")
Public Property Get Object() As Object
End Property

Then we implement it with a WeakReference class. The trick is to use CopyMemory from the Win32 API to take the bytes at a given address and copy them into an object reference we can use and return.

For an easy-to-use API, we give the class a default instance by toggling the VB_PredeclaredId attribute, and use a factory method to create and return an IWeakReference given any object reference: we take the object’s object pointer using the ObjPtr function, store/encapsulate that pointer address into a private instance field, and implement the IWeakReference.Object getter such that if anything goes wrong, we return Nothing instead of bubbling a run-time error.

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "WeakReference"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
Option Explicit
Implements IWeakReference

#If Win64 Then
Private Declare PtrSafe Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As LongPtr)
#Else
Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)
#End If

Private Type TReference
#If VBA7 Then
    Address As LongPtr
#Else
    Address As Long
#End If
End Type

Private this As TReference

'@Description("Default instance factory method.")
Public Function Create(ByVal instance As Object) As IWeakReference
    With New WeakReference
        .Address = ObjPtr(instance)
        Set Create = .Self
    End With
End Function

Public Property Get Self() As IWeakReference
    Set Self = Me
End Property

#If VBA7 Then
Public Property Get Address() As LongPtr
#Else
Public Property Get Address() As Long
#End If
    Address = this.Address
End Property

#If VBA7 Then
Public Property Let Address(ByVal Value As LongPtr)
#Else
Public Property Let Address(ByVal Value As Long)
#End If
    this.Address = Value
End Property

Private Property Get IWeakReference_Object() As Object
' Based on Bruce McKinney's code for getting an Object from the object pointer:

#If VBA7 Then
    Dim pointerSize As LongPtr
#Else
    Dim pointerSize As Long
#End If

    On Error GoTo CleanFail
    pointerSize = LenB(this.Address)

    Dim obj As Object
    CopyMemory obj, this.Address, pointerSize

    Set IWeakReference_Object = obj
    CopyMemory obj, 0&, pointerSize

CleanExit:
    Exit Property

CleanFail:
    Set IWeakReference_Object = Nothing
    Resume CleanExit
End Property

Now Class2 can hold an indirect reference to Class1, like this:

'Class2
Option Explicit
Private parent As IWeakReference

Public Property Get Owner() As Class1
    Set Owner = parent.Object
End Property

Public Property Set Owner(ByVal Value As Class1)
    Set parent = WeakReference.Create(Value)
End Property

Private Sub Class_Terminate()
    Debug.Print TypeName(Me) & " is terminating"
End Sub

Now Module1.Test produces the expected output, and the memory leak is fixed:

Class1 is terminating
Class2 is terminating

Understanding ‘Me’ (no flowers, no bees)

You may have read that Me was a keyword, or that it was some kind of “special object that’s built into Excel”; or, you might have inferred that it’s some kind of hidden instance/module-level variable that’s only there in class/form/document modules: that’s pretty much how I was understanding Me, until I saw what the language specifications say about it (emphasis mine):

Within the <procedure-body> of a procedure declaration that is defined within a <class-module-code-section> the declared type of the reserved name Me is the named class defined by the enclosing class module and the data value of Me is an object reference to the object that is the target object of the currently active invocation of the function.

So Me is a reserved name… and it only exists in procedure scope; the type being the class it’s used in makes it easy for IntelliSense to know what the members are, but its value is ultimately provided by the caller – from section 5.3.1.5 “Parameter lists”:

Each procedure that is a method has an implicit ByVal parameter called the current object that corresponds to the target object of an invocation of the method. The current object acts as an anonymous local variable with procedure extent and whose declared type is the class name of the class module containing the method declaration. […]

In other words when you do this:

Dim foo As Class1
Set foo = New Class1
foo.DoSomething 42

What really happens under the hood is something like this:

Dim foo As Class1
Set foo = New Class1
Class1.DoSomething foo, 42

So every parameterless method you ever wrote like this:

Public Sub DoSomething()
End Sub

Is understood by VBA as this (assuming that method is in Class1):

Public Sub DoSomething(ByVal Me As Class1)
End Sub

…which, interestingly, is pretty much the same mechanics as the this pointer in C++.

So Me isn’t a magic keyword, and doesn’t have anything whatsoever to do with Excel (or whatever your VBA host application is) – Me is simply a reserved name that allows us to refer to this hidden current object pointer inside a procedure scope, and that current object is whichever instance of the current class the calling code is working with.

OOP Battleship Part 4: AI Strategies

NewGame

If you recall the AIPlayer class from Part 2, the Create factory method takes an IGameStrategy parameter:

Public Function Create(ByVal gridId As Byte, ByVal GameStrategy As IGameStrategy) As IPlayer
    With New AIPlayer
        .PlayerType = ComputerControlled
        .GridIndex = gridId
        Set .Strategy = GameStrategy
        Set .PlayGrid = PlayerGrid.Create(gridId)
        Set Create = .Self
    End With
End Function

An AIPlayer can be created with an instance of any class that implements the IGameStrategy interface.

In any OOP language that supports class inheritance, we could have a base class e.g. GameStrategyBase, from which we could derive the various implementations, and with that we would have a place to write all the code that’s common to all implementations, …or that all implementations would possibly need to use… or not. See, class inheritance is the most important language feature that the “VBA can’t do OOP” or “VBA is not a real language” crowd love to bring up. And yet, more often than not, class inheritance isn’t the ideal solution – composition is.

And we’re going to do exactly that, by composing all IGameStrategy implementations with a GameStrategyBase class:

Battleship.AI

Coupling a game strategy with this “base” class isn’t an issue: the class is specifically meant to be used by IGameStrategy implementations. So we can shamelessly do this:

Option Explicit
Implements IGameStrategy
Private base As GameStrategyBase

Private Sub Class_Initialize()
    Set base = New GameStrategyBase
End Sub

And then proceed with implementing the PlaceShip method, given that AI player’s own PlayerGrid and the IShip the game controller is asking us to place on the grid. The base.PlaceShip method simply returns the first legal position+direction it can find.

Then we can implement the Play function to return an IGridCoord position and let the controller know what position this player is shooting at. We have a number of helper functions in GameStrategyBase we can use for that.

Random

The RandomShotStrategy shoots at random coordinates until it has located all enemy ships …then proceeds to sink them all, one after the other. It also places its ships randomly, regardless of whether the ships are adjacent or not.

Private Sub IGameStrategy_PlaceShip(ByVal grid As PlayerGrid, ByVal currentShip As IShip)

    Dim direction As ShipOrientation
    Dim position As IGridCoord
    Set position = base.PlaceShip(Random, grid, currentShip, direction)

    grid.AddShip Ship.Create(currentShip.ShipKind, direction, position)
    If grid.shipCount = PlayerGrid.ShipsPerGrid Then grid.Scramble

End Sub

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As IGridCoord
    Do
        If EnemyShipsNotAcquired(enemyGrid)  0 Then
            Set position = base.ShootRandomPosition(Random, enemyGrid)
        Else
            Set position = base.DestroyTarget(Random, enemyGrid, enemyGrid.FindHitArea)
        End If
    Loop Until base.IsLegalPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

Here the double-negative in the statement “the number of enemy ships not acquired, is not equal to zero” (WordPress is having a hard time with rendering that  operator, apparently), will probably be end up being inverted into a positive statement, which would make it read better. Perhaps If EnemyShipsToFind = 0 Then, and invert the Else logic. Or…

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As IGridCoord
    Do
        If EnemyShipsToFind(enemyGrid) > 0 Then
            Set position = base.ShootRandomPosition(Random, enemyGrid)
enemyGrid.FindHitArea)
        Else
            Set position = base.DestroyTarget(Random, enemyGrid,
        End If
    Loop Until base.IsLegalPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

That EnemyShipsToFind function should probably be a member of the PlayerGrid class.

FairPlay

The FairPlayStrategy is similar, except it will proceed to destroy an enemy ship as soon as it’s located. It also takes care to avoid placing ships adjacent to each other.

Private Sub IGameStrategy_PlaceShip(ByVal grid As PlayerGrid, ByVal currentShip As IShip)
    Do
        Dim direction As ShipOrientation
        Dim position As IGridCoord
        Set position = base.PlaceShip(Random, grid, currentShip, direction)

    Loop Until Not grid.HasAdjacentShip(position, direction, currentShip.Size)

    grid.AddShip Ship.Create(currentShip.ShipKind, direction, position)
    If grid.shipCount = PlayerGrid.ShipsPerGrid Then grid.Scramble
End Sub

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As GridCoord
    Do
        Dim area As Collection
        Set area = enemyGrid.FindHitArea

        If Not area Is Nothing Then
            Set position = base.DestroyTarget(Random, enemyGrid, area)
        Else
            Set position = base.ShootRandomPosition(Random, enemyGrid)
        End If
    Loop Until base.IsLegalPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

Merciless

The MercilessStrategy is more elaborate: it doesn’t just shoot at random – it shoots in patterns, targeting the edges and/or the center areas of the grid. It will destroy an enemy ship as soon as it’s found, and will avoid shooting in an area that couldn’t possibly host the smallest enemy ship that’s still afloat. And yet, it’s possible it just shoots a random position, too:

Private Sub IGameStrategy_PlaceShip(ByVal grid As PlayerGrid, ByVal currentShip As IShip)
    Do
        Dim direction As ShipOrientation
        Dim position As IGridCoord
        Set position = base.PlaceShip(Random, grid, currentShip, direction)
    Loop Until Not grid.HasAdjacentShip(position, direction, currentShip.Size)

    grid.AddShip Ship.Create(currentShip.ShipKind, direction, position)
    If grid.shipCount = PlayerGrid.ShipsPerGrid Then grid.Scramble
End Sub

Private Function IGameStrategy_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Dim position As GridCoord
    Do
        Dim area As Collection
        Set area = enemyGrid.FindHitArea

        If Not area Is Nothing Then
            Set position = base.DestroyTarget(Random, enemyGrid, area)
        Else
            If this.Random.NextSingle < 0.1 Then
                Set position = base.ShootRandomPosition(this.Random, enemyGrid)
            ElseIf this.Random.NextSingle < 0.6 Then
                Set position = ScanCenter(enemyGrid)
            Else
                Set position = ScanEdges(enemyGrid)
            End If
        End If

    Loop Until base.IsLegalPosition(enemyGrid, position) And _
               base.VerifyShipFits(enemyGrid, position, enemyGrid.SmallestShipSize) And _
               AvoidAdjacentHitPosition(enemyGrid, position)
    Set IGameStrategy_Play = position
End Function

In most cases (ScanCenter and ScanEdges do), the AI doesn’t even care to “remember” the last hit it made: instead, it asks the enemy grid to give it a “hit area”. It then proceeds to analyze whether that area is horizontal or vertical, and then attempts to extend it further.

It’s Open-Source!

I uploaded the complete code to GitHub: https://github.com/rubberduck-vba/Battleship.

OOP Battleship Part 3: The View

Download the macro-enabled Excel workbook here

Now that we have defined our model, we need a view. In MVC terms, the view is the component that’s making the game state visible to the player; it is responsible for the two-way communication with the controller. Since we’re in Microsoft Excel, we can use a worksheet to do this. So we craft a lovely-looking Battleship game screen:

pgyam

I used a stock image for the background, spent more time than I probably should have looking for images of the game ships, and used a number of rounded rectangle shapes to make various boxes and buttons – the clickable ones being attached to sheet-local macros. The two game grids use a customized 5-icon conditional format that not-so-coincidentally map to the GridState enum values:

jxpfw

If you recall from the previous post, the GridState enum was defined as follows:

Public Enum GridState
'@Description("Content at this coordinate is unknown.")
Unknown = -1
'@Description("Unconfirmed friendly ship position.")
PreviewShipPosition = 0
'@Description("Confirmed friendly ship position.")
ShipPosition = 1
'@Description("Unconfirmed invalid/overlapping ship position.")
InvalidPosition = 2
'@Description("No ship at this coordinate.")
PreviousMiss = 3
'@Description("An enemy ship occupies this coordinate.")
PreviousHit = 4
End Enum

The PlayerGrid class has a StateArray read-only property that returns a 2D variant array with Unknown values being Empty, and the rest of the state values being returned as-is: this means in order to “refresh” the view, all we need to do is dump this 2D variant array onto the appropriate game grid, and we’re done!

Private Property Get PlayerGrid(ByVal gridId As Byte) As Range
    Set PlayerGrid = Me.Names("PlayerGrid" & gridId).RefersToRange
End Property

Public Sub RefreshGrid(ByVal grid As PlayerGrid)
    Application.ScreenUpdating = False
    Me.Unprotect
    PlayerGrid(grid.gridId).Value = Application.WorksheetFunction.Transpose(grid.StateArray)
    Me.Protect
    Me.EnableSelection = xlUnlockedCells
    Application.ScreenUpdating = True
End Sub

Listing all the code here like I did for the model post would be rather boring, so I’m not going to do that. If the model was just a handful of classes with factory methods and explicit interfaces, the view is much more interesting as a concept.

The worksheet handles 3 worksheet events:

Private Sub Worksheet_BeforeDoubleClick(ByVal target As Range, ByRef Cancel As Boolean)
    Cancel = True
    Dim gridId As Byte
    Dim position As IGridCoord
    Set position = RangeToGridCoord(target, gridId)
    If Mode = FleetPosition Or Mode = player1 And gridId = 2 Or Mode = player2 And gridId = 1 Then
        RaiseEvent DoubleClick(gridId, position, Mode)
    End If
End Sub

Private Sub Worksheet_BeforeRightClick(ByVal target As Range, Cancel As Boolean)
    Cancel = True
    If Mode = FleetPosition Then
        Dim gridId As Byte
        Dim position As IGridCoord
        Set position = RangeToGridCoord(target, gridId)
        RaiseEvent RightClick(gridId, position, Mode)
    End If
End Sub

Private Sub Worksheet_SelectionChange(ByVal target As Range)
    Dim gridId As Byte
    Dim position As IGridCoord
    Set position = RangeToGridCoord(target, gridId)
    If Not position Is Nothing Then
        Me.Unprotect
        CurrentSelectionGrid(gridId).Value = position.ToA1String
        CurrentSelectionGrid(IIf(gridId = 1, 2, 1)).Value = Empty
        Me.Protect
        Me.EnableSelection = xlUnlockedCells
        RaiseEvent SelectionChange(gridId, position, Mode)
    End If
End Sub

Notice these aren’t doing anything really – they merely work out a way to talk to another component – see, making a worksheet (or any document module class) implement an interface is a very bad idea: don’t do it (unless you like to crash the host and lose everything). So instead, we make another class implement the “view” interfaces, and make that class talk to the worksheet – a bit like we did in There is no worksheet.

The view needs two interfaces: one for the controller to send messages to the view, and the other for the view to send messages to the controller. If we call controller-to-view messages “commands”, and view-to-controller messages “events”, then the names IGridViewEvents and IGridViewCommands make complete sense!

So the WorksheetView class (not the GameSheet worksheet) implements the IGridViewCommands interface, like this:

Private Sub IGridViewCommands_OnBeginAttack(ByVal currentPlayerGridId As Byte)
    sheetUI.ShowInfoBeginAttackPhase currentPlayerGridId
End Sub

Private Sub IGridViewCommands_OnBeginShipPosition(ByVal currentShip As IShip, ByVal player As IPlayer)
    sheetUI.ShowInfoBeginDeployShip currentShip.Name
End Sub

Private Sub IGridViewCommands_OnBeginWaitForComputerPlayer()
    Application.Cursor = xlWait
    Application.StatusBar = "Please wait..."
End Sub

the WorksheetView class also handles the custom events sent from the worksheet, like this:

Private Sub sheetUI_DoubleClick(ByVal gridId As Byte, ByVal position As IGridCoord, ByVal Mode As ViewMode)
    Select Case Mode
        
        Case ViewMode.FleetPosition
            ViewEvents.ConfirmShipPosition gridId, position
            
        Case ViewMode.player1, ViewMode.player2
            ViewEvents.AttackPosition gridId, position
            
    End Select
End Sub

Private Sub sheetUI_PlayerReady()
    ViewEvents.HumanPlayerReady
End Sub

Private Sub sheetUI_RightClick(ByVal gridId As Byte, ByVal position As IGridCoord, ByVal Mode As ViewMode)
    If Mode = FleetPosition Then ViewEvents.PreviewRotateShip gridId, position
End Sub

Private Sub sheetUI_SelectionChange(ByVal gridId As Byte, ByVal position As IGridCoord, ByVal Mode As ViewMode)
    If Mode = FleetPosition Then ViewEvents.PreviewShipPosition gridId, position
End Sub

So what is this ViewEvents? If VBA allowed an interface to expose events, we wouldn’t need it: we would simply raise an event to relay the message directly to the controller, who would then handle the view events and respond with a command back to the view. But VBA does not let us expose events on an interface, so this is where the adapter pattern kicks in.

We have a GridViewAdapter class that implements both IGridViewEvents and IGridViewCommands interfaces; the WorksheetView holds a (weak) reference to the adapter, through its IGridViewEvents interface – so ViewEvents.AttackPosition is a method on the adapter.

The GridViewAdapter class receives these messages from the view, and relays them back to the controller, via events:

Private Sub IGridViewEvents_AttackPosition(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnAttackPosition(gridId, position)
End Sub

Private Sub IGridViewEvents_ConfirmShipPosition(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnConfirmCurrentShipPosition(gridId, position)
End Sub

Private Sub IGridViewEvents_CreatePlayer(ByVal gridId As Byte, ByVal pt As PlayerType, ByVal difficulty As AIDifficulty)
    RaiseEvent OnCreatePlayer(gridId, pt, difficulty)
End Sub

Private Sub IGridViewEvents_HumanPlayerReady()
    RaiseEvent OnPlayerReady
End Sub

Private Sub IGridViewEvents_PreviewRotateShip(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnRotateCurrentShipPosition(gridId, position)
End Sub

Private Sub IGridViewEvents_PreviewShipPosition(ByVal gridId As Byte, ByVal position As IGridCoord)
    RaiseEvent OnPreviewCurrentShipPosition(gridId, position)
End Sub

The GameController has a Private WithEvents viewAdapter As GridViewAdapter private field, and with that it’s able to respond to the adapter’s events and, say, create a HumanPlayer in grid 1, or a MercilessAI AI player in grid2 – and then instruct the view to begin positioning the ships, one by one, until the game is ready to begin.

Apart from events, the worksheet exposes methods that display, hide, or flash such or such shape, depending on what the controller says needs to happen next: the worksheet doesn’t control anything whatsoever about the game mechanics – that’s the controller’s job. The view raises events, the adapter handles them and relays them to the controller; controller alters game state, and then sends a command to the view to reflect the current state.

This makes the controller blissfully unaware about any worksheet, or event about any WorksheetView class: it knows about the GridViewAdapter, but then looking at how the game is started…

Public Sub PlayWorksheetInterface()
    Dim view As WorksheetView
    Set view = New WorksheetView
    
    Dim randomizer As IRandomizer
    Set randomizer = New GameRandomizer
    
    Set controller = New GameController
    controller.NewGame GridViewAdapter.Create(view), randomizer
End Sub

…we can easily infer that the adapter would work with any class that implements the IGridViewCommands interface and that’s able to “adapt” its event model to the IGridViewEvents methods: the components are said to be decoupled; we can easily swap one implementation for another – be it for unit-testing the individual components… or we could implement a view that has nothing to do with any Excel worksheet.

We could easily add another button to the start screen, attach it to some PlayUserFormInterface macro, and do something like this:

Public Sub PlayUserFormInterface()
    Dim view As UserFormView
    Set view = New UserFormView
    
    Dim randomizer As IRandomizer
    Set randomizer = New GameRandomizer
    
    Set controller = New GameController
    controller.NewGame GridViewAdapter.Create(view), randomizer
End Sub

And then play the exact same game with a UI that’s entirely different.

OOP Battleship Part 2: The Model

Download the macro-enabled Excel workbook here

Merciless.png
“Merciless” AI (Player1) this close to winning this game

So we’re making a game of Battleship, and we’re going to do this using an object-oriented pattern called Model-View-Controller (MVC). The first thing we need to do, is to modelize the problem in terms of objects. We’re going to need:

  • Player object, so that we know who’s playing on which grid. A player might be human or computer-controlled, and a player has a grid.
  • PlayerGrid object, so that we know the state of each player’s game grid; a player’s grid has a number of ships on it.
  • Ship object that we can place on a player’s grid. A ship has a size and an orientation – we can place them anywhere on the grid, horizontally or vertically; a ship is also going to need to know where it’s hit and whether it’s sunken.
  • GridCoordinate object, to encapsulate X and Y positions and make it easy to pass these two values together as a single entity. This object could have an Offset method that gives us another coordinate at a relative X or Y position.

These objects solve the problem space of modelizing a game of Battleship: with them we have everything we need to track game state. We’ll need something else that can make the players take turns at shooting missiles at each other’s grid, but that will be the controller‘s job; we’ll also need something else that can display the game state and take a human user’s inputs, but that will be the view‘s job. The role of the model is to encapsulate the data that we need to manipulate, and with these objects we’ve got everything we need… for now.

GridCoordinate

Let’s start with the grid coordinates system, since that is our smallest building block, and a grid coordinate doesn’t need to know about a ship or a player interface. We want a grid coordinate to be read-only: once an instance is created for position A1, it’s A1 and remains A1. We want to be able to determine if two grid coordinates are the same without needing to check for both X and Y coordinates every time, and a function that returns True when a coordinate is adjacent to another would be useful, too. Next we’ll want a string representation of the coordinate that lines up with the A1 notation of the game grid, but it would also be useful to have a (x,y) representation that can easily round-trip from a string to a grid coordinate and back, without needing to work out the column number for H.

So the IGridCoord interface would look like this:

'@Folder("Battleship.Model")
'@Description("Describes a coordinate in a 2D grid.")
'@Interface
Option Explicit

'@Description("Gets the horizontal position.")
Public Property Get X() As Long
End Property

'@Description("Gets the vertical position.")
Public Property Get Y() As Long
End Property

'@Description("Creates and returns a new coordinate by offsetting this instance.")
Public Function Offset(Optional ByVal xOffset As Long, Optional ByVal yOffset As Long) As IGridCoord
End Function

'Description("Returns True if the specified coordinate is adjacent to this instance.")
Public Function IsAdjacent(ByVal other As IGridCoord) As Boolean
End Function

'@Description("Returns True if the specified coordinate describes the same location as this instance.")
Public Function Equals(ByVal other As IGridCoord) As Boolean
End Function

'@Description("Returns a (x,y) string representation of this instance.")
Public Function ToString() As String
End Function

'@Description("Returns a A1 string representation of this instance.
Public Function ToA1String() As String
End Function

We’re making it an interface, because otherwise there would be no way of exposing X and Y properties as read-only values. Now we’re going to be writing the game against this IGridCoord interface, rather than against the GridCoord class directly. In order to make it easy to create a grid coordinate by providing an X and an Y value, we’ll give the class a predeclared ID, and use its default instance not to store state, but to expose convenient factory methods.

The listing includes module attributes, so don’t juse copy-paste this in the VBE: you need to import it in a VBA project for it to work.

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "GridCoord"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = True
'@Folder("Battleship.Model")
'@IgnoreModule UseMeaningfulName; X and Y are perfectly fine names here.
Option Explicit
Implements IGridCoord

Private Type TGridCoord
    X As Long
    Y As Long
End Type

Private this As TGridCoord

Public Function Create(ByVal xPosition As Long, ByVal yPosition As Long) As IGridCoord
    With New GridCoord
        .X = xPosition
        .Y = yPosition
        Set Create = .Self
    End With
End Function

Public Function FromString(ByVal coord As String) As IGridCoord
    coord = Replace(Replace(coord, "(", vbNullString), ")", vbNullString)

    Dim coords As Variant
    coords = Split(coord, ",")

    If UBound(coords) - LBound(coords) + 1  2 Then Err.Raise 5, TypeName(Me), "Invalid format string"

    Dim xPosition As Long
    xPosition = coords(LBound(coords))

    Dim yPosition As Long
    yPosition = coords(UBound(coords))

    Set FromString = Create(xPosition, yPosition)
End Function

Public Property Get Self() As IGridCoord
    Set Self = Me
End Property

Public Property Get X() As Long
    X = this.X
End Property

Public Property Let X(ByVal value As Long)
    this.X = value
End Property

Public Property Get Y() As Long
    Y = this.Y
End Property

Public Property Let Y(ByVal value As Long)
    this.Y = value
End Property

Public Property Get Default() As IGridCoord
    Set Default = New GridCoord
End Property

Public Function ToString() As String
    ToString = "(" & this.X & "," & this.Y & ")"
End Function

Private Function IGridCoord_Equals(ByVal other As IGridCoord) As Boolean
    IGridCoord_Equals = other.X = this.X And other.Y = this.Y
End Function

Private Function IGridCoord_IsAdjacent(ByVal other As IGridCoord) As Boolean
    If other.Y = this.Y Then
        IGridCoord_IsAdjacent = other.X = this.X - 1 Or other.X = this.X + 1
    ElseIf other.X = this.X Then
        IGridCoord_IsAdjacent = other.Y = this.Y - 1 Or other.Y = this.Y + 1
    End If
End Function

Private Function IGridCoord_Offset(Optional ByVal xOffset As Long, Optional ByVal yOffset As Long) As IGridCoord
    Set IGridCoord_Offset = Create(this.X + xOffset, this.Y + yOffset)
End Function

Private Function IGridCoord_ToString() As String
    IGridCoord_ToString = Me.ToString
End Function

Private Function IGridCoord_ToA1String() As String
    IGridCoord_ToA1String = Chr$(64 + this.X) & this.Y
End Function

Private Property Get IGridCoord_X() As Long
    IGridCoord_X = this.X
End Property

Private Property Get IGridCoord_Y() As Long
    IGridCoord_Y = this.Y
End Property

So from the default instance, we have access to Create and FromString factory methods, a convenient Default property that gives a (0,0) default coordinate that should be equivalent to the class’ default instance; the writable X and Y properties are meant for instance state: they make no sense outside a factory method.

And now we can create and use a grid coordinate like this:

Dim position As IGridCoord
Set position = GridCoord.Create(3, 4)
Debug.Print position.ToA1String

We can also write a suite of test methods that validate that our GridCoord class behaves as expected in every case… and then make a PlayerGrid class, to represent each player’s grid.

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "PlayerGrid"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = True
'@Folder("Battleship.Model.Player")
Option Explicit

Private Const GridSize As Byte = 10
Private Const MaxShipsPerGrid As Byte = 5

Private Const KnownGridStateErrorMsg As String _
    = "Specified coordinate is not in an unknown state."
Private Const CannotAddShipAtPositionMsg As String _
    = "Cannot add a ship of this size at this position."
Private Const CannotAddMoreShipsMsg As String _
    = "Cannot add more ships to this grid."

Public Enum PlayerGridErrors
    KnownGridStateError = vbObjectError Or 127
    CannotAddShipAtPosition
    CannotAddMoreShips
End Enum

Public Enum AttackResult
    Miss
    Hit
    Sunk
End Enum

Public Enum GridState
    '@Description("Content at this coordinate is unknown.")
    Unknown = -1
    '@Description("Unconfirmed friendly ship position.")
    PreviewShipPosition = 0
    '@Description("Confirmed friendly ship position.")
    ShipPosition = 1
    '@Description("Unconfirmed invalid/overlapping ship position.")
    InvalidPosition = 2
    '@Description("No ship at this coordinate.")
    PreviousMiss = 3
    '@Description("An enemy ship occupies this coordinate.")
    PreviousHit = 4
End Enum

Private Type TPlayGrid
    Id As Byte
    ships As Collection
    State(1 To GridSize, 1 To GridSize) As GridState
End Type

Private this As TPlayGrid

Public Function Create(ByVal gridId As Byte) As PlayerGrid
    With New PlayerGrid
        .gridId = gridId
        Set Create = .Self
    End With
End Function

Public Property Get Self() As PlayerGrid
    Set Self = Me
End Property

Of course there’s more to it, but just listing it here would get boring – the important part is that there’s a GridState array, and a collection of ships. And then these GridState and AttackResult enums.

One important method is TryHit, which is the mechanism that sets the internal state to PreviousHit or PreviousMiss, depending on whether there’s a ship at the specified position – and if there’s one, we return a ByRef reference to it, so that the controller can tell the view to update that ship’s status:

'@Description("(side-effecting) Attempts a hit at the specified position; returns the result of the attack, and a reference to the hit ship if successful.")
Public Function TryHit(ByVal position As IGridCoord, Optional ByRef hitShip As IShip) As AttackResult
    
    If this.State(position.X, position.Y) = GridState.PreviousHit Or _
       this.State(position.X, position.Y) = GridState.PreviousMiss Then
        Err.Raise PlayerGridErrors.KnownGridStateError, TypeName(Me), KnownGridStateErrorMsg
    End If
    
    Dim currentShip As IShip
    For Each currentShip In this.ships
        If currentShip.Hit(position) Then
            this.State(position.X, position.Y) = GridState.PreviousHit
            If currentShip.IsSunken Then
                TryHit = Sunk
            Else
                TryHit = Hit
            End If
            Set hitShip = currentShip
            Exit Function
        End If
    Next
    
    this.State(position.X, position.Y) = GridState.PreviousMiss
    TryHit = Miss
    
End Function

Another important function is FindHitArea, which the AI player uses when it wants to hunt down a damaged ship – it returns a collection of collections of previously hit grid positions, that the AI player can then analyze to try and infer a direction:

'@Description("Finds area around a damaged ship, if one exists.")
Public Function FindHitArea() As Collection
    Dim currentShip As IShip
    For Each currentShip In this.ships
        If Not currentShip.IsSunken Then
            Dim currentAreas As Collection
            Set currentAreas = currentShip.HitAreas
            If currentAreas.Count > 0 Then
                Set FindHitArea = currentAreas(1)
                Exit Function
            End If
        End If
    Next
End Function

Lastly, the Scamble method is invoked for AI players’ grid – it replaces confirmed ship positions with unknown states, so that the AI enemy ships are hidden. Without this method, the AI-positioned ships would be in plain sight!

'@Description("Removes confirmed ship positions from grid state.")
Public Sub Scramble()
    Dim currentX As Long
    For currentX = 1 To GridSize
        Dim currentY As Long
        For currentY = 1 To GridSize
            If this.State(currentX, currentY) = GridState.ShipPosition Then
                this.State(currentX, currentY) = GridState.Unknown
            End If
        Next
    Next
End Sub

Player

What is a player? What does it need to be able to do? We know a player will need to be associated with a game grid; we know a player can be human or computer-controlled. And if we break down the game into individual steps, we can tell we’ll need a player to be able to place a ship on its grid, and – given the enemy grid, be able to tell the game where it’s going to be shooting next. So we can already have an IPlayer interface that formalizes this contract:

'@Folder("Battleship.Model.Player")
'@Interface
Option Explicit

Public Enum PlayerType
    HumanControlled
    ComputerControlled
End Enum

'@Description("Identifies whether the player is human or computer-controlled.")
Public Property Get PlayerType() As PlayerType
End Property

'@Description("Gets the player's grid/state.")
Public Property Get PlayGrid() As PlayerGrid
End Property

'@Description("Places specified ship on game grid.")
Public Sub PlaceShip(ByVal currentShip As IShip)
End Sub

'@Description("Attempts to make a hit on the enemy grid.")
Public Function Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
End Function

The HumanPlayer implementation is rather boring – PlaceShip and Play do nothing. The AIPlayer implementation is much more interesting:

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
END
Attribute VB_Name = "AIPlayer"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
'@Folder("Battleship.Model.Player")
Option Explicit
Implements IPlayer

Private Const Delay As Long = 800

Private Type TPlayer
    GridIndex As Byte
    PlayerType As PlayerType
    PlayGrid As PlayerGrid
    Strategy As IGameStrategy
End Type

Private this As TPlayer

Public Function Create(ByVal gridId As Byte, ByVal GameStrategy As IGameStrategy) As IPlayer
    With New AIPlayer
        .PlayerType = ComputerControlled
        .GridIndex = gridId
        Set .Strategy = GameStrategy
        Set .PlayGrid = PlayerGrid.Create(gridId)
        Set Create = .Self
    End With
End Function

Public Property Get Self() As IPlayer
    Set Self = Me
End Property

Public Property Get Strategy() As IGameStrategy
    Set Strategy = this.Strategy
End Property

Public Property Set Strategy(ByVal value As IGameStrategy)
    Set this.Strategy = value
End Property

Public Property Get PlayGrid() As PlayerGrid
    Set PlayGrid = this.PlayGrid
End Property

Public Property Set PlayGrid(ByVal value As PlayerGrid)
    Set this.PlayGrid = value
End Property

Public Property Get GridIndex() As Byte
    GridIndex = this.GridIndex
End Property

Public Property Let GridIndex(ByVal value As Byte)
    this.GridIndex = value
End Property

Public Property Get PlayerType() As PlayerType
    PlayerType = this.PlayerType
End Property

Public Property Let PlayerType(ByVal value As PlayerType)
    this.PlayerType = value
End Property

Private Property Get IPlayer_PlayGrid() As PlayerGrid
    Set IPlayer_PlayGrid = this.PlayGrid
End Property

Private Sub IPlayer_PlaceShip(ByVal currentShip As IShip)
    this.Strategy.PlaceShip this.PlayGrid, currentShip
End Sub

Private Function IPlayer_Play(ByVal enemyGrid As PlayerGrid) As IGridCoord
    Win32API.Sleep Delay
    Set IPlayer_Play = this.Strategy.Play(enemyGrid)
End Function

Private Property Get IPlayer_PlayerType() As PlayerType
    IPlayer_PlayerType = this.PlayerType
End Property

Notice the Play and PlaceShip methods aren’t actually implemented in the AIPlayer class; instead, we inject an IGameStrategy and that is what polymorphism allows us to do: we can now inject an instance of a class that implements a given strategy, and we can extend the game with another AI, without even changing a single line of existing AIPlayer code!

NewGame.png