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 program knows that it is 64bit or 32bit?
Goto page 1, 2, 3  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> 64-bit
View previous topic :: View next topic  
Author Message
DanRRight



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

PostPosted: Sat Apr 21, 2018 10:03 pm    Post subject: How program knows that it is 64bit or 32bit? Reply with quote

Any way for running program to know about itself is it 32 or 64bit ? If there is no such facility then would be great to create one
Back to top
View user's profile Send private message
wahorger



Joined: 13 Oct 2014
Posts: 1217
Location: Morrison, CO, USA

PostPosted: Sat Apr 21, 2018 10:56 pm    Post subject: Reply with quote

You could use /VPARAM and set the variable to a value when it is compiled.

In the Help file, under the 64 bit ClearWin+ section (Parallel Development using FTN95) is also described how one can use this facility to conditionally compile the code, thus using the appropriate USE or INCLUDE.

I use conditional compilation for two different reasons in my compilations. Works great!
Back to top
View user's profile Send private message Visit poster's website
wahorger



Joined: 13 Oct 2014
Posts: 1217
Location: Morrison, CO, USA

PostPosted: Sat Apr 21, 2018 11:21 pm    Post subject: Reply with quote

Examples:

This one allows me to set a parameter that defines an array size. The variable named, if it is NOT a /VPARAM, sets the parameter via the #else side.

Code:
#ifdef RESTRICTED
   INTEGER*4,PARAMETER:: MAX_REFERENCES = 5
#else
   INTEGER*4,PARAMETER:: MAX_REFERENCES = 8192
#endif


This one is used with my .INS files to initialize the variables only when being compiled in a BLOCK DATA program. This way, I can keep the variables AND the initialization in a single file, making changes much easier. The /VPARAM is there only on the compilation of the BLOCK DATA sections.

Code:

   common/select_holeid_common_INTS/n,catalog_index_list,select_catalog_entry,direction_holeid,
     $      fieldid_quad,fieldid_state,fieldid_scale_code,fieldid_scale_actual,fieldid_project,fieldid_logid_start,
     $      num_records,quad_selector,hole_selector,quad_select_holeid_time,quad_select_holeid_keystroke
#ifdef INIT_ME
   DATA   quad_selector/' '/,hole_selector/' '/
   DATA   select_catalog_entry/max_catalog_records*0/ ! for the LV control
   DATA   catalog_index_list/max_catalog_records*0/
   DATA   fieldid_quad/0/,fieldid_state/0/,fieldid_scale_code/0/,fieldid_scale_actual/0/,fieldid_project/0/,fieldid_logid_start/0/
   DATA   num_records/0/
   DATA   direction_holeid/10*.false./
   DATA   quad_select_holeid_keystroke/.false./
   DATA   quad_select_holeid_time/0.0/

#endif


