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 

64-Bit FTN95 Compiler
Goto page Previous  1, 2, 3, 4  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
LitusSaxonicum



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

PostPosted: Tue Dec 11, 2018 6:31 pm    Post subject: Reply with quote

Paul,

Thanks for the offer, but nothing I do is contingent on the answer. I write stuff that works within 1Gb of RAM, and it's now hard to find a computer with that little.

However, there's an important point or two here, I believe. That is if a 32bit app should be able to access most, if not all, of 4Gb when running in a 64bit Windows OS, then that provides a 'halfway house' between the limits in a 32bit OS and making the app 64bit.

The second point, if there is one, is that there isn't an error message - the program just doesn't run. I think that there should be.

What would suit me best is that you could give it some thought during idle moments (if you have such things) and possibly announce the solution some time in the future, having found the solution with a minimum of effort and with an 'Eureka moment', but without treating it as any kind of high priority.

After all, this thread began with you more or less stating that there wasn't going to be a 64-bit FTN95, and now there is.

Best regards

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


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

PostPosted: Tue Dec 11, 2018 6:54 pm    Post subject: Reply with quote

Eddie

Unfortunately there are no easy answers as to how memory is allocated. Hopefully things will get simpler and better as the 64 bit compiler progresses but further development for 32 bits seems unlikely.

For 32 bits, /CHECK mode has its own memory management with limited size.
Otherwise (for 32 bits) memory can be static, allocated from the stack or allocated from the heap. On 32 bit machines total memory allocation was limited to 2GB with the possibility of extension to 3GB via a switch at startup together with one in SLINK. The limits of 32 bit FTN95 on 64 bit machines remains largely unexplored though John Campbell may have some insights into this.
Back to top
View user's profile Send private message AIM Address
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Dec 12, 2018 2:07 am    Post subject: Reply with quote

Eddie,

Combining your program and info Paul has provided previously, the following program demonstrates allocating of 4gb.
Note:
I have not tested using these arrays
The arrays above 2gb must be allocated, else the .exe is not recognised.
Code:
      PROGRAM BIG
      integer*4, parameter :: million = 1000000
      integer*4, parameter :: n = 50*million
      REAL*8 A(n),B(n),C(n)                         !3*8*50=1200million
      REAL*8, allocatable :: D(:),E(:),F(:)         !a
      REAL*8, allocatable :: X(:),Y(:),Z(:)         !b
      INTEGER*4 J, stat
!     
      J=n
      A(J)=1.0D0
      B(J)=1.0D0
      C(J)=1.0D0
!      D(J)=1.0D0   !a
!      E(J)=1.0D0   !a
!      F(J)=1.0D0   !a
!      X(J)=1.0D0   !b
!      Y(J)=1.0D0   !b
!      Z(J)=1.0D0   !b
      WRITE(*,*) A(J), B(J), C(J)
!      WRITE(*,*) D(J), E(J), F(J)   !a
!      WRITE(*,*) X(J), Y(J), Z(J)   !b
!
      call report_memory_usage ('FTN95_Version : no allocate')
      write (*,*) 'A defined at', jloc(A)
      write (*,*) 'B defined at', jloc(B)
      write (*,*) 'C defined at', jloc(C)
!
      allocate ( d(n), stat=stat )
      call report_memory_usage ('FTN95_Version : D allocated')
      if ( stat == 0 ) then
        write (*,*) 'D allocated at', jloc(d)
      else
        write (*,*) 'D NOT allocated : stat=', stat
      end if
!
      allocate ( e(n), stat=stat )
      call report_memory_usage ('FTN95_Version : E allocated')
      if ( stat == 0 ) then
        write (*,*) 'E allocated at', jloc(e)
      else
        write (*,*) 'E NOT allocated : stat=', stat
      end if
!
      allocate ( f(n), stat=stat )
      call report_memory_usage ('FTN95_Version : F allocated')
      if ( stat == 0 ) then
        write (*,*) 'F allocated at', jloc(f)
      else
        write (*,*) 'F NOT allocated : stat=', stat
      end if
!
      allocate ( X(n), stat=stat )
      call report_memory_usage ('FTN95_Version : X allocated')
      if ( stat == 0 ) then
        write (*,*) 'X allocated at', jloc(X)
      else
        write (*,*) 'X NOT allocated : stat=', stat
      end if
