Silverfrost Forums

Welcome to our forums

How to find Operating System the program is running on ?

13 Jun 2012 1:21 #10331

Is it Win7, Vista or XP?

13 Jun 2012 4:57 #10332

You can do something like this:

  SUBROUTINE WINVERS (SYSTEM)

! USE MSWIN IMPLICIT NONE ! INTEGER4 OS CHARACTER SYSTEM12,MAJORVERSION6, & MINORVERSION6 !----------------------------------------------------------------------- OS=GetVersion()
! WRITE(MAJORVERSION,'(I6)')LOBYTE(LOWORD(OS)) MAJORVERSION=ADJUSTL(MAJORVERSION) WRITE(MINORVERSION,'(I6)')HIBYTE(LOWORD(OS)) MINORVERSION=ADJUSTL(MINORVERSION) ! IF (AND(HIWORD(OS),Z'8000').EQ.Z'8000') THEN SYSTEM='Windows 95' ELSE IF(LOBYTE(LOWORD(OS)).GE.6)THEN !VISTA SYSTEM='Vista' ELSE SYSTEM='Windows NT' ENDIF ENDIF ! RETURN END

Regards,

Detlef

13 Jun 2012 7:19 #10333

Thanks Detlef. That was cool brain draining exercise i suppose! By the way for 64bit Win7 i get OS=170393861. Code says it's Vista because Win7 was not programmed in. So let's add Win7 into the source but before that let's double check what specific integer number (OS) you get for Vista? is it the same or different?

13 Jun 2012 7:50 #10335

Detlef,

FTN95 has the routine:

CALL GET_OS_VER@ (ID_Platform, Major, Minor)

which does a bit of the working out for you. It can certainly resolve Win 7 as 7. Looks a bit simpler than your solution.

Dan,

When you have 6 or 7 as the Major, then the mechanism for handling large fonts is different. Also the system font changes. For a Vista and 7 look and feel you need to use Segoe UI. For XP it was Trebuchet.

Regards

Eddie

13 Jun 2012 9:26 #10337

Great hint, Eddie, i missed this routine somehow, searching in Help/Index instead of Help/Search BTW, for 64bit Win7 it gives ID_Platform, Major, Minor = 2, 6, 1, respectively. What OS gives 7?

14 Jun 2012 6:37 #10341

Hi,

yesterday I have sent an older version of my subroutine. Now I have found the newest version. It returns much more information on my PC:

MAJORVERSION=6 MINORVERSION=1 BUILDNUMBER=7601 PLATFORMID=2 CSYSTEM='Windows 7' and CSDVERSION='Service Pack 1'

Here is the listing:

  SUBROUTINE WINVERS(CSYSTEM,WINVERSION)

! USE MSWIN ! IMPLICIT NONE ! INTEGER4 N,WINVERSION CHARACTER CSYSTEM20,CSDVERSION128, & CMAJ3,CMIN3 LOGICAL4 LC ! INTEGER4 OSVERSIONINFO(37), & OSVERSIONINFOSIZE, & MAJORVERSION, & MINORVERSION, & BUILDNUMBER, & PLATFORMID INTEGER1 ICSDVERSION(128) EQUIVALENCE (OSVERSIONINFO(1),OSVERSIONINFOSIZE), & (OSVERSIONINFO(2),MAJORVERSION), & (OSVERSIONINFO(3),MINORVERSION), & (OSVERSIONINFO(4),BUILDNUMBER), & (OSVERSIONINFO(5),PLATFORMID), & (OSVERSIONINFO(6),ICSDVERSION) !----------------------------------------------------------------------- CSYSTEM='Windows ???' CSDVERSION=' ' !SERVICE PACK INFO OSVERSIONINFO=0 OSVERSIONINFOSIZE=148 ICSDVERSION=0 ! LC=GetVersionEx(OSVERSIONINFO)
! IF(LC)THEN
WINVERSION=MAJORVERSION ! DO N=1,128 IF(ICSDVERSION(N).EQ.0)THEN EXIT ELSE CSDVERSION(N:N)=CHAR(ICSDVERSION(N)) ENDIF ENDDO ! IF(MAJORVERSION.LT.5)THEN CSYSTEM='Windows 95' ELSEIF(MAJORVERSION.EQ.5)THEN IF(MINORVERSION.EQ.0)THEN CSYSTEM='Windows 2000' ELSEIF(MINORVERSION.EQ.1)THEN CSYSTEM='Windows XP' ELSEIF(MINORVERSION.EQ.2)THEN CSYSTEM='Windows Server 2003' ELSE WRITE(CMIN,'(I3)')MINORVERSION CMIN=ADJUSTL(CMIN) CSYSTEM='Windows 5.'// & TRIM(CMIN) ENDIF ELSEIF(MAJORVERSION.EQ.6)THEN IF(MINORVERSION.EQ.0)THEN CSYSTEM='Windows Vista' ELSEIF(MINORVERSION.EQ.1)THEN CSYSTEM='Windows 7' ELSE WRITE(CMIN,'(I3)')MINORVERSION CMIN=ADJUSTL(CMIN) CSYSTEM='Windows 6.'// & TRIM(CMIN) ENDIF ELSE WRITE(CMAJ,'(I3)')MAJORVERSION CMAJ=ADJUSTL(CMAJ) WRITE(CMIN,'(I3)')MINORVERSION CMIN=ADJUSTL(CMIN) CSYSTEM='Windows '// & TRIM(CMAJ)// & '.'// & TRIM(CMIN) ENDIF ENDIF ! RETURN END

