Page 2 of 2 FirstFirst 12
Results 41 to 76 of 76

Thread: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DATA

  1. #41
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by AAraya View Post
    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
    And for example, all this code will go to hell when defining Windows Millennium.

  2. #42
    PowerPoster Arnoutdv's Avatar
    Join Date
    Oct 2013
    Posts
    6,430

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    I assume it only works for NT kernels.

  3. #43
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    No, it should work in Windows 98 too. But I haven't checked in Win98 yet.
    According to the results of my check in Windows Me, I will now have to rewrite the function to actually detect Windows 10. So that Windows Me doesn't mistakenly count as Windows 10. It's really important.

    Code:
    Private Declare Function GetMem4 Lib "msvbvm60" (src As Any, dst As Any) As Long
    
    Private Sub Form_Load()
        Dim MajorWindowsVersion As Long
        Dim MinorWindowsVersion As Long
        
        GetMem4 ByVal &H7FFE026C, MajorWindowsVersion
        GetMem4 ByVal &H7FFE0270, MinorWindowsVersion
        
        Debug.Print MajorWindowsVersion, MinorWindowsVersion
        
        If MajorWindowsVersion >= 10 And MajorWindowsVersion < 8000 Then
            Debug.Print "Windows 10 and latter"
        Else
            Debug.Print "old versions windows"
        End If
    End Sub
    I had to add a condition that if MajorWindowsVersion is less than 8000, although to be honest in Windows Me this value is generally sky-high, it gives out more than 800 million.

  4. #44
    PowerPoster Arnoutdv's Avatar
    Join Date
    Oct 2013
    Posts
    6,430

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    You are still developing for Win95/98/Me ?
    What type of clients/users do you have?

  5. #45
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by wqweto View Post
    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>
    This code will also crash to hell in Windows Me. This will cause runtime error number 6 (stack overflow). You should change this code to be compatible with older versions of WIndows. This is especially true for Windows Me.

  6. #46
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by Arnoutdv View Post
    You are still developing for Win95/98/Me ?
    What type of clients/users do you have?
    No, I just decided today to check for interest whether my programs will work in the old Windows Me. Just out of curiosity. So I decided to fix some codes to be compatible with the old version of Windows, it turns out it's not that difficult and a lot of things work in older Windows.

  7. #47
    Fanatic Member
    Join Date
    Aug 2011
    Location
    Palm Coast, FL
    Posts
    663

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    For practical purposes, not sure you need to worry too much about ME

    Worldwide market share percentages:

    Windows 10 60.37%
    Windows 11 36.6%
    Windows 7 2.25%
    Windows 8 0.16%
    Windows ME Negligible (not reported in modern statistics)

  8. #48
    PowerPoster
    Join Date
    Jan 2020
    Posts
    5,042

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    The WMI, like ie11, runs slowly. He actually has a way to increase the speed of operation by 10 times and 100 times. But Microsoft's approach is the same, as long as a feature is completed, it will not be improved for 10 or 30 years. The only thing he will do is choose when to abandon him.

    Instead, create a way to replace it that is less useful.

  9. #49
    PowerPoster
    Join Date
    Jan 2020
    Posts
    5,042

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    everythibg.exeThis software can manage millions of files on your computer and search them successfully in one second. Even if you search the contents of the file, you can almost find the whole hard disk in 10 seconds to a minute.
    However, the search function that comes with windows may take 5 to 10 minutes to find the file name.

    Many of Microsoft's design methods are very low. We can only find ways to do all kinds of judgments and tests by ourselves.

  10. #50

    Thread Starter
    PowerPoster
    Join Date
    Jul 2010
    Location
    NYC
    Posts
    6,832

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    I believe Arnoutdv is correct, this is only for NT kernels. If you look at the full UDT the fact the version fields are named NtMajorVersion and NtMinorVersion should be a clue.

    Just the version direct copying works on NT4-Win11, but not 9x or ME. As noted, "The [full] type can be truncated after ProcessorFeatures for Windows 2000 and NT4 compatibility-- the top snippet without declares works on NT4-11.

    Have you found any evidence otherwise? Not crashing isnt evidence; you could just get random junk.

    If you want to support 9x/me, you'll need to use a different method.

  11. #51
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Then how do you explain to me this code from wqweto that includes Windows 98 enumeration? Is this code a lie?

    Code:
    Private Enum UcsOsVersionEnum
        ucsOsvNt4 = 400
        ucsOsvWin98 = 410
        ucsOsvWin2000 = 500
        ucsOsvXp = 501
        ucsOsvVista = 600
        ucsOsvWin7 = 601
        ucsOsvWin8 = 602
        [ucsOsvWin8.1] = 603
        ucsOsvWin10 = 1000
    End Enum

  12. #52

    Thread Starter
    PowerPoster
    Join Date
    Jul 2010
    Location
    NYC
    Posts
    6,832

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    wqweto probably just used an existing enum for major/minor to OS originally written for other functions, or like you assumed it would work, I seriously doubt he tested it on Win98.

  13. #53

  14. #54

    Thread Starter
    PowerPoster
    Join Date
    Jul 2010
    Location
    NYC
    Posts
    6,832

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    If it's not working on ME it's almost certainly not working on 98, especially with the indications it's for the NT kernel only, since it's a type tightly bound to kernel mode information; KMODE_SHARED is referring to that; shared data between kernel mode and user mode.

    "Lying" isn't really the best word either.

  15. #55
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,784

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by HackerVlad View Post
    Then how do you explain to me this code from wqweto that includes Windows 98 enumeration? Is this code a lie?
    A lie? Wouldn't say so, while you don't understanding the full picture -- definitely!

    Imagine a codebase where there are both RealOsVersion and OsVersion properties both returning the same UcsOsVersionEnum enum.

    Btw, you don't need RealOsVersion on anything before Win8. . .

    cheers,
    </wqw>

  16. #56

  17. #57
    PowerPoster Arnoutdv's Avatar
    Join Date
    Oct 2013
    Posts
    6,430

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    It's just a generic enumeration, used for multiple purposes.

  18. #58
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,784

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by HackerVlad View Post
    I don't understand why it was necessary to write "ucsOsvWin98 = 410" and thus mislead people.
    Apparently there is only one person this is misleading to. Everyone else seems to orient themselves just fine.

    Why you so confused?

    cheers,
    </wqw>

  19. #59

  20. #60
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,784

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by HackerVlad View Post
    After seeing this, people will expect that this code will work in Windows 98 and will be extremely disappointed when they realize that this is not the case.
    Btw, disappointment is the "correct" feeling to have when dealing with Win9x :-))

    An appropiate usage pattern here is first to check OsVersion and only if OsVersion >= Win8 then to check RealOsVersion.

    Anyway, once again -- "No good deed remains unpunished" proverb has been proven. I'm not the original author of the snippet but I was just sharing my usage on an "it works for me" basis.

    I don't care about 9x and if I did I would wrap RealOsVersion with necessary checks to return OsVersion instead. Do you want me to publicly appologize now for including Win98 in the enumeration or something?

    I cannot remove this entry from the larger codebase it was taken from as the code is littered with hundereds of (now obsolete) Win9x checks and there is no one to refactor this just to not confuse anyone when pasted on VBForums.

    Anyway, you and anyone dealing with 9x will have to "bite" their disappointment and get used to copy/pasting not working snippets from here. . . ¯\_(?)_/¯

    cheers,
    </wqw>

  21. #61

    Thread Starter
    PowerPoster
    Join Date
    Jul 2010
    Location
    NYC
    Posts
    6,832

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by HackerVlad View Post
    After seeing this, people will expect that this code will work in Windows 98 and will be extremely disappointed when they realize that this is not the case.
    I find it hard to believe anyone interested in retro computing is unaware the ME/9x kernel, APIs and architecture is substantially different from the NT side and therefore confused by why a lot of code from the past 20 years has far less compatibility with non-NT versions, or that legacy artifacts exist but don't continue to be meaningful/active/working.

  22. #62
    PowerPoster yereverluvinuncleber's Avatar
    Join Date
    Feb 2014
    Location
    Norfolk UK (inbred)
    Posts
    2,932

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    I have hundreds of thousands of potential Win98 users but in reality, none. So it will never be a problem.
    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.

  23. #63
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Ha ha ha , they amused me with their humor, of course, but if anyone is interested, I launched Windows 98 and checked what values it gives.

    Major: 2143127994
    Minor: 2143128004

    The numbers are clearly overstated, as you can see, and now I fully realize that this code is only for NT platforms.

  24. #64
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    To check if Windows is a system bigger than Windows XP, I had to use the old GetVersionExA function.

    Code:
    Private Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As Any) As Long
    
    ...
    
    Dim inf(36) As Long ' instead of a structure
    Dim IsXPAndLater As Boolean
    
    inf(0) = 148: GetVersionEx inf(0): IsXPAndLater = inf(4) = 2 And inf(1) >= 5 And inf(2) >= 1 ' Get the Windows version
    
    If IsXPAndLater = True Then
        ' This is Windows XP or later
    Else
        ' It's less than WinXP, maybe Windows 98!
    End If

  25. #65
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    I wanted to use the ready-made IsWindowsXPOrGreater function first, but the description says that it only works since Windows 2000 (it's strange that it doesn't work with XP) and therefore Windows 98 simply doesn't know such a function...

  26. #66

    Thread Starter
    PowerPoster
    Join Date
    Jul 2010
    Location
    NYC
    Posts
    6,832

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Unless there's a good reason or requirement, I don't even try support Windows before Vista/7 anymore. So much great stuff was added in that like using the much easier and better IFileDialog instead of GetOpenFileName. I do however try to avoid requiring Windows 8 or higher.

  27. #67
    PowerPoster yereverluvinuncleber's Avatar
    Join Date
    Feb 2014
    Location
    Norfolk UK (inbred)
    Posts
    2,932

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    I am testing on ReactOS (NT5 moving slowly to NT6) so I do have a reason to create apps that are XP tolerant but no Windows oses prior to XP. I can't find a reason to do so.
    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.

  28. #68

  29. #69
    PowerPoster yereverluvinuncleber's Avatar
    Join Date
    Feb 2014
    Location
    Norfolk UK (inbred)
    Posts
    2,932

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    ReactOS is in a state of flux at the moment.

    Development is moving over to 64bit and the beginnings of NT6 functionality. Moving away from the the NT5 32bit target.

    Lots of progress being made but it does not make for a stable environment, so set your expectations low. The only builds to try are the dailies, there hasn't been s table release for a long time (two years) as they only release once they get down to a certain number of bugs and with all the change, they have introduced a lot of new bugs.

    There is a 32bit release that is more stable whilst the 64bit version is only for seeing that they are making progress, not usable at all at the moment. Lots happening though and a very dynamic team.

    You can test a ReactOS daily build and VB5 will install, VB6 with some effort depending upon the release, you have some stuff to copy from Windows to make it happen, runtime components.

    IF you do try it, do it in a VM only, NOT real hardware, use virtualbox and not the most recent versions of Vbox as they introduce some bugs of their own.
    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.

  30. #70

    Thread Starter
    PowerPoster
    Join Date
    Jul 2010
    Location
    NYC
    Posts
    6,832

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    ReactOS still pretending they never used the leaked XP source?

    It's a damn tragedy none of the Windows source leaks even included msvbvm60.dll.

    Can't believe no version of VB's source has leaked either.

  31. #71
    PowerPoster yereverluvinuncleber's Avatar
    Join Date
    Feb 2014
    Location
    Norfolk UK (inbred)
    Posts
    2,932

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    They don't pretend. They don't use it. You can't even mention MS source code on the chat, instant ban. Their code has been rewritten and improved dozens of times. It was required as the early code was often rather bad. The 64bit code is all new and being written by very few.

    What do they say about **** though? ... it sticks.

    The story goes that an elderly English couple were taking an evening stroll along some Spanish beach when they came across a tanned and weather-beaten old man painting his boat. They got talking and after a while introduced themselves. But when they asked what the old man’s name was the conversation turned a little cold.

    “You see the fish on the market stalls in town every day?” he said. “I catch those fish. I bring them to market. I feed the people. Do they call me Alberto the Fisherman? No!”
    “You see the boats on the shoreline all clean and brightly painted? I paint those boats. Do they call me Alberto the Boatman? No!”
    "You see the maisonettes on the hillside with their red roofs? I make those tiles and lay them on the roofs. Do they call me Alberto the Tiler? No!”.
    "You see that bridge to the village?, I built that bridge with my own sweat and my own bare hands. Do they now call me Alberto the Bridge-builder? No, they do not! - but you know, you shag one lousy sheep.”
    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.

  32. #72
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    So you haven't answered my question. what version of Windows is defined in ReactOS? For example, using the GetVersionEx function
    Or using the code that is discussed in this article. What will be the version? 5.1? Like in XP?

  33. #73
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by fafalone View Post
    ReactOS still pretending they never used the leaked XP source?

    It's a damn tragedy none of the Windows source leaks even included msvbvm60.dll.

    Can't believe no version of VB's source has leaked either.
    The ReactOS code was written before the XP source code was leaked, but perhaps later, after the leak, the ReactOS developers began to borrow something for themselves, but no one will ever know about it. I sometimes borrow code myself, it can be very useful.
    There are some things I couldn't do at all without looking at the ReactOS source codes, which sometimes helps a lot to figure out some of the subtleties...

  34. #74
    PowerPoster yereverluvinuncleber's Avatar
    Join Date
    Feb 2014
    Location
    Norfolk UK (inbred)
    Posts
    2,932

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by HackerVlad View Post
    So you haven't answered my question. what version of Windows is defined in ReactOS? For example, using the GetVersionEx function
    Or using the code that is discussed in this article. What will be the version? 5.1? Like in XP?
    ReactOS version, though I believe it can be spoofed for apps that specifically request it.
    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.

  35. #75
    PowerPoster yereverluvinuncleber's Avatar
    Join Date
    Feb 2014
    Location
    Norfolk UK (inbred)
    Posts
    2,932

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by HackerVlad View Post
    The ReactOS code was written before the XP source code was leaked, but perhaps later, after the leak, the ReactOS developers began to borrow something for themselves, but no one will ever know about it. I sometimes borrow code myself, it can be very useful.
    There are some things I couldn't do at all without looking at the ReactOS source codes, which sometimes helps a lot to figure out some of the subtleties...
    The specific code in question was re-written a few times. A lot of the other code is being continuously re-written. It is just a work massively in progress.

    ReactOS code is very useful to understand what Windows might be doing, always 'might' as very little of the important stuff has been documented by MS. A lot of ReactOS code is being looked at by AI and fed back as helper code. Some of that leaked source from MS is sure to bubble its way to the surface in the same manner. It will soon be hard to distinguish any code's provenance.
    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.

  36. #76
    Fanatic Member HackerVlad's Avatar
    Join Date
    Nov 2023
    Posts
    674

    Re: [VB6/VBA/twinBASIC] The quickest way to the real Windows version: KUSER_SHARED_DA

    Quote Originally Posted by yereverluvinuncleber View Post
    ReactOS version, though I believe it can be spoofed for apps that specifically request it.
    And again you didn't answer. I'm asking what the version number will be? Major number version? Minor number version?
    The functions determine the Windows version. And these functions already work in ReactOS. But what values will be given by the functions that determine the Windows version in the ReactOS system?

Page 2 of 2 FirstFirst 12

Posting Permissions

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



Click Here to Expand Forum to Full Width