I find using the existence (or non-existence #ifndef) better for me that using the value of the parameter name.

Code:

#ifndef RESTRICTED   
      sw_version   = my_block%sw_version
      serial      = my_block%serlno ! get the serial number
      download_link   = my_block%download_link
#else
      sw_version   = "For Evaluation Only"
      serial      = "Evaluation"
      download_link   = "http://cjdsoftware.com"
#endif


That said, I have used the value assigned to a /VPARAM parameter for another purpose earlier in my development process.
Back to top
View user's profile Send private message Visit poster's website
DanRRight



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

PostPosted: Sun Apr 22, 2018 4:05 pm    Post subject: Reply with quote

Bill, Never heard about /VPARAM so now despite of using this compiler for 3 decades starting from FTN77 i am like a novice looking at the new option and for me of course the most difficult part is just to start using it after reading the "FTN95 HELL-P" (everyone knows my idiosyncrasy to snobism of HELP or /HELP or error reporting of this compiler).

OK, let's look with the eyes of novice, this will be a good example: suppose i have the simplest 2 line code in the file aaa.f95
Code:
Print*, 'kk=',kk
end

which i compile
Code:
ftn95 aaa.f95 /debug /link /vparam kk 1 >z

to give kk the value 1 via /vparam. It is reasonable to expect based on HELP file the /vparam will assign kk value 1 during compilation, right? This is how novice thinks (novice may think about 10 different other ways of what's to do based on HELP file). So why this does not work always giving kk zero? And because this did not work for me no matter what i have done, i started with swearing more and more to try more crazy variants to make it work. I even tried to use your #ifdef in Fortran source code and got swear of compiler error in respond. Why HELP did not provide the complete example of usage in 3 decades?

Based on ideology of this compiler I'd expect to implement some kind of key in the form kk=IsThis64Bits@() . The /vparam if figure out how it actually works is probably more powerful then that but most probably there is nothing in other Fortran compilers to warrant that this feature will be in the Standard at least not in too distant future...


Last edited by DanRRight on Tue Apr 24, 2018 12:10 am; edited 1 time in total
Back to top
View user's profile Send private message
John-Silver



Joined: 30 Jul 2013
Posts: 1520
Location: Aerospace Valley

PostPosted: Sun Apr 22, 2018 8:22 pm    Post subject: Reply with quote

Dan, have you got the statement
Quote:
SPECIAL PARAMETER kk

in your Fortran code (which is my understanding is needed as well as specifuìying in the compile command line) ? ... and in no other type statement

see here
https://silverfrost.com/ftn95-help/exten/conditional_compilation.aspx
... of course a simple, clear example would be worth a thoudìsand words in the documentation, but I know I don't have to tell you that .
_________________
''Computers (HAL and MARVIN excepted) are incredibly rigid. They question nothing. Especially input data.Human beings are incredibly trusting of computers and don't check input data. Together cocking up even the simplest calculation ... Smile "
Back to top
View user's profile Send private message
DanRRight



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

PostPosted: Mon Apr 23, 2018 2:36 am    Post subject: Reply with quote

From my text above it is clear that i tried to 'translate' the general English text ( clearly, England is the country of Shakespeare) into something related to Fortran, so words, words, words. But seems this English words info in Help file have to be translated into some unknown specific command language of compilation? OMG. So many translations of something into something.

If the example would be there we'd translate it into something anyone on the planet would understands, even penguins in my Antarctica without necessity of additional translation of one more intermediate language, which are regular words in English in this case, into binary computer code.

If talk about verbosity I'd prefer that the Fortran compiler told me where is my errors instead of keeping mum and just crash with access violation. At least %pl has to do that for broader range of errors similar way like it already started to do when it sees zero in data with LOG scale


Last edited by DanRRight on Mon Apr 23, 2018 12:54 pm; edited 1 time in total
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


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

PostPosted: Mon Apr 23, 2018 7:22 am    Post subject: Reply with quote

Here is an extract from the notes on 64 bit FTN95....

CIF conditional compilation
----------------------------------------------------------------------------------------------------------------------------
_WIN32 and _WIN64 are predefined for use with CIF. For example:

CIF(_WIN64)
k = 64
CELSE
k = 32
CENDIF
print*, k

will print "64" if /64 (with /fpp) is used on the FTN95 command line.
This is particularly useful with CODE/EDOC blocks. In other contexts it is possible to use an equivalent run-time condition...

IF(KIND(1_7) == 4)THEN
k = 64
ELSE
k = 32
ENDIF
print*, k
Back to top
View user's profile Send private message AIM Address
DietmarSiepmann



Joined: 03 Jun 2013
Posts: 279

PostPosted: Mon Apr 23, 2018 9:58 am    Post subject: Reply with quote

Dan,

#ifdef relates to the C preprocessor and hence you would have to use option /cfpp when compiling the source with ftn95. Using C processeor statements Paul's code (using CIF) would read
Code:

#IF _WIN64     
      k = 64   
#ELSE         
      k = 32   
#ENDIF         
      print*, k

.

Paul,
are there other (preprocessor) symbols defined by ftn95 like _WIN64?

Regards,
Dietmar
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


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

PostPosted: Mon Apr 23, 2018 10:21 am    Post subject: Reply with quote

Dietmar

Yes there are others but they are not documented and I doubt that they remain useful. Here are two others that are easy to understand.

_DEBUG (indicates that /DEBUG has been used or implied)

_CLR (indicates that /CLR has been used)
Back to top
View user's profile Send private message AIM Address
wahorger



Joined: 13 Oct 2014
Posts: 1217
Location: Morrison, CO, USA

PostPosted: Mon Apr 23, 2018 6:40 pm    Post subject: Reply with quote

Dan, yes, I was also unable to get the value to "show up". Also, the SPECIAL PARAMETER statement does no eliminate the error if IMPLICIT NONE is specified.

That said, the #ifdef and #endif do work (with /CFPP), and knowing that _WIN32 and _WIN64 will allow detection of the compilation target is helpful.

I like the #ifdef because it is easier to see in the code that the other form of conditional compilation using CIF, et. al.

The "C" compiler does not have the problem you described and we both experienced with the compile-time value not getting "assigned".
Back to top
View user's profile Send private message Visit poster's website
DietmarSiepmann



Joined: 03 Jun 2013
Posts: 279

PostPosted: Wed May 22, 2019 3:13 pm    Post subject: Reply with quote

Paul,

does ftn95 supply a C-style preprocessor symbol for the version number of the ftn95 compiler?

Having one you could display the version number of the ftn95 compiler with which an executable has been built.

Moreover you would be able to write version dependent code then.

Regards,
Dietmar
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Thu May 23, 2019 5:55 am    Post subject: Reply with quote

Paul has previously supplied us with an example of calling GlobalMemoryStatusEx.
This includes the Size of virtual address space.
A review of this will indicate if 32 or 64 bit
I think I have posted this before but I just tested and it works for 32-bit and 64-bit FTN95.
You could easily cut it down to generate a logical function IS_64_bit.
Code:
  call report_memory_usage ('FTN95_Version')
  end
 
subroutine report_memory_usage (string)
  character string*(*)
!
 integer, parameter:: knd = 4

 stdcall GlobalMemoryStatusEx 'GlobalMemoryStatusEx'(REF):logical

 type MEMORYSTATUSEX
 sequence
   integer dwLength;
   integer dwMemoryLoad;
   integer(knd) ullTotalPhys;
   integer(knd) ullAvailPhys;
   integer(knd) ullTotalPageFile;
   integer(knd) ullAvailPageFile;
   integer(knd) ullTotalVirtual;
   integer(knd) ullAvailVirtual;
   integer(knd) ullAvailExtendedVirtual;
 end type 

 type(MEMORYSTATUSEX)::mdata
!
 integer(knd) :: lastAvailPhys = 0
  real*8 gb
  external gb
 
 mdata%dwLength = 64

 if (GlobalMemoryStatusEx(mdata)) then

  write (*,11) mdata%ullAvailPhys, (lastAvailPhys-mdata%ullAvailPhys), string

  lastAvailPhys = mdata%ullAvailPhys

   print *,  "Percentage of physical memory in use        ", mdata%dwMemoryLoad           
   print 10, "Amount of actual physical memory            ", gb(mdata%ullTotalPhys)
   print 10, "Amount of physical memory available         ", gb(mdata%ullAvailPhys)
   print 10, "Committed memory limit                      ", gb(mdata%ullTotalPageFile)
   print 10, "Amount of memory current process can commit ", gb(mdata%ullAvailPageFile)
   print 10, "Size of virtual address space               ", gb(mdata%ullTotalVirtual)
   print 10, "Amount of unreserved/uncommitted memory     ", gb(mdata%ullAvailVirtual)
 10 format(1x,a,f0.3)

 else
   print*,"Report Memory Failed ", string 
 end if

 11 format (B'---,---,---,--#',B'---,---,---,--#',2x,a)
 
end subroutine report_memory_usage

 real*8 function gb ( bytes )
   integer*8 :: bytes
   real*8    :: one_gb = 1024.*1024.*1024.   ! size of 1 gb
!
   gb = dble (bytes) / one_gb

 end function gb
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Thu May 23, 2019 6:15 am    Post subject: Reply with quote

The following simplified logical function appears to work with FTN95
Code:
 logical function is_64_bitx ()
!
 stdcall GlobalMemoryStatusEx 'GlobalMemoryStatusEx'(REF):logical
 integer*8, parameter :: two = 2
 integer*8 :: gb_32 = two**32
 integer*8 mdata(8)
 integer*4 leng
 equivalence (mdata, leng)
!
 mdata = 0
 leng  = 64

 if ( GlobalMemoryStatusEx(mdata) ) then

!   Size of virtual address space
   print*,"Virtual Memory =",mdata(6), gb_32
   is_64_bitx = ( mdata(6) > gb_32 )

 else
   print*,"Report Memory Failed "
   is_64_bitx = .false.
 end if

end function is_64_bitx
Back to top
View user's profile Send private message
DietmarSiepmann



Joined: 03 Jun 2013
Posts: 279

PostPosted: Thu May 23, 2019 11:53 am    Post subject: Reply with quote

John,

thank-you for the code example you posted. I now learnt how to check at runtime if an app executed is a 64 bit app or not.

In the same post Paul gave the hint to preprocessor symbol _WIN64 (and _Win32) which is known at compile time if ftn95 option /fpp [using preprocessor if clause CIF(_WIN64) ] or /cfpp [using C style preprocessor if clause #IF _WIN64) is used. The samples in the post show how you would use this symbol to print if the app is a 64 bit app or a 32 bit app.

Now I am interested in a C style preprocessor symbol say FTN95_VERSION containing the version information of ftn95 (i.e. 8.50, 8.40 or 8.30) depending on the version used for compilation. If we had such a symbol the version number of the compiler which has been used for building an app could be printed.

I could use it for my test samples for the big number ftn95 versions installed on my machine automatically (printing the version number and if it is a 64 bit or 32 bit executable).

If such a symbol existed that would be fine. That's why my question Wink

Regards,
Dietmar
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Thu May 23, 2019 12:07 pm    Post subject: Reply with quote

Rather than going the C preprocessor route, I think that the better solution to obtaining the compiler version, etc., is to use the F2008 intrinsics COMPILER_VERSION() and COMPILER_OPTIONS(), which are part of the module ISO_FORTRAN_ENV.

We can request Paul to consider implementing these intrinsics.
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> 64-bit 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