!
      allocate ( y(n), stat=stat )
      call report_memory_usage ('FTN95_Version : Y allocated')
      if ( stat == 0 ) then
        write (*,*) 'Y allocated at', jloc(Y)
      else
        write (*,*) 'Y NOT allocated : stat=', stat
      end if
!
      allocate ( Z(n), stat=stat )
      call report_memory_usage ('FTN95_Version : Z allocated')
      if ( stat == 0 ) then
        write (*,*) 'Z allocated at', jloc(Z)
      else
        write (*,*) 'Z NOT allocated : stat=', stat
      end if
!
    contains
      integer*8 function jloc (address)
        real*8    address(*)
        integer*4 aa(2)
        integer*8 bb
        equivalence (aa,bb)
        bb = 0
        aa(1) = loc (address)
        jloc  = bb
      end function jloc
      END
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Dec 12, 2018 2:17 am    Post subject: Reply with quote

code ctd.
Code:
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 *, ' '
   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


Apologies as to how well this works, it is a quick patch-up to see what is reported. more could be done to see what is usable.
Hopefully "report_memory_usage" works for 32 and 64 bit. It can be informative for what it does and doesn't report.

Basically to access > 2gb in 32-bit or 64-bit you need to use ALLOCATE.

There can also be a problem with 32-bit and using SDBG, so 64-bit would be much better alternative.
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


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

PostPosted: Wed Dec 12, 2018 9:31 am    Post subject: Reply with quote

As a footnote to John's helpful post, note that FTN95 provides the routine GlobalMemoryStatus@ as alternative to calling GlobalMemoryStatusEx directly.
Back to top
View user's profile Send private message AIM Address
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Dec 12, 2018 10:02 am    Post subject: Reply with quote

The following might not be very different, but provides more info for 32-bit or 64-bit compile. "bit_64" needs to be adjusted for 64-bit.
64-bit is a better option, unless you only have 32-bit dll's
Code:
   PROGRAM BIG
!
      logical   :: bit_64 = .false.                  ! change for 32-bit or 64-bit compile
      integer*8 :: one_Mb = 2**20                   ! size of 1 Mb
      integer*8 :: one_Gb = 2**30
      integer*4, parameter :: million = 1000000
      integer*4, parameter :: n = 50*million
!
      REAL*8  A(n),B(n),C(n)                        !3*8*50=1200million
      REAL*8, allocatable :: D(:),E(:),F(:)         !a
      REAL*8, allocatable :: X(:),Y(:),Z(:)         !b
      INTEGER*4 J, stat
!     
      call report_memory_usage ('FTN95_Version : start of usage')
      A(:)=(/(j,j=1,n)/)
      B = A+1
      C = A+2
      J = n
!
      call report_memory_usage ('FTN95_Version : no allocate')
      write (*,11) 'A defined at', jloc(A), gb_loc (A), A(j)
      write (*,11) 'B defined at', jloc(B), gb_loc (B), B(j)
      write (*,11) 'C defined at', jloc(C), gb_loc (C), C(j)
!
      allocate ( d(n), stat=stat )
      call report_memory_usage ('FTN95_Version : D allocated')
      if ( stat == 0 ) then
        D = A+3   !a
        write (*,11) 'D allocated at', jloc(D), gb_loc (D), D(j)
      else
        write (*,12) 'D NOT allocated : stat=', stat
      end if
!
      allocate ( e(n), stat=stat )
      call report_memory_usage ('FTN95_Version : E allocated')
      if ( stat == 0 ) then
        E = A+4   !a
        write (*,11) 'E allocated at', jloc(E), gb_loc (E), E(j)
      else
        write (*,12) 'E NOT allocated : stat=', stat
      end if
!
      allocate ( f(n), stat=stat )
      call report_memory_usage ('FTN95_Version : F allocated')
      if ( stat == 0 ) then
        F = A+5   !a
        write (*,11) 'F allocated at', jloc(F), gb_loc (F), F(j)
      else
        write (*,12) 'F NOT allocated : stat=', stat
      end if
!
      allocate ( X(n), stat=stat )
      call report_memory_usage ('FTN95_Version : X allocated')
      if ( stat == 0 ) then
        X = A+6   !a
        write (*,11) 'X allocated at', jloc(X), gb_loc (X), X(j)
      else
        write (*,12) 'X NOT allocated : stat=', stat
      end if
