Silverfrost Forums

Welcome to our forums

64-Bit FTN95 Compiler

5 May 2010 6:39 #6352

Paul,

Could a minimum FTN95_64 be :-

  • support for SLINK_64 to generate a 64-bit exutable,
  • Allocate > 2gb arrays and
  • subroutine array arguments could be explicitly declared as huge ?

So :-

  • Library routines limited to 2gb, so no change.
  • Array intrinsics limited to 2gb, so no change.
  • Write to/from big arrays could be excluded, so no change for I/O.

It would be good to generate a 64-bit exutable !

The code I would like to compile is SUBROUTINE REDCOL (A, B, NB, JB, JT, IL) ! ! Reduces vector 'A' by block 'B' ! real8, dimension(), huge, intent (inout) :: a real8, dimension(), huge, intent (in) :: b integer8, dimension(), huge, intent (in) :: nb INTEGER4 JB, JT INTEGER8 IL ! REAL8 VECSUM_big EXTERNAL VECSUM_big ! integer8 I0, J, JBOT, JPOINT, JBAND, J0, JL ! IF (JB > JT) RETURN JBOT = NB(1) I0 = 1-IL DO J = JB,JT JPOINT = J - JBOT + 3 J0 = NB(JPOINT) - J JL = NB(JPOINT-1) - J0 + 1 IF (IL > JL) JL = IL JBAND = J - JL IF (JBAND < 1) CYCLE A(J+I0) = A(J+I0) - VECSUM_big (A(JL+I0), B(JL+J0), JBAND) END DO ! RETURN END

      REAL*8 FUNCTION VECSUM_big (A, B, N)
!
!   Performs a vector dot product  VECSUM =  [A] . [B]
!
      integer*8,                     intent (in)    :: n
      real*8,    dimension(n), huge, intent (in)    :: a
      real*8,    dimension(n), huge, intent (in)    :: b
!
      real*8    c
      integer*8 i
!
      c = 0.0
      do i = n,1,-1
         c = c + a(i)*b(i)
      end do
      vecsum_big = c
      RETURN
!
      END

John

5 Aug 2011 11:46 #8739

A question to the developers of FTN95:

Are there already plans for a 64-bits-version of FTN95 / ClearWin? Can you tell me when approximately it will be available?

Thank you and best regards Wilfried

5 Aug 2011 12:40 #8740

There are currently no plans to write a 64 bit compiler but the possibility is continuously under review.

8 Aug 2011 2:00 #8752

What happenings can move this from 'review' to 'action'? It has been noted several times by different people on this forum that there is a very urgent need for this.

8 Aug 2011 6:09 #8755

No comment!

9 Aug 2011 6:12 #8757

That's pretty sad. Both things.

11 Dec 2018 11:07 #22955

I keep reading that 64 bit Windows allows 32 bit applications to use 4Gb. Now 32 bit Windows seems to limit applications to 2Gb, but with appropriate switches set, 3Gb is usable. That seems fair enough, as the 4Gb has to contain OS 'stuff'.

The 2Gb limit seems to apply for 32 bit FTN95 programs running under Windows 64, and that doesn't seem to me to be as reasonable. Suppose we take a program like this:

      PROGRAM BIG
      REAL*8 A(50000000),B(50000000),C(50000000)    !3*8*50=1200million
!      REAL*8 D(50000000),E(50000000),F(50000000)   !a
!      REAL*8 X(50000000),Y(50000000),Z(50000000)   !b
      INTEGER*4 J
      J=50000000
      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
      END

It runs fine, and produces the correct output of 3 ones.

Now, uncomment the lines marked !a, and although it seems to compile and run, it does not produce any output or error message. The same happens if both the !a and !b lines are uncommented. Clearly !a puts it over 2Gb, but !a and !b combined don't put it over 4Gb.

Can someone please clarify this for me? Doesn't the 'too big' problem deserve some sort of message?

Eddie

11 Dec 2018 4:23 #22963

Eddie

I could investigate this issue for you if it is critical to your development program.

No doubt the memory usage has some limiting factor but tracking the point of failure and whether or not there should/could be a failure message may be non-trivial and hence time consuming.

11 Dec 2018 5:31 #22964

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

11 Dec 2018 5:54 #22965

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.

12 Dec 2018 1:07 #22966

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.

      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
12 Dec 2018 1:17 #22967

code ctd.

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.

12 Dec 2018 8:31 #22968

As a footnote to John's helpful post, note that FTN95 provides the routine GlobalMemoryStatus@ as alternative to calling GlobalMemoryStatusEx directly.

12 Dec 2018 9:02 #22969

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

   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)
!
12 Dec 2018 9:03 #22970

ctd : contains

  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 
12 Dec 2018 10:03 #22971

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

12 Dec 2018 12:06 #22975

Quoted from LitusSaxonicum 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

12 Dec 2018 12:58 #22978

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

12 Dec 2018 1:14 #22979

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.

12 Dec 2018 2:32 #22980

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

Please login to reply.