Skip to content

Commit bfc6447

Browse files
authored
Merge pull request #18 from Imh0t3b/master
Fixes conditional compilation to work with Excel 2007.
2 parents 346f27d + 7806a53 commit bfc6447

File tree

3 files changed

+28
-10
lines changed

3 files changed

+28
-10
lines changed

Battleship.xlsm

-765 KB
Binary file not shown.

src/GameSheet.doccls

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -335,7 +335,9 @@ Private Sub ShowInformation(ByVal message As String)
335335
.Characters.Delete
336336
.Characters.Text = vbNewLine & message
337337
.VerticalAlignment = xlVAlignTop
338-
.VerticalOverflow = xlOartVerticalOverflowEllipsis
338+
#If Version > "12.0" Then
339+
.VerticalOverflow = xlOartVerticalOverflowEllipsis
340+
#End If
339341
.HorizontalAlignment = xlHAlignLeft
340342
End With
341343
End With
@@ -357,7 +359,9 @@ Public Sub ShowError(ByVal message As String)
357359
.Characters.Delete
358360
.Characters.Text = vbNewLine & message
359361
.VerticalAlignment = xlVAlignTop
360-
.VerticalOverflow = xlOartVerticalOverflowEllipsis
362+
#If Version > "12.0" Then
363+
.VerticalOverflow = xlOartVerticalOverflowEllipsis
364+
#End If
361365
.HorizontalAlignment = xlHAlignLeft
362366
End With
363367
End With

src/Win32API.bas

Lines changed: 22 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -32,11 +32,11 @@ Private Const EM_SETEVENTMASK = (WM_USER + 69)
3232
#Else
3333
Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
3434

35-
Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWndParent As Long, ByVal hWndChildAfter As Long, ByVal lpszClass As String,ByVal lpszWindow As String) As Long
36-
Private Declare Function InvalidateRect Lib "user32" (ByVal hWnd As Long, ByRef lpRect As Long, ByVal bErase As Long) As Long
37-
Private Declare Function UpdateWindow Lib "user32" (ByVal hWnd As Long) As Long
38-
Private Declare Function LockWindowUpdate Lib "user32" (ByVal hWnd As Long) As Long
39-
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
35+
Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWndParent As Long, ByVal hWndChildAfter As Long, ByVal lpszClass As String, ByVal lpszWindow As String) As Long
36+
Private Declare Function InvalidateRect Lib "user32" (ByVal hwnd As Long, ByRef lpRect As Long, ByVal bErase As Long) As Long
37+
Private Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) As Long
38+
Private Declare Function LockWindowUpdate Lib "user32" (ByVal hwnd As Long) As Long
39+
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
4040

4141
Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
4242
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hwnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
@@ -53,17 +53,24 @@ Public Sub ScreenUpdate(ByVal bState As Boolean)
5353
Application.ScreenUpdating = bState
5454
Exit Sub
5555
#End If
56-
56+
#If VBA7 Then
5757
Dim hwnd As LongPtr
58+
#Else
59+
Dim hwnd As Long
60+
#End If
5861
hwnd = GethWndWorkbook
5962

6063
'Using SendMessage:
6164
' - Turn off redraw for faster and smoother action:
6265
' SendMessage hEdit, %WM_SETREDRAW, 0, 0
6366
' - Turn on redraw again and refresh:
6467
' SendMessage hEdit, %WM_SETREDRAW, 1, 0
65-
68+
#If VBA7 Then
6669
Dim lResult As LongPtr
70+
#Else
71+
Dim lResult As Long
72+
#End If
73+
6774
If bState Then
6875
lResult = SendMessage(hwnd, WM_SETREDRAW, 1&, 0&)
6976
lResult = InvalidateRect(hwnd, 0&, 1&)
@@ -76,12 +83,19 @@ Public Sub ScreenUpdate(ByVal bState As Boolean)
7683

7784
End Sub
7885

79-
Private Function GethWndWorkbook() As LongPtr
86+
#If VBA7 Then
87+
Private Function GethWndWorkbook() As LongPtr
8088

8189
Dim hWndXLDESK As LongPtr
90+
#Else
91+
Private Function GethWndWorkbook() As Long
92+
93+
Dim hWndXLDESK As Long
94+
#End If
8295
hWndXLDESK = FindWindowEx(Application.hwnd, 0, "XLDESK", vbNullString)
8396

8497
GethWndWorkbook = FindWindowEx(hWndXLDESK, 0, vbNullString, ThisWorkbook.Name)
8598

8699
End Function
87100

101+

0 commit comments

Comments
 (0)