!
      allocate ( y(n), stat=stat )
      call report_memory_usage ('FTN95_Version : Y allocated')
      if ( stat == 0 ) then
        Y = A+7   !a
        write (*,11) 'Y allocated at', jloc(Y), gb_loc (Y), Y(j)
      else
        write (*,12) 'Y NOT allocated : stat=', stat
      end if
!
      allocate ( Z(n), stat=stat )
      call report_memory_usage ('FTN95_Version : Z allocated')
      if ( stat == 0 ) then
        Z = A+8   !a
        write (*,11) 'Z allocated at', jloc(Z), gb_loc (Z), Z(j)
      else
        write (*,12) 'Z NOT allocated : stat=', stat
      end if
   11 format (/a,' LOC =',i12,' or ',i3,':',i10,' val=',f0.1)
   12 format (/a,1x,i0)
!
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Dec 12, 2018 10:03 am    Post subject: Reply with quote

ctd : contains
Code:
  contains

    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
!Z     real*8, external :: gb
     
     mdata%dwLength = 64
   
     if (GlobalMemoryStatusEx(mdata)) then
   
       write (*,11) "Memory report at ", string, ' Mem_avail=',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)
       print 10, "Change in physical memory available         ", gb (mdata%ullAvailPhys-lastAvailPhys)
   
      lastAvailPhys = mdata%ullAvailPhys
   
     else
       print*,"Report Memory Failed ", string 
     end if
   
  10 format(1x,a,f0.3)
  11 format (/a,a,2x,a,B'---,---,---,--#')
     
    end subroutine report_memory_usage

    real*8 function gb ( bytes )
      integer*8 :: bytes
!
      gb = dble (bytes) / dble (one_gb)
    end function gb

    real*8 function Mb ( bytes )
      integer*8 :: bytes
!
      mb = dble (bytes) / dble (one_mb)
    end function mb

    integer*8 function jloc (address)    ! wirks for both 32-bit and 64-bit
      real*8    address(*)
      integer*4 aa(2)
      integer*8 bb
      equivalence (aa,bb)
!
      if ( bit_64 ) then
        bb    = loc (address)
      else
        bb = 0
        aa(1) = loc (address)
      end if
      jloc  = bb
    end function jloc

    function gb_loc (address) result (addr)
      REAL*8    address(*)
      integer*4 addr(2)
!
      integer*4 aa(2)
      integer*8 bb
      equivalence (aa,bb)
!
      if ( bit_64 ) then
        bb    = loc (address)
      else
        bb = 0
        aa(1) = loc (address)
      end if
      addr(1) = bb / one_gb
      addr(2) = mod (bb, one_gb)
    end function gb_loc

  END PROGRAM BIG
Back to top
View user's profile Send private message
LitusSaxonicum



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

PostPosted: Wed Dec 12, 2018 11:03 am    Post subject: Reply with quote

Many thanks, John,

It seems that going as far as Z (at full size) is an array too far - because there are two 2Gb limits, one for straightforward memory and one for allocatable memory.

Interesting. Now I understand some of your earlier posts.

Eddie
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Dec 12, 2018 1:06 pm    Post subject: Re: Reply with quote

LitusSaxonicum wrote:
It seems that going as far as Z (at full size) is an array too far - because there are two 2Gb limits, one for straightforward memory and one for allocatable memory.


I don't think that is the case as for 32-bit, if you make A,B,C allocatable, then you can still allocate all but Z, which is 3.2 Gb of allocatable arrays. All allocatable arrays go on the "Heap" which consists of multiple packets of available memory, unlike the stack, which is a single block of memory.
This can more easily be seen by reviewing the address of the arrays when using /64
Back to top
View user's profile Send private message
LitusSaxonicum



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

PostPosted: Wed Dec 12, 2018 1:58 pm    Post subject: Reply with quote

You may well be right with regards to allocatable stuff, John. I'll experiment.

I hadn't appreciated that I was using the stack.


Eddie
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Dec 12, 2018 2:14 pm    Post subject: Reply with quote

Eddie,

I am not sure where A,B & C are going in the original example. Unlikely it would be on the stack, as 1200 Mb would overflow the stack.
My comment regarding "unlike the stack, which is a single block of memory" was more a comment that the stack is a single block of memory, with a fixed size that is not extendable beyond a nominated limit (although even this comment may get me into hot water).
What can be seen from the allocatable array starting addresses is they are all over the available memory, so heap is a list of multiple packets of memory; much more flexible than stack overflow limitations.