Regards,

Detlef

14 Jun 2012 7:03 #10342

Hi,

just a short addition for WINDOWS 8:

  SUBROUTINE WINVERS(CSYSTEM,WINVERSION)

! USE MSWIN ! IMPLICIT NONE ! INTEGER4 N,WINVERSION CHARACTER CSYSTEM20,CSDVERSION128, & CMAJ3,CMIN3 LOGICAL4 LC ! INTEGER4 OSVERSIONINFO(37), & OSVERSIONINFOSIZE, & MAJORVERSION, & MINORVERSION, & BUILDNUMBER, & PLATFORMID INTEGER1 ICSDVERSION(128) EQUIVALENCE (OSVERSIONINFO(1),OSVERSIONINFOSIZE), & (OSVERSIONINFO(2),MAJORVERSION), & (OSVERSIONINFO(3),MINORVERSION), & (OSVERSIONINFO(4),BUILDNUMBER), & (OSVERSIONINFO(5),PLATFORMID), & (OSVERSIONINFO(6),ICSDVERSION) !----------------------------------------------------------------------- CSYSTEM='Windows ???' CSDVERSION=' ' !SERVICE PACK INFO OSVERSIONINFO=0 OSVERSIONINFOSIZE=148 ICSDVERSION=0 ! LC=GetVersionEx(OSVERSIONINFO) ! IF(LC)THEN WINVERSION=MAJORVERSION ! DO N=1,128 IF(ICSDVERSION(N).EQ.0)THEN EXIT ELSE CSDVERSION(N:N)=CHAR(ICSDVERSION(N)) ENDIF ENDDO ! IF(MAJORVERSION.LT.5)THEN CSYSTEM='Windows 95' ELSEIF(MAJORVERSION.EQ.5)THEN IF(MINORVERSION.EQ.0)THEN CSYSTEM='Windows 2000' ELSEIF(MINORVERSION.EQ.1)THEN CSYSTEM='Windows XP' ELSEIF(MINORVERSION.EQ.2)THEN CSYSTEM='Windows Server 2003' ELSE WRITE(CMIN,'(I3)')MINORVERSION CMIN=ADJUSTL(CMIN) CSYSTEM='Windows 5.'// & TRIM(CMIN) ENDIF ELSEIF(MAJORVERSION.EQ.6)THEN IF(MINORVERSION.EQ.0)THEN CSYSTEM='Windows Vista' ELSEIF(MINORVERSION.EQ.1)THEN CSYSTEM='Windows 7' ELSEIF(MINORVERSION.EQ.2)THEN CSYSTEM='Windows 8' ELSE WRITE(CMIN,'(I3)')MINORVERSION CMIN=ADJUSTL(CMIN) CSYSTEM='Windows 6.'// & TRIM(CMIN) ENDIF ELSE WRITE(CMAJ,'(I3)')MAJORVERSION CMAJ=ADJUSTL(CMAJ) WRITE(CMIN,'(I3)')MINORVERSION CMIN=ADJUSTL(CMIN) CSYSTEM='Windows '// & TRIM(CMAJ)// & '.'// & TRIM(CMIN) ENDIF ENDIF ! RETURN END

Regards,

Detlef

14 Jun 2012 10:26 #10346

There's no doubt that Detlef is getting more information than you get with GET_OS_VER@. The important thing is if 'Major' is 5 or less, and that's XP or earlier, or 6 or more, when it is Vista onwards, as some big changes occurred at this point (i.e. the system font change). Perhaps revisiting GET_OS_VER@ in the light of WIndows 8 is another job on Paul's list!

