Determining 32 bit versus 64 bit in VBA — testers welcome!

Greg Truby

MrExcel MVP
Joined
Jun 19, 2002
Messages
10,025
A client from my consulting days is upgrading hardware and the new notebooks are coming w/ 64-bit Excel and so's I need to make the add-in I wrote for them mind its manners and play nice under 64-bit Excel. I had thought this would be relatively straightforward. It turned out to be a bit more convoluted than I expected. Everything I'd seen on the internet told me I could use the conditional compiling constants WIN64 and VBA7 to handle compiling in various environments. But when I got to a "boots-on-the-ground" situation, it proved pretty inconsistent. Eventually I grew so frustrated that I wrote code to see what in tarnation was going on and then ran that code in as many environments as I personally had access to. I am going to share my results and the code that I used to obtain them. I would be ever so grateful if anyone who is interested would try dropping the code into a workbook and running the macro on their computer and then posting the output.

Thanks in advance to anyone who joins the experiment!

Here's the VBA:

VBA Code:
Option Explicit
                                                           
                                                             #If gccc_XL64 Then
Const c_strTest As String = "sixty four"
                                                           
Private Declare PtrSafe Function GetProcAddress _
    Lib "kernel32" _
        (ByVal hModule As LongPtr, _
         ByVal lpProcName As String) _
    As LongPtr

Private Declare PtrSafe Function GetModuleHandle _
    Lib "kernel32" _
    Alias "GetModuleHandleA" _
        (ByVal lpModuleName As String) _
    As LongPtr

Private Declare PtrSafe Function GetCurrentProcess _
    Lib "kernel32" () _
    As LongPtr

Private Declare PtrSafe Function IsWow64Process _
    Lib "kernel32" _
        (ByVal hProcess As LongPtr, _
         ByRef Wow64Process As Long) _
    As Long
                                                                          #Else

Const c_strTest As String = "thirty two"

Private Declare Function GetProcAddress _
    Lib "kernel32" _
        (ByVal hModule As Long, _
        ByVal lpProcName As String) _
    As Long

Private Declare Function GetModuleHandle _
    Lib "kernel32" _
    Alias "GetModuleHandleA" _
        (ByVal lpModuleName As String) _
    As Long

Private Declare Function GetCurrentProcess _
    Lib "kernel32" () _
    As Long

Private Declare Function IsWow64Process _
    Lib "kernel32" _
        (ByVal hProcess As Long, _
         ByRef Wow64Process As Long) _
    As Long
                                                                        #End If
                                                  
                                                                 #If Win64 Then
Const mc_bytWin64 As Byte = 64
                                                                          #Else
Const mc_bytWin64 As Byte = 32
                                                                        #End If


                                                                  #If VBA7 Then
Const mc_bytExcel As Byte = 64
                                                                          #Else
Const mc_bytExcel As Byte = 32
                                                                        #End If

Rem "foobar" - in memory of the legendary nateo
Private Sub foobar(): MsgBox c_strTest, vbInformation: End Sub

Sub Show32or64_Main()
  
    PutResultsInCells
    MsgBox fnBitnessMessage, vbInformation, "A bit o' this and a bit o' that"

End Sub

Private Sub PutResultsInCells()

    Const c_strStartAddr    As String = "B3", _
          c_strNbrFmt       As String = "0 "" bit"""
  
    '// Note:   using unqualified references, so this will
    '// ¯¯¯¯¯   output to the activesheet.
    Dim r As Range
  
    Set r = Range(c_strStartAddr)
  
    With r
      
        .CurrentRegion.Clear
        .Value = "Windows"
        .Resize(, 2).Style = "Heading 3"
      
        With .Offset(1)
            .Value = "#If Win64"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = mc_bytWin64
                .NumberFormat = c_strNbrFmt
            End With
        End With

        With .Offset(2)
            .Value = "Environ"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = fnWindowsBitnessEnviron
                .NumberFormat = c_strNbrFmt
            End With
        End With

        With .Offset(3)
            .Value = "WOW64"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = fnWindowsBitnessIsWow64
                .NumberFormat = c_strNbrFmt
            End With
        End With

        With .Offset(4)
            .Value = "Excel"
            .Resize(, 2).Style = "Heading 3"
            .RowHeight = 30
        End With
      
        With .Offset(5)
            .Value = "#If VBA7"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = mc_bytExcel
                .NumberFormat = c_strNbrFmt
            End With
        End With

        With .Offset(6)
            .Value = "Dimensioning test"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = fnExcelBitnessDim
                .NumberFormat = c_strNbrFmt
            End With
        End With

        With .Offset(7)
            .Value = "Address test"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = fnExcelBitnessDummyAddress
                .NumberFormat = c_strNbrFmt
            End With
        End With
      
        With .Offset(8)
            .Value = "HInstance test"
            .IndentLevel = 1
            With .Offset(, 1)
                .Value = fnExcelBitnessHInstance
                .NumberFormat = c_strNbrFmt
            End With
            With .Resize(, 2).Borders(xlEdgeBottom)
                .LineStyle = xlContinuous
                .ColorIndex = 0
                .TintAndShade = 0
                .Weight = xlThin
            End With
        End With
  
        With .Offset(9)
            .Value = "Version Nbr"
            .IndentLevel = 1
            .Offset(, 1).Value = Application.Version
        End With
      
        With .Offset(10)
            .Value = "Build Nbr"
            .IndentLevel = 1
            .Offset(, 1).Value = Application.Build
        End With
  
    End With    '// starting cell

