forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

How to find Operating System the program is running on ?
Goto page 1, 2, 3  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Wed Jun 13, 2012 2:21 pm    Post subject: How to find Operating System the program is running on ? Reply with quote

Is it Win7, Vista or XP?
Back to top
View user's profile Send private message
dpannhorst



Joined: 29 Aug 2005
Posts: 165
Location: Berlin, Germany

PostPosted: Wed Jun 13, 2012 5:57 pm    Post subject: Reply with quote

You can do something like this:

SUBROUTINE WINVERS (SYSTEM)
!
USE MSWIN
IMPLICIT NONE
!
INTEGER*4 OS
CHARACTER SYSTEM*12,MAJORVERSION*6, &
MINORVERSION*6
!-----------------------------------------------------------------------
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
Code:
Back to top
View user's profile Send private message Visit poster's website
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Wed Jun 13, 2012 8:19 pm    Post subject: Reply with quote

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?
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Wed Jun 13, 2012 8:50 pm    Post subject: Reply with quote

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
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Wed Jun 13, 2012 10:26 pm    Post subject: Reply with quote

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?
Back to top
View user's profile Send private message
dpannhorst



Joined: 29 Aug 2005
Posts: 165
Location: Berlin, Germany

PostPosted: Thu Jun 14, 2012 7:37 am    Post subject: Reply with quote

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
!
INTEGER*4 N,WINVERSION
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
!
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
Back to top
View user's profile Send private message Visit poster's website
dpannhorst



Joined: 29 Aug 2005
Posts: 165
Location: Berlin, Germany

PostPosted: Thu Jun 14, 2012 8:03 am    Post subject: Reply with quote

Hi,

just a short addition for WINDOWS 8:

SUBROUTINE WINVERS(CSYSTEM,WINVERSION)
!
USE MSWIN
!
IMPLICIT NONE
!
INTEGER*4 N,WINVERSION
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
!
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
Back to top
View user's profile Send private message Visit poster's website
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Thu Jun 14, 2012 11:26 am    Post subject: Reply with quote

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
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Thu Jun 14, 2012 12:06 pm    Post subject: Reply with quote

Detlef, thanks. But check the first one of last two, the CSDVERSION there shows just ascii soup, while second with Win8 addition works fine
Back to top
View user's profile Send private message
dpannhorst



Joined: 29 Aug 2005
Posts: 165
Location: Berlin, Germany

PostPosted: Thu Jun 14, 2012 3:06 pm    Post subject: Reply with quote

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
Back to top
View user's profile Send private message Visit poster's website
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Sat Jun 16, 2012 11:16 pm    Post subject: Reply with quote

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)
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Sun Jun 17, 2012 11:03 pm    Post subject: Reply with quote

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

Code:
!  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


Last edited by DanRRight on Mon Jun 18, 2012 2:27 am; edited 6 times in total
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2815
Location: South Pole, Antarctica

PostPosted: Sun Jun 17, 2012 11:14 pm    Post subject: Reply with quote

Code:
     WRITE(CMAJ,'(I3)')MAJORVERSION
     CMAJ=ADJUSTL(CMAJ)
     WRITE(CMIN,'(I3)')MINORVERSION
     CMIN=ADJUSTL(CMIN)
     CSYSTEM='Windows '// &
     TRIM(CMAJ)// &
     '.'// &
     TRIM(CMIN)

   ENDIF
 ENDIF

 RETURN
 END
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7924
Location: Salford, UK

PostPosted: Mon Jun 18, 2012 7:31 am    Post subject: Reply with quote

I will take a look at this as soon as I can.
Back to top
View user's profile Send private message AIM Address
dpannhorst



Joined: 29 Aug 2005
Posts: 165
Location: Berlin, Germany

PostPosted: Mon Jun 18, 2012 7:49 am    Post subject: Reply with quote

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
Back to top
View user's profile Send private message Visit poster's website
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General All times are GMT + 1 Hour
Goto page 1, 2, 3  Next
Page 1 of 3

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group