Skip to main content

[archive] Calling kernel32.dll

  • April 13, 2004
  • 9 replies
  • 0 views

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub

9 replies

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
I am happy to hear that you will be attending our Advanced Windows API training this summer. I sure hope you will find it informative.

Now, having said that, your example refer to usign GetVersionEx, my first thought is, do you need all this info? If not, the oldest version is a bit easier to handle, here are some code that illustrates the use of GetVersion.


       IDENTIFICATION  DIVISION.
       PROGRAM-ID.     GetWinVer.
       DATE-WRITTEN.   2003/01/24
       REMARKS.
      *This program illustrates how to get the current Windows version.

       WORKING-STORAGE SECTION.
       01  myDWord                  PIC X(4) COMP-N.
       01  myRedefines redefines myDWord.
           03 Byte-1                PIC X COMP-N.
           03 Byte-2                PIC X COMP-N.
           03 Byte-3                PIC X COMP-N.
           03 Byte-4                PIC X COMP-N.
       01  NumA                     PIC 9(3).
       01  NumB                     PIC 9(3).
       01  myString                 PIC X(256).

       PROCEDURE   DIVISION.
       MAIN-LOGIC.
      *We're calling the API, make sure we use the correct calling
      *convention
           SET     ENVIRONMENT "DLL-CONVENTION" TO "1".
      *The function we are about to use, are located in kernel32.dll
           CALL    "KERNEL32.DLL".
           CALL    "GetVersion"     GIVING myDWord.
           CANCEL  "KERNEL32.DLL".

       IF      myDWord         
                   MOVE             Byte-1 TO NumA
                   MOVE             Byte-2 TO NumB
               STRING           "NT Class OS" x"0A"
                                    "Version:" x"09" NumA "." NumB x"0A"
                                    DELIMITED BY SIZE INTO myString
           ELSE
                   MOVE             Byte-1 TO NumA
                   MOVE             Byte-2 TO NumB
               STRING           "Win 9x/Me Class OS" x"0A"
                                    "Version:" x"09" NumA "." NumB x"0A"
                                    DELIMITED BY SIZE INTO myString
                   END-IF.

           DISPLAY MESSAGE          BOX myString.
           GOBACK.



