Results 1 to 7 of 7

Thread: Version Info using VBA and registry quirks

Threaded View

Previous Post Previous Post   Next Post Next Post
  1. #7
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    This is post #7
    https://www.excelfox.com/forum/showt...ll=1#post24876
    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues?p=24876&viewfull=1#pst24876




    This is post #552
    https://www.excelfox.com/forum/showt...ge56#post24323
    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues/page56#post24323
    https://www.excelfox.com/forum/showt...ll=1#post24323
    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues?p=24317&viewfull=1#post24323





    Edit: I gave up with this post after getting so many quirky results in Windows 10 and windows 11, so I started this Thread


    Some functions and rough notes on Versions on some computers used in the testings from this page 56 and page 55 and a few other related forum postings

    Its useful to keep track of some of your computer specs, and Office versions when playing around with the codings on this page.
    The macro below, Sub WhatAmI() ( along with the functions under it which go with it) may help to get some of that info. Run it and some info should appear in the Immediate Window. (From the VB Editor, hold the Ctrl key down and then hit key g to get that Immediate Window up)
    Note there are a few bugs and quirks :
    _ Application.OperatingSystem can give quirky answers in windows 11 , so the operating system result may be wrong for if you have Windows 11. In fact currently it seems a bit wonky everywhere
    _I don’t know if that macro gets it correct in Office versions 2016, 2019,2021, 2024 or 365, since I don’t have them versions to check. My guess is that it might be a bit iffy for 2016 2019,2024 or 365

    Code:
    Sub WhatAmI()   '     https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues?p=24323&viewfull=1#post24323     https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues/page56#post24323
    Debug.Print ExcelVersion & "    " & Application.OperatingSystem & "     (ApplicationVersion " & CLng(Val(Application.Version)) & ")     Computer named " & CreateObject("WScript.Network").ComputerName                      '  Environ$("computername")      Nigel Heffernan  https://stackoverflow.com/questions/3551055/how-to-get-name-of-the-computer-in-vba/10108951#10108951
    '    Windows 11 (2021)                  ...
    '    Windows 10 S (2017) ...
    '    Windows 10 (2015) - MS Version 6.4. ...
    '    Windows 8/8.1 (2012-2013) - MS Version 6.2/6.3. ...
    '    Windows 7 (2009) - MS Version 6.1. ...
    '    Windows Vista (2006) - MS Version 6.0. ...
    '    Windows XP (2001) - MS Version 5.1. ...
    '    Windows 2000 (2000) - MS Version 5.0.
    End Sub
    
    Private Function ExcelVersion() As String ' From Rory somewhere, then a blind mod for above 2016 from https://excelguru.ca/check-the-application-version-in-modern-office/  , which probably does not work too well - https://excelguru.ca/check-the-application-version-in-modern-office/#comment-358558
    Dim Temp    As String
        'On Error Resume Next
        #If Mac Then
            Select Case CLng(Val(Application.Version))
             Case 11: Temp = "Excel 2004"
             Case 12: Temp = "Excel 2008" ' this should NEVER happen!
             Case 14: Temp = "Excel 2011"
             Case 15: Temp = "Excel 2016 (Mac)"
             Case Else: Temp = "Unknown"
            End Select
        #Else
            Select Case CLng(Val(Application.Version))
             Case 9: Temp = "Excel 2000"
             Case 10: Temp = "Excel 2002"
             Case 11: Temp = "Excel 2003"
             Case 12: Temp = "Excel 2007"
             Case 14: Temp = "Excel 2010"
             Case 15: Temp = "Excel 2013"
             Case 16:  '    https://excelguru.ca/check-the-application-version-in-modern-office/
              Let Temp = ForVersion16()         '
             Case Else: Temp = "Unknown"
            End Select
        #End If
        #If Win64 Then
         Let Temp = Temp & " 64 bit"
        #Else
         Let Temp = Temp & " 32 bit"
        #End If
    
     Let ExcelVersion = Temp
    End Function
    Function ForVersion16() As String  '    https://excelguru.ca/check-the-application-version-in-modern-office/  This may be crap - https://excelguru.ca/check-the-application-version-in-modern-office/#comment-358558
    'Test the Office application version,   'Written by Ken Puls (www.excelguru.ca)   '  ...."From Office 2016 onwards, Microsoft has not revved the Application.Version number - they all show as 16.0 - giving you no way to differentiate between versions."....
    Dim registryObject As Object
    Dim rootDirectory As String, keyPath As String
    Dim arrEntryNames As Variant, arrValueTypes As Variant
    Dim x As Long
    'Check for existence of Licensing key
     Let keyPath = "Software\Microsoft\Office\" & CStr(Application.Version) & "\Common\Licensing\LicensingNext"
     Let rootDirectory = "."
     Set registryObject = GetObject("winmgmts:{impersonationLevel=impersonate}!\\" & rootDirectory & "\root\default:StdRegProv")
    registryObject.EnumValues &H80000001, keyPath, arrEntryNames, arrValueTypes
    On Error GoTo ErrorExit
        For x = 0 To UBound(arrEntryNames)
            If InStr(arrEntryNames(x), "365") > 0 Then
             Let ForVersion16 = 365
            Exit Function
            End If
            If InStr(arrEntryNames(x), "2019") > 0 Then
             Let ForVersion16 = 2019
            Exit Function
            End If
            If InStr(arrEntryNames(x), "2021") > 0 Then
             Let ForVersion16 = 2021
            Exit Function
            If InStr(arrEntryNames(x), "2024") > 0 Then
             Let ForVersion16 = 2024
            Exit Function
            End If
        Next x
    Exit Function
    ErrorExit:
    'Version 16, but no licensing key. Must be Office 2016
     Let ForVersion16 = 2016
    End Function
    







    'Some typical results of my computers for future reference for me because I keep forgetting which versions I have where
    Code:
     '  ExcelVersion      Application.OperatingSystem        (CLng(Val(Application.Version)   CreateObject("WScript.Network").ComputerName                    '  Environ$("computername")      Nigel Heffernan  https://stackoverflow.com/questions/3551055/how-to-get-name-of-the-computer-in-vba/10108951#10108951
    '(based on App.version)
    '  Excel 2007 32 bit      Windows (32-bit) NT 6.00              (ApplicationVersion 12)     Alan's Computer named ELSTON-LAPTOP   KB Vista     Office 2007
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.00              (ApplicationVersion 14)     Computer named ELSTON-PC              Alan's Computer GB Vista     Office 10
    
    
    '  Excel 2003 32 bit      Windows (32-bit) NT 6.01              (ApplicationVersion 11)     Computer named ALAN-PC                 Martin Windows 7 Pro   Office 2003
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.01              (ApplicationVersion 14)     Computer named ALAN-PC                Martin Windows 7 pro   Office 2010
    
    
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.02              (ApplicationVersion 14)     Computer named TM5730G                Alan's Computer Verranda Windows 10 Office 10
    '  Excel 2013 32 bit      Windows (32-bit) NT :.00              (ApplicationVersion 15)     Computer named DESKTOP-G7BIH1B        Alan's Computer SerSzuD2 Windows 10 Office 13
    '  Excel 2016 (Windows) 32 bit    Windows (32-bit) NT 10.00     (ApplicationVersion 16)     Alan's Computer named DESKTOP-14C4HCR   Torrox Windows 10  Office 2016
    
    
    
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.02              (ApplicationVersion 14)     Computer named ASPIRE7730G     Elfy Windows 11    Office 10
    '
    Last edited by DocAElstein; 10-28-2024 at 01:33 AM.

Similar Threads

  1. ADS info via VBA 64bit
    By TML59 in forum Excel Help
    Replies: 9
    Last Post: 07-13-2024, 03:43 PM
  2. Replies: 26
    Last Post: 07-17-2013, 11:42 AM
  3. Office Version Independent Non-Activex Date Time Picker Using Form Controls
    By Excel Fox in forum Excel and VBA Tips and Tricks
    Replies: 0
    Last Post: 07-17-2013, 12:27 AM
  4. Info: different Value !
    By PcMax in forum Excel Help
    Replies: 2
    Last Post: 04-22-2012, 04:13 PM
  5. Version 2003 to 2007
    By PcMax in forum Excel Help
    Replies: 5
    Last Post: 11-23-2011, 07:52 PM

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •