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 

Limits on GET_STORAGE@?
Goto page Previous  1, 2
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
PaulLaidler
Site Admin


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

PostPosted: Sun Apr 08, 2012 7:04 am    Post subject: Reply with quote

At the moment we do not have a system for general beta access. This is mainly because work can be taking place on different parts of the compiler etc. which means that extra work is required on our part in order to make beta versions reasonably safe. From time to time we do make beta versions available to individuals who are willing to accept the risks involved and this does help us to reduce the number of regressions that can occur with our full releases.
Back to top
View user's profile Send private message AIM Address
KennyT



Joined: 02 Aug 2005
Posts: 320

PostPosted: Mon Apr 09, 2012 2:30 pm    Post subject: Re: Reply with quote

JohnCampbell wrote:
K,

Look at the load map (.map) and see how much memory is used by static allocation....
John

Sorry, where is this shown? In my .EXE, I get:

Code:

Executable section map:

Section   Base      Length    Flags   

.text     00401000  00001a56  60000020
.bss      00403000  00000054  c0000080
.comment  00404000  000000fa  00000a00
.data     00405000  00000398  c0000040
.rdata    00406000  00000038  40000040
.idata    00407000  0000090f  c0000040
.rsrc     00408000  000748f8  40000040
.CRT      0047d000  0000000c  c0000040
.salfmap  0047e000  00000800  40000040
.salfdbg  0047f000  00000408  42000040
.salfsys  00480000  00000018  c0000040
.salfvc   00481000  0000002c  c0000040
.reloc    00482000  00000000  42000040


And in my main DLL:

Code:

Section   Base      Length    Flags   

.text     10001000  00fdaa40  60000020
.bss      10fdc000  05e2e3cc  c0000080
.comment  16e0b000  0000313a  00000a00
.data     16e0f000  00609d2b  c0000040
.rdata    17419000  00000038  40000040
.idata    1741a000  0000847b  c0000040
.CRT      17423000  0000000c  c0000040
.edata    17424000  0002c763  40000040
.salfmap  17451000  00032258  40000040
.salfdbg  17484000  0003de98  42000040
.salfsys  174c2000  00000018  c0000040
.salfvc   174c3000  0000002c  c0000040
.reloc    174c4000  00000000  42000040


K
Back to top
View user's profile Send private message Visit poster's website
JohnCampbell



Joined: 16 Feb 2006
Posts: 2625
Location: Sydney

PostPosted: Tue Apr 10, 2012 8:38 am    Post subject: Reply with quote

K,

I am not familiar with using a DLL.
However, I do have a subroutine which I use to map all available memory.
You can call it from a location in your code to identify what memory is now available for ALLOCATE.
Once you have called it, all memory is now locked so the program will not be able to proceed. It will give you some idea of what free memory is available if the routine had not been called.
Again, I have not tested this when using DLL's.

I hope this may provide an indication of where your memory is being lost.

John
Code:
!     ******************************************************************
!     report_free_mem.f95
!     Copyright(c) JDC 2000
!
!     Created: 29/09/2010 9:47:18 AM
!     Author : JOHN CAMPBELL
!     Last change: JC 10/04/2012 5:29:02 PM
!     ******************************************************************
!
      call report_free_memory_chunks (0)
      end

      subroutine report_free_memory_chunks (ilu)
!
! routine to find the largest available ALLOCATABLE memory space now available
!
      integer*4  ilu  ! unit number to report results
!
      integer*4, parameter :: one_mb_i4 = 2**18
      real*8,    parameter :: one_mb_r4 = 1024. * 1024. / 4.
      integer*8, parameter :: two       = 2
      integer*8, parameter :: four      = 4
!
!   Include a defined common for location
!z    integer*4, parameter :: i0 = 1500 * one_mb_i4     ! option to test large common
      integer*4, parameter :: i0 = 1 * one_mb_i4        ! small common option
      integer*4 a0(i0)
      common /aa/ a0
!
      integer*4 i, lu, iostat, m_i4, k, mi, n
      integer*8 l, nblock, block_start(0:30), block_size(0:30)
      integer*8 m8, bytes
      real*8    mb, sec, sec_0
      real*4    block_sec(0:30)
!
      integer*4, allocatable, dimension(:) :: jj    ! allocatable array for test 1
      integer*4, pointer,     dimension(:) :: ii    ! array for test 2; repeat allocation
!
      integer*4 get_free_memory_size
      external  get_free_memory_size
!
      lu = ilu
      if (lu < 11) lu = 1
      if (lu > 1) open (lu, file='free_mem.log')
!
!  Test 1 : Allocate increasing size arrays to report the maximum array and
!           identify an error response
!
      write (lu,2000) 'TEST 1 : Testing for maximum free block size'
      mi = 100 * one_mb_i4
      do i = 1,32
         m_i4 = mi * i
         allocate (JJ(m_i4), stat=iostat)
         if (iostat == 0) then
            call test_JJ (jj, m_i4, lu)
            deallocate (JJ)
         else
            mb = m_i4 ; mb = mb / one_mb_r4
            write (lu,9001) ' Testing size =',m_i4, mb, iostat
            exit
         end if
      end do
 9001 format (a,b'zz,zzz,zzz,zz#',3x,b'zz,zz#.##',' mb : error code ',i0)
!
!  Test 2 : Now keep allocating the largest available memory block
!           until no more appears available (max of 28)
!
      call cpu_sec (sec_0)
      write (lu,2000) 'TEST 2 : Mapping free memory'
!
      n              = 0
      nblock         = 0
      block_start    = 0
      block_size     = 0
      block_sec      = 0
!
!   stats on common AA
!lf95 l              = pointer (a0)
      l              = loc (a0)
      write (lu,1002) 0, size(a0)*4, l
      n              = n+1
      block_start(n) = l                   ! common address
      block_size(n)  = size(a0)*4          ! size (bytes)
      call cpu_sec (sec) ; sec = sec - sec_0
      block_sec(n)   = sec
!
      n              = n+1
      block_start(n) = two**32             ! end of possible memory
      nblock         = n
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2625
Location: Sydney

PostPosted: Tue Apr 10, 2012 8:40 am    Post subject: Reply with quote

code continued
Code:
!
      do i = 1,28

         m_i4  = get_free_memory_size (i)
!
         do k = 0,m_i4                              ! this loop included for LF95, reducing
            allocate (ii(m_i4), stat=iostat)
            if (iostat == 0) exit
            m_i4 = m_i4-1
            if (m_i4 < 4) exit
         end do
         if (k > 0) write (lu,*) 'Target array size reduced from', m_i4+k,' to',m_i4, iostat
!lf95           l = pointer (ii)
         l     = loc (ii)
!
         m8    = m_i4
         bytes = m8 * four
         call cpu_sec (sec) ; sec = sec - sec_0
         write (lu,1002) i, bytes, l, iostat, sec
         if (iostat /= 0) exit
         if (m_i4 < 4) exit
!
!      Insert block info into table
         do k = nblock,0,-1
            if (block_start(k) < l) then
               block_start(k+1) = l          ! start address
               block_size(k+1)  = bytes      ! memory size
               block_sec(k+1)   = sec
               nblock = nblock+1
               exit
            else
               block_start(k+1) = block_start(k)
               block_size(k+1)  = block_size(k)
               block_sec(k+1)   = block_sec(k)
            end if
         end do
      end do
!
 1002  format (' Array A',i2.2,' allocated as ',b'zz,zzz,zzz,zz#',' bytes, at address ',b'zz,zzz,zzz,zz#', i5, f10.4)
!
!  Now provide a map of free and reserved memory
!
      write (lu,2000) 'Free Memory Mapping'
      write (lu,2000) ' Blk       Lead Gap          Start     Size_bytes   Size_mb'
      do k = 1,nblock
         mb = block_size(k) / 1024. / 1024.
         write (lu,2002) k, block_start(k) - (block_start(k-1)+block_size(k-1)), block_start(k), block_size(k), mb, block_sec(k)
      end do
 2000 format (/1x,a)
 2002 format (i5,3(b'zzz,zzz,zzz,zz#'), f10.2, f10.4)
end

      integer*4 function get_free_memory_size (i)
!
!  This routinme searches for the largest available memory block still available
!  LF95 does not give non-zero STAT if array is > 2gb
!
      integer*4 i, m_low, m_high, m, iostat
      integer*4, allocatable, dimension(:) :: jj
!      real*4    mb
      integer*4, parameter :: m_high_start = 2**30 + 2**28    ! works as 2**29
      data  m_high / -1 /
!
      if (m_high < 0) m_high = m_high_start
      m_low = 0
!
      do
         m = m_low + (m_high-m_low)/2
         if (m == m_low) exit
         allocate (jj(m), stat=iostat)