End Sub '// PutResultsInCells

Function fnBitnessMessage() As String
  
    Let fnBitnessMessage _
          = "COND COMPILE says Windows is " & vbTab & CStr(mc_bytWin64) & " bit" & vbCrLf _
          & "ENVIRON test says Windows is " & vbTab & CStr(fnWindowsBitnessEnviron) & " bit" & vbCrLf _
          & "WOW64 test says Windows is " & vbTab & vbTab & CStr(fnWindowsBitnessIsWow64) & " bit" & vbCrLf _
          & String(24, "—") & vbCrLf _
          & "COND COMPILE says Excel is " & vbTab & vbTab & CStr(mc_bytExcel) & " bit" & vbCrLf _
          & "DIM bitness test says Excel is " & vbTab & vbTab & CStr(fnExcelBitnessDim) & " bit" & vbCrLf _
          & "ADDRESS bitness test says Excel is " & vbTab & CStr(fnExcelBitnessDummyAddress) & " bit" & vbCrLf _
          & "HINSTANCE bitness test says Excel is " & vbTab & CStr(fnExcelBitnessHInstance) & " bit" & vbCrLf

End Function

Function fnWindowsBitnessEnviron() As Byte
    Let fnWindowsBitnessEnviron = IIf(CBool(Len(Environ("ProgramW6432"))), 64, 32)
    End Function

Function fnWindowsBitnessIsWow64() As Byte

                                                             #If gccc_XL64 Then
    Dim h As LongPtr
                                                                          #Else
    Dim h As Long
                                                                        #End If
    Dim lngIs64

    Let h = GetProcAddress(GetModuleHandle("kernel32"), "IsWow64Process")

    '// IsWow64Process function exists.  Now use the function
    '// to determine if we are running under Wow64
    If h > 0 Then IsWow64Process GetCurrentProcess(), lngIs64
    Let fnWindowsBitnessIsWow64 = IIf(CBool(lngIs64), 64, 32)

End Function

Function fnExcelBitnessDim() As Byte
  
                                                             #If gccc_XL64 Then
    Dim ptrTest As LongPtr
                                                                          #Else
    Dim ptrTest As Long
                                                                        #End If
    Let fnExcelBitnessDim = IIf(LenB(ptrTest) = 4, 32, 64)
    End Function

Function fnExcelBitnessDummyAddress() As Byte
    Let fnExcelBitnessDummyAddress = IIf(TypeName(AddressOf fnDummy) = "Long", 32, 64)
    End Function

Function fnDummy()
    End Function
  
Function fnExcelBitnessHInstance() As Byte
  
    Dim vntHinstance As Variant
  
    On Error Resume Next
    vntHinstance = Application.Hinstance
    Let fnExcelBitnessHInstance = IIf(Err = 0, 32, 64)
    End Function

'// just a utility 'cuz I forget 'em
Private Sub AllEnvironVariables()
    Dim strEnviron As String
    Dim VarSplit As Variant
    Dim i As Long
    For i = 1 To 255
        strEnviron = Environ$(i)
        If LenB(strEnviron) = 0& Then GoTo TryNext:
        VarSplit = Split(strEnviron, "=")
        If UBound(VarSplit) > 1 Then Stop
        Range("A" & Range("A" & Rows.Count).End(xlUp).Row + 1).Value = i
        Range("B" & Range("B" & Rows.Count).End(xlUp).Row + 1).Value = VarSplit(0)
        Range("C" & Range("C" & Rows.Count).End(xlUp).Row + 1).Value = VarSplit(1)
TryNext:
    Next
End Sub

