-
Mar 19th, 2024, 04:45 PM
#1
[VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DATA
The simplest version APIs all lie unless you have a manifest. If you want to be sure you get the real version no matter what, there's various more complicated techniques. The one I had been using involved reading the version info from kernel32.dll. This way is easier, and involves a neat technique. The KUSER_SHARED_DATA type is always resident in memory. You can declare it, then copy it, with no APIs besides CopyMemory.
The version info can be extracted directly. To use this, you need no declares besides CopyMemory:
Code:
Dim dwMajor As Long, dwMinor As Long, dwBuild As Long
CopyMemory dwMajor, ByVal &H7FFE026C, 4
CopyMemory dwMinor, ByVal &H7FFE0270, 4
CopyMemory dwBuild, ByVal &H7FFE0260, 4
Debug.Print dwMajor & "." & dwMinor & "." & dwBuild
That's based on the offsets of the members of the full type.
If you're interested in the full type, the following is the expanded form: It also returns a ton of other info.
Code:
Public Type LARGE_INTEGER
#If (TWINBASIC = 1) Or (Win64 = 1) Then
QuadPart As LongLong
#Else
lowpart As Long
highpart As Long
#End If
End Type
Public Type KSYSTEM_TIME
LowPart As Long '0x0
High1Time As Long '0x4
High2Time As Long '0x8
End Type
Public Enum NT_PRODUCT_TYPE
NtProductWinNt = 1
NtProductLanManNt = 2
NtProductServer = 3
End Enum
Public Enum ALTERNATIVE_ARCHITECTURE_TYPE
StandardDesign = 0
NEC98x86 = 1
EndAlternatives = 2
End Enum
Public Enum VER_SUITE_VALUES
VER_SERVER_NT = &H80000000
VER_WORKSTATION_NT = &H40000000
VER_SUITE_SMALLBUSINESS = &H00000001
VER_SUITE_ENTERPRISE = &H00000002
VER_SUITE_BACKOFFICE = &H00000004
VER_SUITE_COMMUNICATIONS = &H00000008
VER_SUITE_TERMINAL = &H00000010
VER_SUITE_SMALLBUSINESS_RESTRICTED = &H00000020
VER_SUITE_EMBEDDEDNT = &H00000040
VER_SUITE_DATACENTER = &H00000080
VER_SUITE_SINGLEUSERTS = &H00000100
VER_SUITE_PERSONAL = &H00000200
VER_SUITE_BLADE = &H00000400
VER_SUITE_EMBEDDED_RESTRICTED = &H00000800
VER_SUITE_SECURITY_APPLIANCE = &H00001000
VER_SUITE_STORAGE_SERVER = &H00002000
VER_SUITE_COMPUTE_SERVER = &H00004000
VER_SUITE_WH_SERVER = &H00008000&
VER_SUITE_MULTIUSERTS = &H00020000
End Enum
Public Type KUSER_SHARED_DATA
TickCountLowDeprecated As Long '0x0
TickCountMultiplier As Long '0x4
InterruptTime As KSYSTEM_TIME '0x8
SystemTime As KSYSTEM_TIME '0x14
TimeZoneBias As KSYSTEM_TIME '0x20
ImageNumberLow As Integer '0x2c
ImageNumberHigh As Integer '0x2e
NtSystemRoot(0 To 259) As Integer '0x30
MaxStackTraceDepth As Long '0x238
CryptoExponent As Long '0x23c
TimeZoneId As Long '0x240
LargePageMinimum As Long '0x244
' Reserved2(0 To 6) As Long '0x248
AitSamplingValue As Long '0x24C
AppCompatFlag As Long '0x250
#If (TWINBASIC = 1) Or (Win64 = 1) Then
RNGSeedVersion As LongLong
#Else
RNGSeedVersion As Currency
#End If
GlobalValidationRunlevel As Long
TimeZoneBiasStamp As Long
NtBuildNumber As Long
NtProductType As NT_PRODUCT_TYPE '0x264
ProductTypeIsValid As Byte '0x268
Reserved0 As Byte
NativeProcessorArchitecture As Integer
NtMajorVersion As Long '0x26c
NtMinorVersion As Long '0x270
ProcessorFeatures(0 To 63) As Byte '0x274
Reserved1 As Long '0x2b4
Reserved3 As Long '0x2b8
TimeSlip As Long '0x2bc
AlternativeArchitecture As ALTERNATIVE_ARCHITECTURE_TYPE '0x2c0
BootId As Long 'Windows 10+ only
SystemExpirationDate As LARGE_INTEGER '0x2c8
SuiteMask As VER_SUITE_VALUES '0x2d0
KdDebuggerEnabled As Byte '0x2d4
MitigationPolicies As Byte '0x2d5
CyclesPerYield As Integer 'Only on Win10 1903 and higher
ActiveConsoleId As Long '0x2d8
DismountCount As Long '0x2dc
ComPlusPackage As Long '0x2e0
LastSystemRITEventTickCount As Long '0x2e4
NumberOfPhysicalPages As Long '0x2e8
SafeBootMode As Byte '0x2ec
VirtualizationFlags As Byte
Reserved12(1) As Byte
SharedDataFlags As Long '0x2f0 NOTE: TraceLogging on 2k/XP
DataFlagsPad(0) As Long
#If (TWINBASIC = 1) Or (Win64 = 1) Then
TestRetInstruction As LongLong '0x2f8
#Else
TestRetInstruction As Currency
#End If
SystemCall As Long '0x300
SystemCallReturn As Long '0x304
#If (TWINBASIC = 1) Or (Win64 = 1) Then
SystemCallPad(0 To 2) As LongLong '0x308
TickCountQuad As LongLong '0x320
#Else
SystemCallPad(0 To 2) As Currency
TickCountQuad As Currency
#End If
'union
'{
' volatile struct _KSYSTEM_TIME TickCount; //0x320
'TickCount As KSYSTEM_TIME
ReservedTickCountOverlay(1) As Long 'Since not using _KSYSTEM_TIME
'};
Cookie As Long '0x330
'Wow64SharedInformation(0 To 15) As Long '0x334
End Type
There's a lot more on the end, but it's not particularly useful, varies from version to version. The one given will work on XP-11.
Then using it is as simple as:
Code:
#If VBA7 Then
Public Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
#Else
Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
#End If
Private Sub ReadRealVersion()
Dim kusd As KUSER_SHARED_DATA
CopyMemory kusd, ByVal &H7ffe0000, LenB(kusd)
Debug.Print kusd.NtMajorVersion & "." & kusd.NtMinorVersion & "." & kusd.NtBuildNumber
End Sub
The address is the same for both 32bit and 64bit, so need for an alternate version.
The type as provided here is compatible with XP through 11. Build number is only correct on 10/11, but it's much less significant earlier anyway. The type can be truncated after ProcessorFeatures for Windows 2000 and NT4 compatibility-- the top snippet without declares works on NT4-11.
Last edited by fafalone; Mar 21st, 2024 at 04:28 AM.
-
Mar 20th, 2024, 06:02 AM
#2
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Did you check LARGEADDRESSAWARE processes?
cheers,
</wqw>
-
Mar 20th, 2024, 09:25 AM
#3
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I'm not seeing any issue... I compiled an exe in tB in LAA and it worked fine; were you seeing a problem with however you get VB6 to compile with that?
-
Mar 20th, 2024, 10:41 AM
#4
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Didn't test it but the fixed address is halfway through address space and looks weird for LAA process.
cheers,
</wqw>
-
Mar 20th, 2024, 05:50 PM
#5
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Seems even weirder to me that the address is the same on both 32 and 64bit, but it works. The address is documented; there's Microsoft-written articles talking about it and the struct has an MSDN entry. Having a fixed address is one of the main points of it, it seems. The only time it's different is when you're in kernel mode; it's got a separate fixed address for that.
-
Mar 21st, 2024, 04:29 AM
#6
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I updated the post with an even easier method. I realized you don't even need the declares.
Code:
Dim dwMajor As Long, dwMinor As Long, dwBuild As Long
CopyMemory dwMajor, ByVal &H7FFE026C, 4
CopyMemory dwMinor, ByVal &H7FFE0270, 4
CopyMemory dwBuild, ByVal &H7FFE0260, 4
MsgBox dwMajor & "." & dwMinor & "." & dwBuild
That's it, nothing else besides CopyMemory needed, and works on Windows NT4 through 11, on 32bit and 64bit.
-
Mar 21st, 2024, 05:45 AM
#7
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Wicked! Here is a single API call impl
Code:
Dim aBuffer(0 To 4) As Long
Call CopyMemory(aBuffer(0), ByVal &H7FFE0260, 20)
Debug.Print aBuffer(3) & "." & aBuffer(4) & "." & aBuffer(0)
. . . or wrapped in a property
Code:
Option Explicit
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Enum UcsOsVersionEnum
ucsOsvNt4 = 400
ucsOsvWin98 = 410
ucsOsvWin2000 = 500
ucsOsvXp = 501
ucsOsvVista = 600
ucsOsvWin7 = 601
ucsOsvWin8 = 602
[ucsOsvWin8.1] = 603
ucsOsvWin10 = 1000
End Enum
Private Sub Form_Load()
Dim lBuildNo As Long
Debug.Print RealOsVersion(lBuildNo), lBuildNo
End Sub
Private Property Get RealOsVersion(Optional BuildNo As Long) As UcsOsVersionEnum
Dim aBuffer(0 To 4) As Long
Call CopyMemory(aBuffer(0), ByVal &H7FFE0260, 20)
BuildNo = aBuffer(0)
RealOsVersion = aBuffer(3) * 100 + aBuffer(4)
End Property
cheers,
</wqw>
-
Mar 21st, 2024, 06:01 AM
#8
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
And if "dwBuild >= 22000" then it's Windows 11. 
What does your "ucs" abbreviation stand for?
-
Mar 21st, 2024, 06:09 AM
#9
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Yup this is my new standard now... I keep version info around and call ReadWindowsVersion on startup.
Code:
Private bIsWinVistaOrGreater As Boolean
Private bIsWin7OrGreater As Boolean
Private bIsWin8OrGreater As Boolean
Private bIsWin10OrGreater As Boolean
Private bIsWinRS5OrGreater As Boolean
Private bIsWin11OrGreater As Boolean
Private Sub ReadWindowsVersion()
Dim dwMajor As Long, dwMinor As Long, dwBuild As Long
CopyMemory dwMajor, ByVal &H7FFE026C, 4
CopyMemory dwMinor, ByVal &H7FFE0270, 4
CopyMemory dwBuild, ByVal &H7FFE0260, 4
If dwMajor >= 6 Then
bIsWinVistaOrGreater = True
If dwMinor >= 1& Then bIsWin7OrGreater = True
If dwMinor >= 2& Then bIsWin8OrGreater = True
If (dwMinor = 4) Or (dwMajor >= 10) Then bIsWin10OrGreater = True
If (dwMajor >= 10) And (dwBuild >= 17763) Then
bIsWinRS5OrGreater = True
If dwBuild >= 22000 Then bIsWin11OrGreater = True
End If
End If
End Sub
-
Mar 21st, 2024, 06:09 AM
#10
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by VanGoghGaming
And if "dwBuild >= 22000" then it's Windows 11.
What does your "ucs" abbreviation stand for?
I'm interested in build 20348 for Windows Server 2022 too, which has the earliest Schannel version with functional TLS 1.3 support :-))
Well, the prefix remains from when I copy/paste my company production code here. . .
 Originally Posted by fafalone
Yup this is my new standard now... I keep version info around and call ReadWindowsVersion on startup.
It's so cheap (a single API call) that "caching" results is not worth it anymore, IMO.
cheers,
</wqw>
-
Mar 22nd, 2024, 07:44 AM
#11
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by fafalone
Yup this is my new standard now... I keep version info around and call ReadWindowsVersion on startup.
Code:
Private bIsWinVistaOrGreater As Boolean
Private bIsWin7OrGreater As Boolean
Private bIsWin8OrGreater As Boolean
Private bIsWin10OrGreater As Boolean
Private bIsWinRS5OrGreater As Boolean
Private bIsWin11OrGreater As Boolean
Private Sub ReadWindowsVersion()
Dim dwMajor As Long, dwMinor As Long, dwBuild As Long
CopyMemory dwMajor, ByVal &H7FFE026C, 4
CopyMemory dwMinor, ByVal &H7FFE0270, 4
CopyMemory dwBuild, ByVal &H7FFE0260, 4
If dwMajor >= 6 Then
bIsWinVistaOrGreater = True
If dwMinor >= 1& Then bIsWin7OrGreater = True
If dwMinor >= 2& Then bIsWin8OrGreater = True
If (dwMinor = 4) Or (dwMajor >= 10) Then bIsWin10OrGreater = True
If (dwMajor >= 10) And (dwBuild >= 17763) Then
bIsWinRS5OrGreater = True
If dwBuild >= 22000 Then bIsWin11OrGreater = True
End If
End If
End Sub
That code is dangerous
Code:
If (dwMajor >= 10) And (dwBuild >= 17763) Then
Because what happens if dwMajor is 12 and dwBuild is below 17763 ?
-
Mar 22nd, 2024, 08:39 AM
#12
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Been there, done that, should've used If dwMajor > 10 Or (dwMajor = 10 And dwBuild >= 17763) Then
cheers,
</wqw>
-
Mar 22nd, 2024, 10:40 AM
#13
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
-
Mar 28th, 2024, 09:39 AM
#14
Hyperactive Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Interesting but what is the reason MS makes the API lie?
-
Mar 28th, 2024, 10:21 AM
#15
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
With the release of Windows 8.1, the behavior of the GetVersionEx API has changed in the value it will return for the operating system version. The value returned by the GetVersionEx function now depends on how the application is manifested.
Source: https://learn.microsoft.com/en-us/wi...-getversionexw
So far I've been relying on the WMI object to return the OS version but this KUSER_SHARED_DATA seems more slick!
-
Mar 28th, 2024, 11:20 AM
#16
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Who knows what the actual why is. You have to be doing something pretty unusual for version lie to be desirable; but then, why should *everyone* have to worry about it instead of just the people who would want a system API to lie to them?
WMI seems like overkill... it's often disabled for security these days and the COM objects are a very heavyweight solution. I had been reading the kernel32.dll version before this:
Code:
Private Sub ReadWindowsVersion()
'GetVersion[Ex] does not work with Win8 and above, so we'll go by kernel32 version
'GetFileVersionInfo does not work with some versions of Win10 and above.
Dim hMod As LongPtr
Dim hRes As LongPtr
hMod = LoadLibraryW(StrPtr("kernel32.dll"))
If hMod Then
hRes = FindResourceW(hMod, StrPtr("#1"), RT_VERSION)
If hRes Then
Dim hGbl As LongPtr
hGbl = LoadResource(hMod, hRes)
If (hGbl) Then
Dim lpRes As LongPtr
lpRes = LockResource(hGbl)
If lpRes Then
Dim tVerInfo As VS_VERSIONINFO_FIXED_PORTION
CopyMemory tVerInfo, ByVal lpRes, Len(tVerInfo)
If tVerInfo.Value.dwFileVersionMSh >= 6& Then
bIsWinVistaOrGreater = True
If tVerInfo.Value.dwFileVersionMSl >= 1& Then bIsWin7OrGreater = True
If tVerInfo.Value.dwFileVersionMSl >= 2& Then bIsWin8OrGreater = True: bIsWin7OrGreater = True
If (tVerInfo.Value.dwFileVersionMSl = 4&) Or (tVerInfo.Value.dwFileVersionMSh >= 10&) Then
bIsWin7OrGreater = True
bIsWin8OrGreater = True
bIsWin10OrGreater = True
End If
End If
End If
End If
End If
FreeLibrary hMod
End If
End Sub
Another solution was the PEB...
Public Declare PtrSafe Function RtlGetCurrentPeb Lib "ntdll" () As LongPtr
Then major (Long), minor (Long) and build (Integer) start at 0x0A4 (32bit)/0x118 (64bit)
Which comes from
Code:
[Description("This is the base compatibility PEB, usuable from Windows XP through 11+. For additional members, see additional PEBs, e.g. PEB_VISTA.")]
Public Type PEB
InheritedAddressSpace As Byte
ReadImageFileExecOptions As Byte
BeingDebugged As Byte
/* [ TypeHint(PEB_BITFIELD_OLD) ] */ BitField As Byte
Mutant As LongPtr
ImageBaseAddress As LongPtr
Ldr As LongPtr
ProcessParameters As LongPtr 'RTL_USER_PROCESS_PARAMETERS
SubSystemData As LongPtr
ProcessHeap As LongPtr
FastPebLock As LongPtr
AtlThunkSListPtr As LongPtr
SparePtr2 As LongPtr
EnvironmentUpdateCount As Long
KernelCallbackTable As LongPtr
SystemReserved(0) As Long
SpareUlong As Long
FreeList As LongPtr
TlsExpansionCounter As Long
TlsBitmap As LongPtr
TlsBitmapBits(1) As Long
ReadOnlySharedMemoryBase As LongPtr
ReadOnlySharedMemoryHeap As LongPtr
ReadOnlyStaticServerData As LongPtr
AnsiCodePageData As LongPtr
OemCodePageData As LongPtr
UnicodeCaseTableData As LongPtr
NumberOfProcessors As Long
NtGlobalFlag As NTGLB_Flags
#If (TWINBASIC = 0) And (Win64 = 0) Then
pad(3) As Byte
#End If
CriticalSectionTimeout As LARGE_INTEGER
HeapSegmentReserve As LongPtr
HeapSegmentCommit As LongPtr
HeapDeCommitTotalFreeThreshold As LongPtr
HeapDeCommitFreeBlockThreshold As LongPtr
NumberOfHeaps As Long
MaximumNumberOfHeaps As Long
ProcessHeaps As LongPtr
GdiSharedHandleTable As LongPtr
ProcessStarterHelper As LongPtr
GdiDCAttributeList As Long
LoaderLock As LongPtr
OSMajorVersion As Long
OSMinorVersion As Long
OSBuildNumber As Integer
OSCSDVersion As Integer
OSPlatformId As Long
ImageSubsystem As ImageSubsystemType
ImageSubsystemMajorVersion As Long
ImageSubsystemMinorVersion As Long
ImageProcessAffinityMask As LongPtr
#If Win64 Then
GdiHandleBuffer(59) As Long
#Else
GdiHandleBuffer(33) As Long
#End If
PostProcessInitRoutine As LongPtr
TlsExpansionBitmap As LongPtr
TlsExpansionBitmapBits(31) As Long
SessionId As Long
AppCompatFlagsHi As Long
AppCompatFlags As APP_COMPAT_FLAGS 'ULARGE_INTEGER
AppCompatFlagUser As LARGE_INTEGER
pShimData As LongPtr
AppCompatInfo As LongPtr
CSDVersion As UNICODE_STRING
ActivationContextData As LongPtr
ProcessAssemblyStorageMap As LongPtr
SystemDefaultActivationContextData As LongPtr
SystemAssemblyStorageMap As LongPtr
MinimumStackCommit As LongPtr
#If (TWINBASIC = 0) And (Win64 = 0) Then
pad2(3) As Byte
#End If
End Type
But KUSER_SHARED_DATA definitely wins now, because you only need the CopyMemory API; the above you'd need the API to get the PEB address *and* CopyMemory, at a minimum, plus different offsets for x86/x64..
-
Mar 28th, 2024, 02:44 PM
#17
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I've never heard of WMI being disabled. It's an integral part of Windows and many important services depend on it, such as the Windows Firewall. While this may be true in some heavily restricted corporate environments, it's almost never true for regular users.
Also it's pretty hard to beat this one-liner that always returns the correct version:
Code:
Debug.Print GetObject("winmgmts:").InstancesOf("Win32_OperatingSystem").ItemIndex(0).Version
Still, "KUSER_SHARED_DATA" wins hands down.
-
Mar 29th, 2024, 06:46 AM
#18
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Btw, on net stop winmgmt in admin prompt I get a "The Windows Management Instrumentation service could not be stopped" message so it's not that simple to disable WMI but it makes sense for systems in kiosk mode: POS terminals, ATM machines, etc.
cheers,
</wqw>
-
Mar 30th, 2024, 03:05 AM
#19
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
-
Mar 30th, 2024, 05:34 AM
#20
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by VanGoghGaming
I've never heard of WMI being disabled.
I have experienced WMI to be simply not present on a system after a supposedly successful Win7 to Win10 upgrade. None of the structures to contain data built, none of the named repositories existing. It does happen. I don't trust WMI. Laggy to return data, weird methods of storage, unreliable.
https://github.com/yereverluvinunclebert
Skillset: VMS,DOS,Windows Sysadmin from 1985, fault-tolerance, VaxCluster, Alpha,Sparc. DCL,QB,VBDOS- VB6,.NET, PHP,NODE.JS, Graphic Design, Project Manager, CMS, Quad Electronics. classic cars & m'bikes. Artist in water & oils. Historian.
By the power invested in me, all the threads I start are battle free zones - no arguing about the benefits of VB6 over .NET here please. Happiness must reign.
-
Mar 30th, 2024, 07:52 AM
#21
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I should have more appropriately said access to WMI features disabled, not the core low level services themselves.
-
Apr 2nd, 2024, 09:32 AM
#22
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by fafalone
Yup this is my new standard now... I keep version info around and call ReadWindowsVersion on startup.
Code:
Private bIsWinVistaOrGreater As Boolean
Private bIsWin7OrGreater As Boolean
Private bIsWin8OrGreater As Boolean
Private bIsWin10OrGreater As Boolean
Private bIsWinRS5OrGreater As Boolean
Private bIsWin11OrGreater As Boolean
Private Sub ReadWindowsVersion()
Dim dwMajor As Long, dwMinor As Long, dwBuild As Long
CopyMemory dwMajor, ByVal &H7FFE026C, 4
CopyMemory dwMinor, ByVal &H7FFE0270, 4
CopyMemory dwBuild, ByVal &H7FFE0260, 4
If dwMajor >= 6 Then
bIsWinVistaOrGreater = True
If dwMinor >= 1& Then bIsWin7OrGreater = True
If dwMinor >= 2& Then bIsWin8OrGreater = True
If (dwMinor = 4) Or (dwMajor >= 10) Then bIsWin10OrGreater = True
If (dwMajor >= 10) And (dwBuild >= 17763) Then
bIsWinRS5OrGreater = True
If dwBuild >= 22000 Then bIsWin11OrGreater = True
End If
End If
End Sub
The logic for both Win7OrGreater and Win8OrGreater fail on my Windows 10 system (dwMajor = 10, dwMinor = 0, dwBuild = 19045). I believe that the logic for those two lines should be:
Code:
If (dwMajor = 6&) AND (dwMinor >= 1&) Then bIsWin7OrGreater = True
If (dwMajor = 6&) AND (dwMinor >= 2&) Then bIsWin8OrGreater = True
Last edited by AAraya; Apr 2nd, 2024 at 09:49 AM.
-
Apr 2nd, 2024, 09:48 AM
#23
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Here's my updated version of your code fafalone (incorporating the suggestions & feedback that followed the original posting).
Code:
Public Function IsWin7OrGreater() As Boolean
Dim lngMajor As Long
Dim lngMinor As Long
Dim lngBuild As Long
GetWinVerInfo lngMajor, lngMinor, lngBuild
IsWin7OrGreater = (lngMajor > 6& Or (lngMajor = 6& And lngMinor >= 1&))
End Function
Public Function IsWin8OrGreater() As Boolean
Dim lngMajor As Long
Dim lngMinor As Long
Dim lngBuild As Long
GetWinVerInfo lngMajor, lngMinor, lngBuild
IsWin8OrGreater = (lngMajor > 6& Or (lngMajor = 6& And lngMinor >= 2&))
End Function
Public Function IsWin10OrGreater() As Boolean
Dim lngMajor As Long
Dim lngMinor As Long
Dim lngBuild As Long
GetWinVerInfo lngMajor, lngMinor, lngBuild
IsWin10OrGreater = (lngMajor >= 10&)
End Function
Public Function IsWin11OrGreater() As Boolean
Dim lngMajor As Long
Dim lngMinor As Long
Dim lngBuild As Long
GetWinVerInfo lngMajor, lngMinor, lngBuild
IsWin11OrGreater = (lngMajor > 10& Or (lngMajor = 10& And lngBuild >= 22000&))
End Function
Private Sub GetWinVerInfo(ByRef plngMajor As Long, ByRef plngMinor As Long, ByRef plngBuild As Long)
CopyMemory plngMajor, ByVal &H7FFE026C, 4
CopyMemory plngMinor, ByVal &H7FFE0270, 4
CopyMemory plngBuild, ByVal &H7FFE0260, 4
End Sub
Last edited by AAraya; Apr 2nd, 2024 at 05:53 PM.
-
Apr 2nd, 2024, 10:23 AM
#24
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Btw, IsWin11OrGreater = (lngMajor >= 10& And (lngMajor = 10& And lngBuild >= 22000&)) is also incorrect (needs an OR)
cheers,
</wqw>
-
Apr 2nd, 2024, 11:29 AM
#25
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by wqweto
Btw, IsWin11OrGreater = (lngMajor >= 10& And (lngMajor = 10& And lngBuild >= 22000&)) is also incorrect (needs an OR)
cheers,
</wqw>
It's always good to have someone else look over my logic. Appreciate you taking the time to do that!
I don't agree with your correction however. Using your logic of OR rather than AND, a Windows 10 OS would return an incorrect value of True from IsWin11OrGreater. Let's walk through the logic.
Using my Windows OS version for an example, we have the following version component values:
lngMajor = 10
lngMinor = 0
lngBuild = 19045
Plugging these values into your IsWin11OrGreater logic (using OR) I get this:
IsWin11OrGreater = (10>= 10& OR (10= 10& And 19045>= 22000&))
IsWin11OrGreater = (True OR (True And False))
IsWin11OrGreater = (True OR False)
IsWin11OrGreater = True <-- Incorrect result for a Win10 OS
Plugging these values into my original IsWin11OrGreater logic (using AND) I get this:
IsWin11OrGreater = (10>= 10& AND (10= 10& And 19045>= 22000&))
IsWin11OrGreater = (True AND (True And False))
IsWin11OrGreater = (True AND False)
IsWin11OrGreater = False <-- Correct result for a Win10 OS
Do you agree that it should be AND not OR for this case?
Further, I tested my logic using other Win 10 and Win 11 build numbers from this page and they all passed.
Last edited by AAraya; Apr 2nd, 2024 at 11:38 AM.
-
Apr 2nd, 2024, 11:58 AM
#26
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
IsWin11OrGreater = (lngMajor >= 10& And (lngMajor = 10& And lngBuild >= 22000&))
Should be as:
IsWin11OrGreater = (lngMajor > 10& Or (lngMajor = 10& And lngBuild >= 22000&))
And changed to Or and >= changed to >
-
Apr 2nd, 2024, 12:00 PM
#27
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Why add extra variables?
Code:
Private Sub GetWinVerInfo(ByRef plngMajor As Long, ByRef plngMinor As Long, ByRef plngBuild As Long)
CopyMemory plngMajor, ByVal &H7FFE026C, 4
CopyMemory plngMinor, ByVal &H7FFE0270, 4
CopyMemory plngBuild, ByVal &H7FFE0260, 4
End Sub
Unless you're exporting to non-VB callers where you might get a null pointer; but then
If VarPtr(plngMajor) Then CopyMemory plngMajor, ByVal &H7FFE026C, 4
etc
-
Apr 2nd, 2024, 12:38 PM
#28
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by fafalone
Why add extra variables?
Code:
Private Sub GetWinVerInfo(ByRef plngMajor As Long, ByRef plngMinor As Long, ByRef plngBuild As Long)
CopyMemory plngMajor, ByVal &H7FFE026C, 4
CopyMemory plngMinor, ByVal &H7FFE0270, 4
CopyMemory plngBuild, ByVal &H7FFE0260, 4
End Sub
Unless you're exporting to non-VB callers where you might get a null pointer; but then
If VarPtr(plngMajor) Then CopyMemory plngMajor, ByVal &H7FFE026C, 4
etc
Just a habit. But I did think of this of this as well. Thanks!
-
Apr 2nd, 2024, 12:40 PM
#29
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by Krool
IsWin11OrGreater = (lngMajor >= 10& And (lngMajor = 10& And lngBuild >= 22000&))
Should be as:
IsWin11OrGreater = (lngMajor > 10& Or (lngMajor = 10& And lngBuild >= 22000&))
And changed to Or and >= changed to >
Yes, agreed!
-
Dec 12th, 2024, 12:49 PM
#30
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
Great code! I've only seen this kind of code on the internet before, without manifests:
Code:
'==================================================================================
' RealWinVer.bas by Cody Gray, 2016
'
' (Freely available for use and modification, provided that credit is given to the
' original author. Including a comment in the code with my name and/or a link to
' this Stack Overflow answer is sufficient.)
'==================================================================================
Option Explicit
''''''''''''''''''''''''''''''''''''''''''''''''''
' Windows SDK Constants, Types, & Functions
''''''''''''''''''''''''''''''''''''''''''''''''''
Private Const cbCSDVersion As Long = 128 * 2
Private Const STATUS_SUCCESS As Long = 0
Private Const VER_PLATFORM_WIN32s As Long = 0
Private Const VER_PLATFORM_WIN32_WINDOWS As Long = 1
Private Const VER_PLATFORM_WIN32_NT As Long = 2
Private Const VER_NT_WORKSTATION As Byte = 1
Private Const VER_NT_DOMAIN_CONTROLLER As Byte = 2
Private Const VER_NT_SERVER As Byte = 3
Private Const VER_SUITE_PERSONAL As Integer = &H200
Private Type RTL_OSVERSIONINFOEXW
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * cbCSDVersion
wServicePackMajor As Integer
wServicePackMinor As Integer
wSuiteMask As Integer
wProductType As Byte
wReserved As Byte
End Type
Private Declare Function RtlGetVersion Lib "ntdll" _
(lpVersionInformation As RTL_OSVERSIONINFOEXW) As Long
''''''''''''''''''''''''''''''''''''''''''''''''''
' Internal Helper Functions
''''''''''''''''''''''''''''''''''''''''''''''''''
Private Function IsWinServerVersion(ByRef ver As RTL_OSVERSIONINFOEXW) As Boolean
' There are three documented values for "wProductType".
' Two of the values mean that the OS is a server versions,
' while the other value signifies a home/workstation version.
Debug.Assert ver.wProductType = VER_NT_WORKSTATION Or _
ver.wProductType = VER_NT_DOMAIN_CONTROLLER Or _
ver.wProductType = VER_NT_SERVER
IsWinServerVersion = (ver.wProductType <> VER_NT_WORKSTATION)
End Function
Private Function GetWinVerNumber(ByRef ver As RTL_OSVERSIONINFOEXW) As String
Debug.Assert ver.dwPlatformId = VER_PLATFORM_WIN32_NT
GetWinVerNumber = ver.dwMajorVersion & "." & _
ver.dwMinorVersion & "." & _
ver.dwBuildNumber
End Function
Private Function GetWinSPVerNumber(ByRef ver As RTL_OSVERSIONINFOEXW) As String
Debug.Assert ver.dwPlatformId = VER_PLATFORM_WIN32_NT
If (ver.wServicePackMajor > 0) Then
If (ver.wServicePackMinor > 0) Then
GetWinSPVerNumber = "SP" & CStr(ver.wServicePackMajor) & "." & CStr(ver.wServicePackMinor)
Exit Function
Else
GetWinSPVerNumber = "SP" & CStr(ver.wServicePackMajor)
Exit Function
End If
End If
End Function
Private Function GetWinVerName(ByRef ver As RTL_OSVERSIONINFOEXW) As String
Debug.Assert ver.dwPlatformId = VER_PLATFORM_WIN32_NT
Select Case ver.dwMajorVersion
Case 3
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows NT 3.5 Server"
Exit Function
Else
GetWinVerName = "Windows NT 3.5 Workstation"
Exit Function
End If
Case 4
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows NT 4.0 Server"
Exit Function
Else
GetWinVerName = "Windows NT 4.0 Workstation"
Exit Function
End If
Case 5
Select Case ver.dwMinorVersion
Case 0
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows 2000 Server"
Exit Function
Else
GetWinVerName = "Windows 2000 Workstation"
Exit Function
End If
Case 1
If (ver.wSuiteMask And VER_SUITE_PERSONAL) Then
GetWinVerName = "Windows XP Home Edition"
Exit Function
Else
GetWinVerName = "Windows XP Professional"
Exit Function
End If
Case 2
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows Server 2003"
Exit Function
Else
GetWinVerName = "Windows XP 64-bit Edition"
Exit Function
End If
Case Else
Debug.Assert False
End Select
Case 6
Select Case ver.dwMinorVersion
Case 0
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows Server 2008"
Exit Function
Else
GetWinVerName = "Windows Vista"
Exit Function
End If
Case 1
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows Server 2008 R2"
Exit Function
Else
GetWinVerName = "Windows 7"
Exit Function
End If
Case 2
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows Server 2012"
Exit Function
Else
GetWinVerName = "Windows 8"
Exit Function
End If
Case 3
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows Server 2012 R2"
Exit Function
Else
GetWinVerName = "Windows 8.1"
Exit Function
End If
Case Else
Debug.Assert False
End Select
Case 10
If IsWinServerVersion(ver) Then
GetWinVerName = "Windows Server 2016"
Exit Function
Else
GetWinVerName = "Windows 10"
Exit Function
End If
Case Else
Debug.Assert False
End Select
GetWinVerName = "Unrecognized Version"
End Function
''''''''''''''''''''''''''''''''''''''''''''''''''
' Public Functions
''''''''''''''''''''''''''''''''''''''''''''''''''
' Returns a string that contains the name of the underlying version of Windows,
' the major version of the most recently installed service pack, and the actual
' version number (in "Major.Minor.Build" format).
'
' For example: "Windows Server 2003 SP2 (v5.2.3790)" or
' "Windows 10 (v10.0.14342)"
'
' This function returns the *real* Windows version, and works correctly on all
' operating systems, including Windows 10, regardless of whether or not the
' application includes a manifest. It calls the native NT version-info function
' directly in order to bypass compatibility shims that would otherwise lie to
' you about the real version number.
Public Function GetActualWindowsVersion() As String
Dim ver As RTL_OSVERSIONINFOEXW
ver.dwOSVersionInfoSize = Len(ver)
If (RtlGetVersion(ver) <> STATUS_SUCCESS) Then
GetActualWindowsVersion = "Failed to retrieve Windows version"
End If
' The following version-parsing logic assumes that the operating system
' is some version of Windows NT. This assumption will be true if you
' are running any version of Windows released in the past 15 years,
' including several that were released before that.
Debug.Assert ver.dwPlatformId = VER_PLATFORM_WIN32_NT
GetActualWindowsVersion = GetWinVerName(ver) & " " & GetWinSPVerNumber(ver) & _
" (v" & GetWinVerNumber(ver) & ")"
End Function
-
Dec 12th, 2024, 02:19 PM
#31
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
RtlGetVersion has the no manifest lie. To be clear, my code does not require a manifest to return the correct version.
But look at all those lines of code! Why'd you write so much extra!
-
Dec 12th, 2024, 02:26 PM
#32
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
 Originally Posted by fafalone
RtlGetVersion has the no manifest lie. To be clear, my code does not require a manifest to return the correct version.
But look at all those lines of code! Why'd you write so much extra! 
I didn't write this code. I found it on StackOverflow. But your code, fafalone, is certainly better. We just need to come up with some kind of beautiful module. I want a beautiful wrapper.
-
Dec 12th, 2024, 02:30 PM
#33
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
By the way, they have the same thing written in the comments in the code: "This function returns the *real* Windows version, and works correctly on all operating systems, including Windows 10, regardless of whether or not the application includes a manifest."
I don't think they're going to lie...
-
Dec 14th, 2024, 05:24 PM
#34
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I came up with the idea that you can now get the real version of Windows through the GetMem4 function, it will work faster in large processing cycles.
I wrote the code to check if Windows is a version less than 10.
Code:
Private Declare Function GetMem4 Lib "msvbvm60" (src As Any, dst As Any) As Long
Private Sub Form_Load()
Dim MajorWindowsVersion As Long
GetMem4 ByVal &H7FFE026C, MajorWindowsVersion
If MajorWindowsVersion < 10 Then
' old versions windows
Else
' Windows 10 and latter
End If
End Sub
-
Dec 14th, 2024, 10:56 PM
#35
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I can't imagine needing to query the windows version so frequently that a difference between CopyMemory and GetMem4, if it even exists, is significant. Even in that case you'd then want to cache the result on startup.
-
Dec 21st, 2024, 01:57 AM
#36
Addicted Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
hi fafalone
Great code!
is there an instance (besides POS systems, etc.) where this call could fail? It returns a pretty string:
Code:
Public Function GetWinVersion() As String
Dim objWMIService As Object
Dim colOperatingSystems As Object
Dim objOperatingSystem As Object
'// Connect to WMI service
Set objWMIService = GetObject("winmgmts:\\.\root\cimv2")
'// Retrieve the OS version information
Set colOperatingSystems = objWMIService.ExecQuery("Select * from Win32_OperatingSystem")
For Each objOperatingSystem In colOperatingSystems
GetWinVersion = objOperatingSystem.Caption & " - Version: " & objOperatingSystem.Version
Exit For
Next objOperatingSystem
End Function
-
Dec 21st, 2024, 03:37 AM
#37
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
It's not just POS systems where the user might not be a member of the admin or performance users group and thus potentially not have WMI access, but it's usually fine if you really prefer WMI. You're not likely to find it locked down outside corporate environments where people have logons with highly restricted permissions.
-
Dec 21st, 2024, 05:15 AM
#38
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
@taishan: Where does WMI gets real OS version?
It’s probably PEB or KUSER_SHARED_DATA, not the other way around. PEB/kernel does not use WMI for anything. WMI is a high-level abstraction used by admins. It’s like using VBScript objects from VB6 - possible but not always optimal.
-
Dec 21st, 2024, 05:30 AM
#39
Addicted Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
@fafalone & @wqweto: Thanks for the insights. I will use WMI for the 'pretty' string, and KUSER_SHARED_DATA to verify.
Running both at startup for a log file is virtually nothing on startup time, and I can be assured that I know the exact version.
Cheers
-
Feb 10th, 2025, 02:00 PM
#40
Fanatic Member
Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA
I checked this code on Windows Me today. It doesn't work, it gives out some nonsense, the numbers are too high. I don't know what to do or how to identify WinME now.
Moreover, the logic for determining, for example, Windows 7 or more is violated.
Or, for example, this code of mine will not work correctly, which determines that it is Windows 10 or more. Windows Me will count as Windows 10 mistakenly...
Code:
Private Declare Function GetMem4 Lib "msvbvm60" (src As Any, dst As Any) As Long
Private Sub Form_Load()
Dim MajorWindowsVersion As Long
GetMem4 ByVal &H7FFE026C, MajorWindowsVersion
If MajorWindowsVersion < 10 Then
' old versions windows
Else
' Windows 10 and latter
End If
End Sub
Posting Permissions
- You may not post new threads
- You may not post replies
- You may not post attachments
- You may not edit your posts
-
Forum Rules
|
Click Here to Expand Forum to Full Width
|