Using more than 2gb with 32-bit can have other problems, I'd expect for /check or using SDBG, so not a great option.

I now do most of my coding with /64 which removes most of the memory restrictions.
Back to top
View user's profile Send private message
LitusSaxonicum



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

PostPosted: Wed Dec 12, 2018 3:32 pm    Post subject: Reply with quote

John,

I'm in the very fortunate position of not needing those very large data spaces and so the last thing I want to do is get anybody working on what for me is an academic, or (probably) non-, problem. There's more to the limitations than meets the eye.

Eddie
Back to top
View user's profile Send private message
John-Silver



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

PostPosted: Fri Dec 14, 2018 12:10 pm    Post subject: Reply with quote

I've just got up after a long nap, required after doing a bit of research on this simple (well it should be) and yet complex (not difficult complex but logically complex) befuddling question of how much memory: a) has one got available b) can one use .... yes there are 2 quesions to be answered. Often confused.

As a result, I ask the question ..... are Silverfrost / is FTN95 AWE]s-ome ? Smile
_________________
''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
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Sat Dec 15, 2018 9:26 am    Post subject: Reply with quote

It is worth running the program I provided both for FTN95 (/32) and FTN95 /64
( Note : line 3 logical :: bit_64 = .false. needs to be changed for the way I have written the code, although suggestions for using /CFPP would be appreciated )

What you get is two very different types of questions and answers.
Code:

For /32-bit, the following are very important;
"Amount of actual physical memory            ",  is memory installed (of interest)
"Amount of physical memory available         ", is memory available  (of interest)
"Committed memory limit                      ", is virtual paging memory (IGNORE)
"Amount of memory current process can commit ",  is virtual memory (IGNORE)
"Size of virtual address space               ", is available memory for 32-bit .exe (IMPORTANT)
"Amount of unreserved/uncommitted memory     ", is memory available (VERY IMPORTANT)
"Change in physical memory available         ", is memory used on latest allocate (IMPORTANT)

For /64-bit, the following are very important;
"Amount of actual physical memory            ",  is memory installed (IMPORTANT)
"Amount of physical memory available         ", is memory available  (VERY IMPORTANT)
"Committed memory limit                      ", is virtual paging memory (IGNORE)
"Amount of memory current process can commit ",  is virtual memory (IGNORE)
"Size of virtual address space               ",  is virtual Fortran memory (IGNORE)
"Amount of unreserved/uncommitted memory     ", is virtual Fortran memory (IGNORE)
"Change in physical memory available         ", is memory used on latest allocate (IMPORTANT)


When using windows with /64, you never want to exceed the "Amount of physical memory available"; else it looks like your pc has crashed !

When using FTN95 /32, the "Amount of unreserved/uncommitted memory" is typically all you have available for ALLOCATE.
With /CHECK, this will usually be less, as DEALLOCATE may work differently and extra memory is used by FTN95 /CHECK.
If your paging/virtual memory is a limit, then you have a bad setting for pagefile.sys
Back to top
View user's profile Send private message
DietmarSiepmann



Joined: 03 Jun 2013
Posts: 279

PostPosted: Mon Mar 04, 2019 3:53 pm    Post subject: Reply with quote

John,

although it is a little bit late Wink , here is a suggestion for running the code for both 32 bit and 64 bit.

You could substitute line 3 (logical :: bit_64 = .false.) by
Code:

#IFDEF BIT_64
      logical   :: bit_64 = .true.
#ELSE
      logical   :: bit_64 = .false.
#ENDIF

and activate the BIT_64 code (logical :: bit_64 = .true.) by adding
Code:

/CFPP /DEFINE BIT_64 1


to your ftn95 compile options. If you leave out "/define BIT_64 1" in your ftn95 call, then the #ELSE part (logical :: bit_64 = .false.) is activated.

You may check which part is activated by using ftn95 option /lis (in addition to all the other ftn95 options you use). Option /lis generates a file with extension lis which should contain one of the logical :: bit_64 declararations mentioned above (depending on whether "/define BIT_64 1" is set or not in your ftn95 options).

I use this technique to compile one and the same source for Salford 32 bit, Salford 64 bit and several INTEL compile environments.

Regards,
Dietmar
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 -> General All times are GMT + 1 Hour
Goto page Previous  1, 2, 3, 4  Next
Page 3 of 4

 
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