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

16 thoughts on “OOP Battleship Part 2: The Model”

  1. Hi Mathieu,
    just began to work on this wonderful tutorial and came across a minor bug while testing it. As I’m not sure how to mark it as Code, I just pasted it as plain text:
    Sub testGC()
    Dim gc1 As IGridCoord
    Dim gc2 As IGridCoord
    Dim gc3 As IGridCoord

    Set gc1 = GridCoord.Default
    Set gc2 = GridCoord.Create(1, 0)
    Debug.Assert Not gc1.Equals(gc2)
    Set gc3 = gc1.Offset(1, 0)
    Debug.Assert gc3.Equals(gc2)
    Debug.Assert gc1.IsAdjacent(gc2)
    Debug.Assert gc1.ToA1String = “A1” ‘

    Like

  2. Seems you’re assuming GridCoord.Default is (1,1), but there’s a unit test in the GridCoordTests module that is rather explicit about this assumption:

    ‘@TestMethod
    Public Sub DefaultIsZeroAndZero()
    Const expectedX As Long = 0
    Const expectedY As Long = 0

    Dim sut As IGridCoord
    Set sut = GridCoord.Default

    Assert.AreEqual expectedX, sut.X, “X coordinate mismatched.”
    Assert.AreEqual expectedY, sut.Y, “Y coordinate mismatched.”
    End Sub

    The GridCoord class has no idea about any game rules (other than the helper ToA1String method), or any game grid. It doesn’t know whether a game grid is 1-based or 0-based, for it doesn’t need to. Given the helper ToA1String method implementation…

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

    It’s expected that GridCoord.Default.ToA1String outputs an invalid “@0” string representation.

    Like

  3. Thanks for your reply!
    Maybe my misunderstanding results from not looking into the codebase yet, and instead coding along the blogposts. A a result, I was not able to see your Unit-Tests. Moreover did I not have access to a Rubberduck-VBA-Editor, and was forced to test using simple Debug.Assert-Statements. I wasn’t assuming, that the origin was (1,1), I was however assuming, that the A1-String for the origin of the default instance would be “A1”, i. e. the upper left and valid coordinate, regardless of any game logic.
    But i think it will become clearer, during my progress along your series.
    Thanks again for all your mind-widening blogposts about OOP in VBA.

    Liked by 1 person

  4. I’ve never seen an “Or” in an Enum Declaration. What is that all about?
    The above is why I ask:
    Public Enum PlayerGridErrors
    KnownGridStateError = vbObjectError Or 127 ‘<<<<<<<<<
    CannotAddShipAtPosition
    CannotAddMoreShips
    End Enum

    Like

  5. Mathieu, Great project to learn programming but there are memory leaks (
    After a while you can see this. I was not playing but examingn the code ..

    Like

    1. That’s been narrowed down to ….a bug in Excel itself – I’ve naively used “Freeze Panes” to disable scrolling; if you unfreeze the panes and set the sheet’s ScrollArea instead, the leak is gone!
      I *really* need to get around to push the local updates I have for this project…

      Like

  6. Thanks so much for your posts, here and on Code Review, you’re helping me become a better developer
    Ironically, however, the version of Battleship on Git Hub is out-of-date 😉

    Like

    1. Thanks for the feedback! That’s right, the .xlsm is really just a host for the VBA code in the src folder: I really need to write about this workflow, but in a nutshell you open the workbook, sync/overwrite the project files with those in the src folder, make the changes, save the host document, export the project into the src folder, git commit/push …the single version of the truth isn’t in the .xlsm anymore: it’s the source code in the src folder now =)

      Like

  7. Thanks for your articles and the rubberduck project in general. It has improved my coding and understanding immensely.

    One thing I wondered is that when you close excel the state of the grid, player etc are lost. As the worksheet is just a view it doesn’t appear to hold any data, host show it. How would you go about saving the objects state so that the game could in theory be closed and resumed?

    Liked by 1 person

    1. That’s a great question! I would probably use an external file, perhaps leveraging the built-in binary serialization of the Private Type declarations holding each object’s internal state. So it would probably take the form of an ISerializable interface with Serialize and Deserialize methods, and a GameStateSerializer object that would coordinate the work. ISerializable would then need to be implemented by all classes that hold any game state; the Serialize method would Put# the This instance variable into a file handle provided by the serializer, and the Deserialize method would similarly Get# from the file handle into the This instance variable of a new instance of the serializable class. Once everything is loaded we inject the players and grids and ships into the game controller, probably as parameters to a new ResumeGame method that a new ResumeGame parameterless macro would invoke after successfully prompting the user for a game file to load. This could be pretty fun to implement!

      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