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:
Bill, Fluff, Jon, Mark - thank you so much for your input.

Microsoft doesn't support 2003 or 2007 any more (and support for 2010 goes away in only a matter of months). Simplify your life and ignore them.

Spoken like a man who has the luxury of controlling his own Excel-destiny! ;) Unfortunately the vast majority of Excel users have little control over what version of Excel corporate IT lets them use. And even if you are enough of a power user to get IT to upgrade you, if your code is gonna get shared, you gotta make sure it'll play nice on the machines of those who couldn't wheedle an upgrade out of corporate IT.

A simple way to determine bitness is from the product code. ... That fourth block of four characters is 0000 for 32-bit and 1000 for 64-bit. ...

Thanks! I did not come across that little nugget in my research.

Of course, getting those compiler constants to work out can be frustrating. It has to be something like this:

VBA Code:
#If Vba7 Then

' VBA7 (Office 2010 or newer)

  #If Win64 Then

    ' Code is running in 64-bit version of Microsoft Office

    Declare PtrSafe Function ... (with 64-bit data types)

  #Else

    ' Code is running in 32-bit version of Microsoft Office

    Declare PtrSafe Function ... (with 32-bit data types)

  #End If

#Else

  ' VBA6 or earlier (Office 2007 or earlier)

  Declare Function ...

#End If

I remember seeing this nested construct somewhere, but the version of it I saw didn't have the comments in there which explained what was going on. Now, of course, it looks kinda obvious. It certainly didn't seem quite so obvious when I was trying to suss out just why I kept winding up off in the weeds.

The real trick is finding the right variable types for each declaration. The internet gets them about half right.

Jan Karel with an assist from Charles — God bless the both of them — have done a good job (at least for all of the ones he looked at) on his website. Excel: Declaring API functions in 64 bit Office

Thanks again for all the great information, Jon.

...I get the impression from your initial post that you may have misunderstood what those constants are testing. Win64 doesn't actually test the bitness of Windows, in spite of its name. WIN64 lets you know that your code is running in 64 bit Office (which by extension must be in 64 bit Windows). VBA7 simply tells you that you are, as implied this time, running VBA7 - i.e. you are in Office 2010 or later. Between the two of them, they should cater for pretty much any situation you actually need to code around.

Rory, that is precisely what I had mistakenly thought, i.e. that the WIN64 compiling constant referred to WINDOWS and not OFFICE. Furthermore, I had not understood that I could use ptrSafe versions of API calls and the LongPtr data type in 32-bit Excel; I had mistakenly thought you had to be using 64-bit Office for that.
 
Upvote 0

Excel Facts

Show numbers in thousands?
Use a custom number format of #,##0,K. Each comma after the final 0 will divide the displayed number by another thousand
Ah, no. The whole point of LongPtr is that it will resolve to a Long in 32bit Office and a LongLong in 64 bit.
 
Upvote 0

Ah, no. The whole point of LongPtr is that it will resolve to a Long in 32bit Office and a LongLong in 64 bit.

Yeah, now that I've read the article John W. linked to, I see that. Alas, my research had not led me to that article so I had not understood that LongPtr resolved differently under different bit-versions of Office. Thank you very much for the link to that article, John.
 
Upvote 0
It is confusing but IsWow64Process will always return FALSE when applied to a 64-bit Process .

IsWow64Process determines if a running process is on WOW64, which is only set to TRUE, if the process is 32-bit and the OS is 64-bit.
So in other words, the FALSE result your are getting with your WIN64 test is actually correct .(when excel 64bit and OS 64-bit)

In addition, IsWow64Process is not a reliable way to detect whether the operating system is a 64-bit version of Windows because the Kernel32.dll in current versions of 32-bit Windows also contains this function.
 
Last edited:
Upvote 0
Jaafar! Great to see you! Thanks! This is precisely the kind of thing that happens when I fight above my weight class in coding. :rolleyes: I'd seen that example and thought I understood what it was doing. (I wish I knew even 10% of what you know about API calls, etc.)
 
