@@ -7,27 +7,28 @@ Attribute VB_GlobalNameSpace = False
77Attribute VB_Creatable = False
88Attribute VB_PredeclaredId = True
99Attribute VB_Exposed = False
10- '@Folder("Battleship.Model.Player")
10+ Attribute VB_Description = "An implementation of IPlayer that is AI-controlled."
11+ '@Folder("Battleship.Model")
12+ '@ModuleDescription("An implementation of IPlayer that is AI-controlled.")
13+ '@PredeclaredId
1114Option Explicit
1215Implements IPlayer
1316
1417Private Const Delay As Long = 800
1518
1619Private Type TPlayer
17- GridIndex As Byte
1820 PlayerType As PlayerType
1921 PlayGrid As PlayerGrid
2022 Strategy As IGameStrategy
2123End Type
2224
2325Private this As TPlayer
2426
25- Public Function Create (ByVal gridId As Byte , ByVal GameStrategy As IGameStrategy ) As IPlayer
27+ Public Function Create (ByVal grid As PlayerGrid , ByVal GameStrategy As IGameStrategy ) As IPlayer
2628 With New AIPlayer
2729 .PlayerType = ComputerControlled
28- .GridIndex = gridId
2930 Set .Strategy = GameStrategy
30- Set .PlayGrid = PlayerGrid.Create(gridId)
31+ Set .PlayGrid = grid
3132 Set Create = .Self
3233 End With
3334End Function
@@ -52,14 +53,6 @@ Public Property Set PlayGrid(ByVal value As PlayerGrid)
5253 Set this.PlayGrid = value
5354End Property
5455
55- Public Property Get GridIndex() As Byte
56- GridIndex = this.GridIndex
57- End Property
58-
59- Public Property Let GridIndex(ByVal value As Byte )
60- this.GridIndex = value
61- End Property
62-
6356Public Property Get PlayerType() As PlayerType
6457 PlayerType = this.PlayerType
6558End Property
@@ -72,19 +65,21 @@ Private Property Get IPlayer_PlayGrid() As PlayerGrid
7265 Set IPlayer_PlayGrid = this.PlayGrid
7366End Property
7467
75- Private Sub IPlayer_PlaceShip (ByVal currentShip As IShip )
76- this.Strategy.PlaceShip this.PlayGrid, currentShip
68+ Private Sub IPlayer_PlaceShip (ByVal CurrentShip As IShip )
69+ this.Strategy.PlaceShip this.PlayGrid, CurrentShip
7770End Sub
7871
7972Private Function IPlayer_Play (ByVal enemyGrid As PlayerGrid ) As IGridCoord
73+
8074 Win32API.Sleep Delay
75+ Set IPlayer_Play = this.Strategy.Play(enemyGrid)
76+
8177 Static shots As Long
8278 shots = shots + 1
83- Set IPlayer_Play = this.Strategy.Play(enemyGrid)
84- Debug. Print "AI Player " & this.GridIndex & "(" & TypeName(this.Strategy) & ") has played " & shots & " turns"
79+ Debug. Print "AI Player " & this.PlayGrid.gridId & "(" & TypeName(this.Strategy) & ") has played " & shots & " turns"
80+
8581End Function
8682
8783Private Property Get IPlayer_PlayerType() As PlayerType
8884 IPlayer_PlayerType = this.PlayerType
8985End Property
90-
0 commit comments