Eddie

14 Jun 2012 11:06 #10350

Detlef, thanks. But check the first one of last two, the CSDVERSION there shows just ascii soup, while second with Win8 addition works fine

14 Jun 2012 2:06 #10352

Hi Dan,

I don't see the difference between the two last versions, which could cause this problem. I have just added the two lines for recognizing Windows 8 in the second version. And, as I have written, I have got a readable answer for CSDVERSION='Service Pack 1'.

Detlef

16 Jun 2012 10:16 #10355

It's not even all miracles. When i run the code separately i get Win7 (major6, minor1), but when insert subroutine into large program it gives me WinXP (major5, minor1).

Suspect it is because i run the large program in the XP compatibility mode....

Same with GET_OS_VER@ (ID_Platform, Major, Minor)

17 Jun 2012 10:03 (Edited: 18 Jun 2012 1:27) #10362

Surprises continue, now i get different verdict also when i run codes including Sinverfrost's own GET_OS_VER@ in debugger! So not only i get bad result when i use those programs in the production code but i also can not debug the code!!! Detlef, can you make an experiment and tell what you get when you compile and run this code (say it's OS.F95 with your Win8 version of the subroutine with the only changes of added couple arguments to its list) like this

ftn95 OS.f95 /link /debug then

  1. run it: OS.EXE
  2. run OS.exe via debugger: sdbg OS.EXE

Full listing is here

!  Compile  ftn95 OS.f95 /link /debug    then
!  1. run OS.EXE   or
!  2. run the code via debugger:  sdbg OS.EXE


use mswin
CHARACTER CSYSTEM*20,CSDVERSION*128
integer WINVERSION, MINORVERSION

 call WINVERS8(WINVERSION, MINORVERSION, CSYSTEM,CSDVERSION) 
 print*, WINVERSION, MINORVERSION
! print*, CSYSTEM,CSDVERSION

 CALL GET_OS_VER@ (ID_Platform, Major, Minor)
 print*, Major, Minor, ID_Platform,

end

!--------------------------------------------------------

SUBROUTINE WINVERS8(WINVERSION, iRevision, CSYSTEM,CSDVERSION) 
 
 USE MSWIN 
 
 IMPLICIT NONE 
 
 INTEGER*4 N,WINVERSION,  iRevision 
 CHARACTER CSYSTEM*20,CSDVERSION*128, & 
 CMAJ*3,CMIN*3 
 LOGICAL*4 LC 
 
 INTEGER*4 OSVERSIONINFO(37), & 
 OSVERSIONINFOSIZE, & 
 MAJORVERSION, & 
 MINORVERSION, & 
 BUILDNUMBER, & 
 PLATFORMID 
 INTEGER*1 ICSDVERSION(128) 
 EQUIVALENCE (OSVERSIONINFO(1),OSVERSIONINFOSIZE), & 
 (OSVERSIONINFO(2),MAJORVERSION), & 
 (OSVERSIONINFO(3),MINORVERSION), & 
 (OSVERSIONINFO(4),BUILDNUMBER), & 
 (OSVERSIONINFO(5),PLATFORMID), & 
 (OSVERSIONINFO(6),ICSDVERSION) 
 !------------------------------------ 

 CSYSTEM='Windows ???' 
 CSDVERSION=' ' !SERVICE PACK INFO 
 OSVERSIONINFO=0 
 OSVERSIONINFOSIZE=148 
 ICSDVERSION=0 
 ! 
 LC=GetVersionEx(OSVERSIONINFO) 
 ! 
 IF(LC)THEN 

   WINVERSION=MAJORVERSION 
   iRevision = MINORVERSION 
 
     DO N=1,128 
     IF(ICSDVERSION(N).EQ.0)THEN 
       EXIT 
     ELSE 
       CSDVERSION(N:N)=CHAR(ICSDVERSION(N)) 
     ENDIF 
     ENDDO 
 
   IF(MAJORVERSION.LT.5)THEN 

     CSYSTEM='Windows 95' 

   ELSEIF(MAJORVERSION.EQ.5)THEN 

     IF(MINORVERSION.EQ.0)THEN 
       CSYSTEM='Windows 2000' 
     ELSEIF(MINORVERSION.EQ.1)THEN 
       CSYSTEM='Windows XP' 
     ELSEIF(MINORVERSION.EQ.2)THEN 
       CSYSTEM='Windows Server 2003' 
     ELSE 
       WRITE(CMIN,'(I3)')MINORVERSION 
       CMIN=ADJUSTL(CMIN) 
       CSYSTEM='Windows 5.'// & 
       TRIM(CMIN) 
     ENDIF 

   ELSEIF(MAJORVERSION.EQ.6)THEN 
  
     IF(MINORVERSION.EQ.0)THEN 
       CSYSTEM='Windows Vista' 
     ELSEIF(MINORVERSION.EQ.1)THEN 
       CSYSTEM='Windows 7' 
     ELSEIF(MINORVERSION.EQ.2)THEN 
       CSYSTEM='Windows 8' 
     ELSE 
       WRITE(CMIN,'(I3)')MINORVERSION 
       CMIN=ADJUSTL(CMIN) 
       CSYSTEM='Windows 6.'// & 
       TRIM(CMIN) 
     ENDIF 

   ELSE
