blob: b3114469685afa936a092c462b07589841062f2e [file] [log] [blame]
Dim rPosition As Range
Public HitCount As Integer
Dim oSize As Integer
Dim m_hits As Collection
Public Property Get Position() As Range
Set Position = rPosition
End Property
Public Property Set Position(ByVal value As Range)
Set rPosition = value
End Property
Public Function IsHit(cell As Range, isPlayer As Boolean) As Boolean
Attribute IsHit.VB_Description = "Checks if the current move is a hit"
Attribute IsHit.VB_HelpID = 1
'Sample of attribute use on function level (show up in the objectbrowser(F2) --> Method --> Properties
If Code.Collide(cell, Position) Then
cell.Worksheet.Unprotect
cell.Interior.Color = vbRed
isHit = True
Hits.Add cell
If Hits.Count = Size Then
Position.BorderAround Weight:=xlMedium
End If
If isPlayer Then
Battleship.Cells(g_logRow, 2).value = "You get a hit on " & cell.Address & "!"
Battleship.Names("PlayerHits").RefersToRange.value = Battleship.Names("PlayerHits").RefersToRange.value + 1
Else
Battleship.Cells(g_logRow, 2).value = "The Computer gets a hit on " & cell.Address
Battleship.Names("ComputerHits").RefersToRange.value = Battleship.Names("ComputerHits").RefersToRange.value + 1
End If
g_logRow = g_logRow + 1
cell.Worksheet.Protect ""
isHit = True
Else
isHit = False
End If
End Function
Public Property Get Hits() As Collection
Set Hits = m_hits
End Property
Public Property Set Hits(ByVal value As Collection)
Set m_hits = value
End Property
Private Sub Class_Initialize()
HitCount = 0
Set Hits = New Collection
End Sub
Public Property Get Size() As Integer
Size = oSize
End Property
Public Property Let Size(ByVal vNewValue As Integer)
oSize = vNewValue
End Property