[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
I am happy to hear that you will be attending our Advanced Windows API training this summer. I sure hope you will find it informative.

Now, having said that, your example refer to usign GetVersionEx, my first thought is, do you need all this info? If not, the oldest version is a bit easier to handle, here are some code that illustrates the use of GetVersion.


       IDENTIFICATION  DIVISION.
       PROGRAM-ID.     GetWinVer.
       DATE-WRITTEN.   2003/01/24
       REMARKS.
      *This program illustrates how to get the current Windows version.

       WORKING-STORAGE SECTION.
       01  myDWord                  PIC X(4) COMP-N.
       01  myRedefines redefines myDWord.
           03 Byte-1                PIC X COMP-N.
           03 Byte-2                PIC X COMP-N.
           03 Byte-3                PIC X COMP-N.
           03 Byte-4                PIC X COMP-N.
       01  NumA                     PIC 9(3).
       01  NumB                     PIC 9(3).
       01  myString                 PIC X(256).

       PROCEDURE   DIVISION.
       MAIN-LOGIC.
      *We're calling the API, make sure we use the correct calling
      *convention
           SET     ENVIRONMENT "DLL-CONVENTION" TO "1".
      *The function we are about to use, are located in kernel32.dll
           CALL    "KERNEL32.DLL".
           CALL    "GetVersion"     GIVING myDWord.
           CANCEL  "KERNEL32.DLL".

       IF      myDWord         
                   MOVE             Byte-1 TO NumA
                   MOVE             Byte-2 TO NumB
               STRING           "NT Class OS" x"0A"
                                    "Version:" x"09" NumA "." NumB x"0A"
                                    DELIMITED BY SIZE INTO myString
           ELSE
                   MOVE             Byte-1 TO NumA
                   MOVE             Byte-2 TO NumB
               STRING           "Win 9x/Me Class OS" x"0A"
                                    "Version:" x"09" NumA "." NumB x"0A"
                                    DELIMITED BY SIZE INTO myString
                   END-IF.

           DISPLAY MESSAGE          BOX myString.
           GOBACK.



[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
I am happy to hear that you will be attending our Advanced Windows API training this summer. I sure hope you will find it informative.

Now, having said that, your example refer to usign GetVersionEx, my first thought is, do you need all this info? If not, the oldest version is a bit easier to handle, here are some code that illustrates the use of GetVersion.


       IDENTIFICATION  DIVISION.
       PROGRAM-ID.     GetWinVer.
       DATE-WRITTEN.   2003/01/24
       REMARKS.
      *This program illustrates how to get the current Windows version.

       WORKING-STORAGE SECTION.
       01  myDWord                  PIC X(4) COMP-N.
       01  myRedefines redefines myDWord.
           03 Byte-1                PIC X COMP-N.
           03 Byte-2                PIC X COMP-N.
           03 Byte-3                PIC X COMP-N.
           03 Byte-4                PIC X COMP-N.
       01  NumA                     PIC 9(3).
       01  NumB                     PIC 9(3).
       01  myString                 PIC X(256).

       PROCEDURE   DIVISION.
       MAIN-LOGIC.
      *We're calling the API, make sure we use the correct calling
      *convention
           SET     ENVIRONMENT "DLL-CONVENTION" TO "1".
      *The function we are about to use, are located in kernel32.dll
           CALL    "KERNEL32.DLL".
           CALL    "GetVersion"     GIVING myDWord.
           CANCEL  "KERNEL32.DLL".

       IF      myDWord         
                   MOVE             Byte-1 TO NumA
                   MOVE             Byte-2 TO NumB
               STRING           "NT Class OS" x"0A"
                                    "Version:" x"09" NumA "." NumB x"0A"
                                    DELIMITED BY SIZE INTO myString
           ELSE
                   MOVE             Byte-1 TO NumA
                   MOVE             Byte-2 TO NumB
               STRING           "Win 9x/Me Class OS" x"0A"
                                    "Version:" x"09" NumA "." NumB x"0A"
                                    DELIMITED BY SIZE INTO myString
                   END-IF.

           DISPLAY MESSAGE          BOX myString.
           GOBACK.



[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
Gisle,

Thanks very much for your reply. This worked perfectly - it's all I needed. As it turns out, I really just needed to know whether the user was using the NT class or the 9x/Me class, so my code ended up being incredibly simple.

Looking forward to your class in June!

Rob

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
Hello,

I am very new to ACUCOBOL and have no experience calling DLL's either. Please excuse my ignorance. I am also trying to call a DLL from a COBOL in a thin client environment, but the application host is UNIX. We are running ACUCOBOL ver 6.2. I cannot get this to work. I copied the GETWINVER program below and it runs fine in the AcuBench tool. When I move it onto the unix box and try to run it, it tells me the KERNEL32.dll is missing or inaccessible. Is this even possible to do when the application host is Unix? Is it possible to do in a different version?

What I really want to do is call a VB.net application on a web server from a COBOL app in a thin client enviroment where the application host Unix. I want to be able to pass information between the 2 applications. Is this possible in version 6.2? If possible in a different version? If it is possible, does anyone have any examples? Thanks is advance.

Denise

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
On Windows this works as the runtime and dlls exist on the same system, when moving to Unix you will need to use the @DISPLAY syntax so that the program running on Unix knows to invoke or execute a resource (or dll) on the client

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
On Windows this works as the runtime and dlls exist on the same system, when moving to Unix you will need to use the @DISPLAY syntax so that the program running on Unix knows to invoke or execute a resource (or dll) on the client

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
On Windows this works as the runtime and dlls exist on the same system, when moving to Unix you will need to use the @DISPLAY syntax so that the program running on Unix knows to invoke or execute a resource (or dll) on the client

[Migrated content. Thread originally posted on 09 April 2004]

I am trying to call kernell32.dll to determine the version of Windows that the client (in a thin client environment) is running. If it weren't thin client, I would use WIN$VERSION, but this won't work in thin client for the client - only the server.

I've had little experience calling DLLs and I cannot figure out how to make this one work. I've attached a simple VB example that does what I need, but I don't know how to "translate" this to COBOL syntax. Can anyone point me in the right direction? Or does anyone have a sample program already?

I'll be attending Gisle's class this Summer in San Diego and I'm sure after that class, I'll know how to do this, but I cannot wait until then!!

Thanks,
Rob


Public Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Public Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

' dwPlatforID Constants
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
'-- End --'

Add this code to a form:
Private Sub Form_Load()

Dim tOSVer As OSVERSIONINFO

' First set length of OSVERSIONINFO
' structure size
tOSVer.dwOSVersionInfoSize = Len(tOSVer)
' Get version information
GetVersionEx tOSVer
' Determine OS type
With tOSVer

Select Case .dwPlatformId
Case VER_PLATFORM_WIN32_NT
' This is an NT version (NT/2000)
' If dwMajorVersion >= 5 then
' the OS is Win2000
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows 2000"
Else
Label1.Caption = "Windows NT"
End If
Case Else
' This is Windows 95/98/ME
If .dwMajorVersion >= 5 Then
Label1.Caption = "Windows ME"
ElseIf .dwMajorVersion = 4 And .dwMinorVersion > 0 Then
Label1.Caption = "Windows 98"
Else
Label1.Caption = "Windows 95"
End If
End Select
' Check for service pack
Label1.Caption = Label1.Caption & " " & Left(.szCSDVersion, _
InStr(1, .szCSDVersion, Chr$(0)))
' Get OS version
Label2.Caption = "Version: " & .dwMajorVersion & "." & _
.dwMinorVersion & "." & .dwBuildNumber

End With

End Sub
Private Sub Command1_Click()
Unload Me
End Sub
Just keep in mind that ActiveX, COM and .net automatically are executed on the client, so for those the @DISPLAY prefix is not required.