Upvote 0
Jaafar! Great to see you! Thanks! This is precisely the kind of thing that happens when I fight above my weight class in coding. :rolleyes: I'd seen that example and thought I understood what it was doing. (I wish I knew even 10% of what you know about API calls, etc.)

I didn't manage to get a sound grab on this 32 vs 64 subject until I installed 64-bit Office\64-bit OS and got my hands dirty.

Quote:
"Alas, my research had not led me to that article so I had not understood that LongPtr resolved differently under different bit-versions of Office. "

Obviously, LongPtr won't compile in VBA6 so using the Long type will still be needed in cross-platform api code in oder to also work in excel 2007 and backwards.

Regards.
 
Upvote 0
I'd be mo st interested in learning where your 64 bit conversion went haywire. I haven't had many issues yet and most of my tools work on both bitnesses. I assume you saw my page on API declarations: Excel: Declaring API functions in 64 bit Office

Yes! Your page is amazing! I cannot thank you and Charles enough for that. Applying the information you provided helped me get my declarations working.

My main problem — as Rory and John correctly assessed — was not understanding exactly what the conditional compiling constants were telling me. I had thought that the WIN64 constant was used to determine Window's bitness, not Excel's. And I thought VBA7 was to determine Excel's bitness, not whether or not one could use PtrSafe, LongPtr, etc. Therefore, even when I had used your web page to get the declaration written correctly, I had the declarations in the wrong #IF clauses.

So far I have not run into it - I have only seen references to it in articles, but one thing that I'm still a little fuzzy on is whole LongLong thing. For example, your article links to the MS article on compatibility. And that article reads as follows:

As stated earlier, there are two new conditional compilation constants: VBA7 and Win64. To ensure backward compatibility with previous versions of Microsoft Office, you use the VBA7 constant (this is the more typical case) to prevent 64-bit code from being used in the earlier version of Microsoft Office. For code that is different between the 32-bit version and the 64-bit version, such as calling a math API which uses LongLong for its 64-bit version and Long for its 32-bit version, you use the Win64 constant. The following code demonstrates the use of these two constants.
VBA Code:
    #if Win64 then
       Declare PtrSafe Function MyMathFunc Lib "User32" (ByVal N As LongLong) As LongLong
    #else
       Declare Function MyMathFunc Lib "User32" (ByVal N As Long) As Long
    #end if
    #if VBA7 then
       Declare PtrSafe Sub MessageBeep Lib "User32" (ByVal N AS Long)
    #else
       Declare Sub MessageBeep Lib "User32" (ByVal N AS Long)
    #end if

It appears that in some cases one must change an arguments from a Long to a LongLong whereas in other cases one changes it from a Long to a LongPtr. I can't seem to find information that would tell me when to use LongLong instead of just always using LongPtr.
 
Upvote 0
That's a confusing example of the Win64 constant in the compatibliity article as it could also be written:

VBA Code:
    #if VBA7 then
       Declare PtrSafe Function MyMathFunc Lib "User32" (ByVal N As LongPtr) As LongPtr
       Declare PtrSafe Sub MessageBeep Lib "User32" (ByVal N AS Long)
    #else
       Declare Function MyMathFunc Lib "User32" (ByVal N As Long) As Long
       Declare Sub MessageBeep Lib "User32" (ByVal N AS Long)
    #end if

On VBA7, you always use LongPtr; you never need LongLong.

As 64-bit Visual Basic for Applications overview says:

"To write code that can port between both 32-bit and 64-bit versions of Office, you only need to use the new LongPtr type alias instead of Long or LongLong for all pointers and handle values."
 
Upvote 0
The crux is as long as you're using VBA7 you can safely use LongPtr as it gets converted to Long when needed and to LongLong when needed automatically.
 
Upvote 0

Forum statistics

Threads
1,214,641
Messages
6,120,685
Members
448,978
Latest member
rrauni

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