Skip to content

Commit

Permalink
Merge pull request #22 from rubberduck-vba/tweaks
Browse files Browse the repository at this point in the history
Misc. Fixes
  • Loading branch information
retailcoder authored Dec 17, 2019
2 parents c5a7abd + 4d2897b commit d46777e
Show file tree
Hide file tree
Showing 41 changed files with 913 additions and 984 deletions.
Binary file modified Battleship.xlsm
Binary file not shown.
31 changes: 13 additions & 18 deletions src/AIPlayer.cls
Original file line number Diff line number Diff line change
Expand Up @@ -7,27 +7,28 @@ Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
'@Folder("Battleship.Model.Player")
Attribute VB_Description = "An implementation of IPlayer that is AI-controlled."
'@Folder("Battleship.Model")
'@ModuleDescription("An implementation of IPlayer that is AI-controlled.")
'@PredeclaredId
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
Public Function Create(ByVal grid As PlayerGrid, ByVal GameStrategy As IGameStrategy) As IPlayer
With New AIPlayer
.PlayerType = ComputerControlled
.GridIndex = gridId
Set .Strategy = GameStrategy
Set .PlayGrid = PlayerGrid.Create(gridId)
Set .PlayGrid = grid
Set Create = .Self
End With
End Function
Expand All @@ -52,14 +53,6 @@ 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
Expand All @@ -72,19 +65,21 @@ 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
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)

Static shots As Long
shots = shots + 1
Set IPlayer_Play = this.Strategy.Play(enemyGrid)
Debug.Print "AI Player " & this.GridIndex & "(" & TypeName(this.Strategy) & ") has played " & shots & " turns"
Debug.Print "AI Player " & this.PlayGrid.gridId & "(" & TypeName(this.Strategy) & ") has played " & shots & " turns"

End Function

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

Loading

0 comments on commit d46777e

Please sign in to comment.