Comments/Notes: Since the built-in conditional compiling constants were behaving like obnoxious drunks, I used a conditional compiling constant of my own. This was only needed when I was trying to compile in Excel 2003 or 2007. For Excel 2010 or better, the LongPtr variable declarations would compile, even when Excel itself was 32-bit. If you are testing under 2007 or lower, then you'd need to flip the compiling constant to false (0). In the VBE it's under Tools | VBAProject Properties...

MrExcel Post 32 or 64.png


Here are the results I obtained in various environments color coded to reflect whether the results were correct or incorrect. As you can see, in my testing the WIN64 and VBA7 conditional compiling constants proved about a trustworthy as a politician's oath:

Show32or64 Excel and OS.xlsm
ABCDEFGH
1WindowsWin 7Win 7Win 7Win 10 PWin 7Win 10 HWin 10 P
2Excel20032007201020102013O365 / 32O365 / 64
3Windows
4#If Win6432 bit32 bit32 bit32 bit32 bit32 bit64 bit
5Environ64 bit64 bit64 bit64 bit64 bit64 bit64 bit
6WOW6464 bit64 bit64 bit64 bit64 bit64 bit32 bit
7Excel
8#If VBA732 bit32 bit64 bit64 bit64 bit64 bit64 bit
9Dimensioning test32 bit32 bit32 bit32 bit32 bit32 bit64 bit
10Address test32 bit32 bit32 bit32 bit32 bit32 bit64 bit
11HInstance test32 bit32 bit32 bit32 bit32 bit32 bit64 bit
12Version Nbr11121414151616
13Build Nbr840467877244724452071192911929
Consolidated


I should comment that the 64-bit Excel is running in a virtual machine. I'm wondering if that might not be the reason the WOW64 test for the OS bitness failed.
 
Last edited:

Excel Facts

Whats the difference between CONCAT and CONCATENATE?
The newer CONCAT function can reference a range of cells. =CONCATENATE(A1,A2,A3,A4,A5) becomes =CONCAT(A1:A5)
Hi Greg,

Also I would add that the #Win64 compilation constant is used in very few screnarios :

a) When the same API function has two different names depending on the bitness of the calling application.

One good example of this is the SetWindowLongA API (ANSI version) . This API takes the name of SetWindowLongPtrA in the 64-bit user32.dll in the C:\Windows\system32 directory while it takes the name of SetWindowLongA in the 32-bit user32.dll in the C:\Windows\SYSWOW64 directory.

So, in a 64-bit OS, an office application that is 64-bit will call SetWindowLongPtrA while a 32-bit office application whill call SetWindowLongA

In this case, in order to write code that is compatible with both 32 and 64 bit versions of office, we will need to use the #Win64 compilation constant something along these lines :
VBA Code:
#If VBA7 Then

    #If Win64 Then
                  '(VBA7 64-Bit)
        Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
    #Else
                 '(VBA7 32-Bit)
        Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As Long) As LongPtr
    #End If
   
#Else
                 '(VBA6)
    Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
   
#End If



b) When the same API function has different arguments depending on the bitness of the calling application.
The same logic as that of SetWindowLong applies here. A good example is the WindowFromPoint API:
VBA Code:
#If VBA7 Then

    #If Win64 Then
                  '(VBA7 64-Bit)
           Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal Point As LongPtr) As LongPtr
    #Else
                  '(VBA7 32-Bit)
           Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As LongPtr
    #End If
   
#Else
                  '(VBA6)
    Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
   
#End If


Not to forget that #Win64 will also be needed throughout the actual code .. Here is a good working example where WindowFromPoint is used;

Notice both the #If VBA7 Then and the #If Win64 Then clauses located inside the IsMouseOverListBox supporting function.
 
Upvote 0

Forum statistics

Threads
1,214,601
Messages
6,120,460
Members
448,965
Latest member
grijken

We've detected that you are using an adblocker.

We have a great community of people providing Excel help here, but the hosting costs are enormous. You can help keep this site running by allowing ads on MrExcel.com.
Allow Ads at MrExcel

Which adblocker are you using?

Disable AdBlock

Follow these easy steps to disable AdBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the icon in the browser’s toolbar.
2)Click on the "Pause on this site" option.
Go back

Disable AdBlock Plus

Follow these easy steps to disable AdBlock Plus

1)Click on the icon in the browser’s toolbar.
2)Click on the toggle to disable it for "mrexcel.com".
Go back

Disable uBlock Origin

Follow these easy steps to disable uBlock Origin

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back

Disable uBlock

Follow these easy steps to disable uBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back
Back
Top