17 Jun 2012 10:14 #10363
     WRITE(CMAJ,'(I3)')MAJORVERSION 
     CMAJ=ADJUSTL(CMAJ) 
     WRITE(CMIN,'(I3)')MINORVERSION 
     CMIN=ADJUSTL(CMIN) 
     CSYSTEM='Windows '// & 
     TRIM(CMAJ)// & 
     '.'// & 
     TRIM(CMIN) 

   ENDIF 
 ENDIF 

 RETURN 
 END
18 Jun 2012 6:31 #10365

I will take a look at this as soon as I can.

18 Jun 2012 6:49 #10366

Hi Dan,

I have no problems to compile, to run and to debug OS.F95.

These are my (reasonable) results:

6 1 6 1 2

Maybe the reason is the following:

I have the option /WINDOWS set as an active option in my FTN95 configuration. If you don't have set this option you should try to compile with

ftn95 OS.f95 /windows /link /debug

Detlef

18 Jun 2012 5:11 #10367

Thanks Detlef and Paul Summary so far under Win7 64bit is

  1. the code above as is gives me right major, minor=6, 1
  2. when run it via debugger i gets wrong result = 5, 1
  3. being placed in the large code i get always only wrong 5, 1
  4. /win key gives me no difference
18 Jun 2012 5:45 #10368

Hi Dan,

I have no problem when I run it via debugger.

I am still getting major, minor = 6, 1

I have made a screenshot in the debug mode, but I don't know how to upload it to the forum here.

Detlef

18 Jun 2012 7:51 #10369

There is nothing wrong with your code. Both methods give the same result means something behind exists.

I suggest to try running it in the XP compatibility mode (Properties/Compatibility/Run this program in XP compatibility mode for/ Windows XP(Service Pack 3) ). This and future EXE versions as a result should give you 5, 1. So these two methods detect not the OS on your computer but something different.

But is there a way to get the OS on this computer instead of lowest OS the code is compatible running with ?

23 Jun 2012 12:20 #10407

GetVersion is the old API function which has limitations.

See http://msdn.microsoft.com/en-us/library/windows/desktop/ms724439(v=vs.85).aspx

get_os_ver@ is the Salford/Silverfrost library routine and it calls the API GetVersionEx.

However the resulting major and minor version numbers are not unique as shown in the table at...

http://msdn.microsoft.com/en-us/library/windows/desktop/ms724833(v=vs.85).aspx

So we have a problem if you need to distinguish between operating systems with the same major and minor version numbers.

24 Jun 2012 3:22 #10413

It will be fine for me with the uncertainty between Win7 and Server 2012 (where both Major/Minor are equal to 6/1) but it will be not if my Win7 computer (Major 6) tells me that this is XP (Major 5)...

Things are that I've made the code compatible with XP by the following reason. This code is actually using another code as an interface between my program and the stock data source of electronic trading broker (Ameritrade or whatever, it is compatible to all of them). They communicate in a client - server manner, thanks to FTN95/CWP function allowing us to get the data from the internet (please make much more such functions ! Intel VF has 20+ more of them but they are not as user-friendly as in FTN95). This interface program when running opening internal server and my program pings its port, port responds accordingly to the protocol, and my code gets the responded data. Very easy.

The problem is that this interface program written by other authors under XP is not working flawlessly when it is moved to Win7. So i have set both mine and interface codes while working under Win7 to be compatible with XP using compatibility option of Win7 (which is also as easy as just couple clicks like i showed above).

The result is that now GetVersionEx is reporting the current Windows version on the computer as if it is XP. So when i move back to real XP sometimes i need to change all the disk names in my code manually because Win7 messed up all the disk partition letters on the computer which is not possible to rename (i have too many partitions from C to Z). If some function detected OS computer is running correctly i'd programmed that and all would work automatically.

Please login to reply.