!         mb = m ; mb = mb / one_mb_r4
!         write (*,2001)' testing', m, mb, iostat
!2001     format (a,b'zz,zzz,zzz,zz#',3x,b'zzz,zz#.##',' mb : error code ',i0)
         if (iostat /= 0) then
            m_high = m
         else
            m_low  = m
            deallocate (jj)
         end if
      end do
!
      get_free_memory_size = m
!
      end function get_free_memory_size

      subroutine test_JJ (jj, m, lu)
!
!  Tests array jj(m) exists by setting and checking values
!
      integer*4 m, jj(m), lu, i, k, er
      real*8    mb, sec, sec_0
      real*8,    parameter :: one_mb_r4 = 1024. * 1024. / 4.
      integer*8 byte_address
      data sec_0 / -1 /
!
      if (sec_0 < 0) call cpu_sec (sec_0)
      er = 0
      k  = m/2
      do i = 1,m
         k = k-1
         jj(i) = k
      end do

      k  = m/2
      do i = 1,m
         k = k-1
         if (jj(i) /= k) er = er+1
      end do
!
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2625
Location: Sydney

PostPosted: Tue Apr 10, 2012 8:43 am    Post subject: Reply with quote

and again as submit limit exceeded !!
Code:
!
      mb = m  ; mb = mb / one_mb_r4
!f95      byte_address  = pointer(jj)
      byte_address = loc(jj)
      call cpu_sec (sec)
      write (lu,2001) ' Testing size =',m, mb, ' at address ', byte_address, ' error count = ',er, sec-sec_0
 2001 format (a,b'zz,zzz,zzz,zz#',3x,b'zz,zz#.##',' mb',a,b'zz,zzz,zzz,zz#',a,i0,f8.2)
      sec_0 = sec
      end

      subroutine cpu_sec (sec)
      real*8 sec
      call use_QueryPerform (sec)
      end

      SUBROUTINE use_QueryPerform (time)
!
      real*8, intent (out) :: time
!
      STDCALL QUERYPERFORMANCEFREQUENCY 'QueryPerformanceFrequency' (REF):LOGICAL*4
      STDCALL QUERYPERFORMANCECOUNTER 'QueryPerformanceCounter' (REF):LOGICAL*4
!
      real*8 :: freq = -1.
      integer*8 num
      logical*4 ll
!
      if (freq < 0) then
         num  = 1
         ll   = QueryPerformanceFrequency (num)     ! cycle rate
         freq = 1.0d0 / dble (num)
      end if
!
      num  = 1
      ll   = QueryPerformanceCounter (num)          ! cycle count; assume ll is ok
!
      time = dble (num) * freq
!
      END SUBROUTINE use_QueryPerform


The free memory mapping reports the start and size of each free block of memory identified. The "Lead Gap" is chunks of memory which are in use. "Start" indicates when this used memory finished, which might give you some idea of what they are. I find that 30 blocks are enough, but this might change with your program.

John
Back to top
View user's profile Send private message
KennyT



Joined: 02 Aug 2005
Posts: 320

PostPosted: Tue Apr 10, 2012 10:29 am    Post subject: Reply with quote

Thanks John, above and beyond and all that!

K
Back to top
View user's profile Send private message Visit poster's website
JohnCampbell



Joined: 16 Feb 2006
Posts: 2625
Location: Sydney

PostPosted: Wed Apr 11, 2012 12:46 am    Post subject: Reply with quote

K,

I am interested to find out what memory is available.
I'd suggest that you call the free memory checking routine both early in the running of the program then near where the memory is not available.
You might want to skip test 1.
If I knew a way of releasing all the memory taken by the pointer array in test 2, then the routine could return for the program to continue.
It could be that the use of a DLL, giving an apparent split memory address (based on the load maps you supplied) could be limiting the available memory.
If so, is it possible to shift the DLL's start address? Again I have not made and linked my own DLL's to know about this.

John

Edit: I changed the memory mapping routine to releqase most of the memory, so that it can continue after being called. I did this with multiple pointer arrays to retain the first 15 addresses and then used DEALLOCATE. Appears to work. If you want to test this area, let me know.
Back to top
View user's profile Send private message
KennyT



Joined: 02 Aug 2005
Posts: 320

PostPosted: Fri Apr 13, 2012 9:06 am    Post subject: Reply with quote

Sorry, John,

a different panic has started (long term project finally got the go ahead!) so I don't have time to investigate this further at the moment. The /3GB switch seems to fix it so I'll carry on with that and get back to this as and when I get time!

thanks

K
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 -> Support All times are GMT + 1 Hour
Goto page Previous  1, 2
Page 2 of 2

 
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