blob: 9c1aca54e4ae89694712e22e0a2d93d5efa28b28 [file] [log] [blame]
Private Sub Worksheet_BeforeDoubleClick(ByVal Target As Range, Cancel As Boolean)
Dim sheet As Worksheet
If g_gameEnded = True Then
Exit Sub
End If
Set sheet = ThisWorkbook.ActiveSheet
If g_Ships Is Nothing Then Code.AddShips Battleship.Range(board1)
If Collide(Target, Battleship.Range(board1)) Then
If Target.Borders(xlDiagonalUp).Weight <> xlMedium Then
SetHit Target
Dim Ship
Dim isHit As Boolean
isHit = False
For Each Ship In g_Ships
If Ship.isHit(Target.Cells(1, 1), True) Then
If CheckWinner(g_Ships) Then
MsgBox "You win!", vbOKOnly + vbExclamation, "Battleships"
g_gameEnded = True
Cancel = True
Exit Sub
End If
isHit = True
Exit For
End If
Next
If isHit = False Then
Unprotect
Battleship.Cells(g_logRow, 2).value = "You get a miss on " & Target.Address
Battleship.Names("PlayerMisses").RefersToRange.value = Battleship.Names("PlayerMisses").RefersToRange.value + 1
g_logRow = g_logRow + 1
Protect ""
End If
ComputerPlay.Move
End If
End If
Cancel = True
End Sub
Private Sub Worksheet_SelectionChange(ByVal Target As Range)
Target.Cells(1, 1).Select
End Sub