replica nfl jerseysreplica nfl jerseyssoccer jerseyreplica nfl jerseys forums.silverfrost.com :: View topic - Allocate/Deallocate
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 

Allocate/Deallocate
Goto page Previous  1, 2, 3  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Mon Apr 08, 2013 4:57 am    Post subject: Reply with quote

If there is not sufficient memory for a duplicate copy, you could use LOC(old_array) and LOC(new_array) and move the values if the start has shifted. You can use FCORE4 or DCORE8 for this purpose. See in help "Win32 platform" > "The in-line assembler" > "Other machine-level facilities"
Be careful not to overwrite the old to new values, depending on if LOC(new) > LOC(old). The argument for DCORE8 is the memory byte address.

I tried the following code, but unfortunalely it did not work
Code:
      MODULE ARRAY_STORAGE
      integer*4, parameter :: million = 1000000
      integer*4 :: num = 250*million    ! 1.9gb
      REAL*8, ALLOCATABLE :: ARRAY(:)
      integer*4 :: test_count = 0
      END MODULE ARRAY_STORAGE
!--------------------------------------------------------------------
      PROGRAM MAIN
      USE ARRAY_STORAGE
!
         call test_allocate
      call sub_allocate
         call test_allocate
      call sub_set
         call test_allocate
      call sub_print
         call test_allocate
!
      call sub_resize_big (num/2)
         call test_allocate
!
      call sub_print
      call sub_deallocate
         call test_allocate
!
      END MAIN
!--------------------------------------------------------------------
      subroutine sub_allocate
      USE ARRAY_STORAGE
      integer*4 stat
!
      ALLOCATE (ARRAY(num),stat=stat)
      if (stat/=0) then
         write (*,*) 'problem allocating array : stat=',stat
         stop
      else
         write (*,11) ' array allocated as size ', size(array)*8./(2.**20),' mb at ',loc(array)
      end if
11    format (a,f0.3,a,b'z,zzz,zzz,zz#')
      end subroutine sub_allocate

      SUBROUTINE SUB_set
      USE ARRAY_STORAGE
      INTEGER*4 I
!
      write (*,*) 'Initialising array'
      DO I=1,num
        ARRAY(I) = REAL(I,KIND=2)
      END DO
      RETURN
      END SUBROUTINE SUB_set

      subroutine sub_print
      USE ARRAY_STORAGE
      integer*4 i
!
      write (*,*) 'First 10 values of array'
      DO I=1,10
        WRITE (*,*) ARRAY(I)
      END DO
      end subroutine sub_print

      subroutine sub_deallocate
      USE ARRAY_STORAGE
!
      write (*,*) 'Releasing array'
      DEALLOCATE (ARRAY)
      end subroutine sub_deallocate

      subroutine test_allocate
      USE ARRAY_STORAGE
!
      test_count = test_count+1
      if (ALLOCATED (ARRAY) ) then
         write (*,11) 'Test ',test_count,' ARRAY is allocated as ', size(array)*8./(2.**30),' gb at ',loc(array)
      else
         write (*,11) 'Test ',test_count,' ARRAY is NOT allocated'
      end if
11    format (20x,a,i0,a,f0.3,a,b'z,zzz,zzz,zz#')
      end subroutine test_allocate
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Mon Apr 08, 2013 5:35 am    Post subject: Reply with quote

Code:
      subroutine sub_resize_big (num_new)
      USE ARRAY_STORAGE
      integer*4 num_new
!
      integer*4 i, p_old, p_new
      integer*8 q_old, q_new
!
      write (*,*) 'Resizing array'
!
      q_old = LOC (array) ; if (q_old < 0) Q_old = q_old + 2_4**32
      p_old = q_old
      deallocate (array)
!
      num = num_new 
      call sub_allocate
!
      q_new = LOC (array) ; if (q_new < 0) Q_new = q_new + 2_4**32
      p_new = q_new
      write (*,*) Q_old, Q_new
      write (*,11) 'Moving array from ',Q_old,' to ',Q_new
11    format (a,b'z,zzz,zzz,zz#',a,b'z,zzz,zzz,zz#')
!
      if (q_new == q_old) return
      if (Q_new < Q_old) then
         do i = 1,num
            write (*,*) i, q_old, p_old, q_new, p_new
            DCORE8(p_new) = DCORE8(P_old)
            q_new = q_new + 8_4
            q_old = q_old + 8_4
            p_new = q_new
            p_old = q_old
         end do
      else
         q_old = q_old + num*8_4
         q_new = q_new + num*8_4
         do i = 1,num
            q_new = q_new - 8_4
            q_old = q_old - 8_4
            p_new = q_new
            p_old = q_old
            DCORE8(p_new) = DCORE8(P_old)
         end do
      end if         
!
      end subroutine sub_resize_big


Unfortunately the memory address 2,147,418,144 is not allowed in DCORE8 when calling sub_resize_big. Am I using DCORE8 correctly ?
Also, when I reduce NUM to 150 * Million, the approach still did not work, as "array" appears to have been zeroed when I allocated it in sub_resize_big > sub_allocate ?
I expected this to work. Any ideas ?

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



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Mon Apr 08, 2013 11:00 pm    Post subject: Reply with quote

If I run the above program (in the last 2 posts) I get an access violation error at:
DCORE8(p_new) = DCORE8(P_old)

this is the first pass of the loop, where P_old and P_new come from LOC
I don't see what is wrong ?

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



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Tue Apr 09, 2013 2:20 am    Post subject: Reply with quote

Paul,

The following simple example appears to show that DEALLOCATE changes the memory location value when num = 10. Possibly array is allocated on the heap/stack ? The change could be due to subsequent use of the heap/stack.
Code:
integer*4, allocatable :: array(:)
integer*4              :: num = 10
integer*4              :: i,ii
!
allocate (array(num)) ; write (*,*) 'allocate (array(num))', num
ii = loc(array)       ; write (*,*) 'ii = loc(array)      ', ii,' Note: address can change on rerun'
i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i
array(1) = 11         ; write (*,*) 'array(1) = 11        ', array(1)
i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i
deallocate (array)    ; write (*,*) 'deallocate (array)   '
i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i,' Note: value changed on deallocate'
end

However if num = 10,000,000, with a different address "II", I get an access violation error when array is deallocated. Array is now allocated outside the previous memory scope of the program, which is reduced once array is released, causing the access violation ?
Code:
integer*4, allocatable :: array(:)
integer*4              :: num = 10000000
integer*4              :: i,ii
!
allocate (array(num)) ; write (*,*) 'allocate (array(num))', num
ii = loc(array)       ; write (*,*) 'ii = loc(array)      ', ii,' Note: address can change on rerun'
i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i
array(1) = 11         ; write (*,*) 'array(1) = 11        ', array(1)
i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i
deallocate (array)    ; write (*,*) 'deallocate (array)   '
i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i,' Note: value changed on deallocate'
end

I did not expect that LOC or CORE4 were restricted for the memory they can address ?
Do you agree with this assessment ?

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



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Tue Apr 09, 2013 4:49 am    Post subject: Reply with quote

An attempt to extend the active address did not succeed. There is more to the access violation test ?
Code:
integer*4, allocatable :: array(:), b(:)
integer*4              :: num = 10000000
integer*4              :: i,ii, j
!
  do j = 0,4              ; write (*,*) ' '
    if (j<4) num = 10 * 100**j
                            write (*,*) ' Test J=',j
    allocate (array(num)) ; write (*,*) 'allocate (array(num))', num
    if (j==3) then
      allocate (b(num))   ; write (*,*) 'allocate (b(num))    ', num,' Note: attempt to extend memory'
      ii = loc(b)         ; write (*,*) 'ii = loc(b)          ',  ii,' Note: address can change on rerun'
    end if
    ii = loc(array)       ; write (*,*) 'ii = loc(array)      ', ii,' Note: address can change on rerun'
    i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i
    array(1) = 11         ; write (*,*) 'array(1) = 11        ', array(1)
    i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i
    deallocate (array)    ; write (*,*) 'deallocate (array)   '
                            write (*,'(a,z9)') ' ii (hex) =              ', ii
    i = core4(ii)         ; write (*,*) 'i = core4(ii)        ', i,' Note: value changed on deallocate'
    if (j==3) then
      deallocate (b)      ; write (*,*) 'deallocate (b)'
    end if
  end do
end


The conclusion from this example is when you deallocate a large array, the memory it used is released from this process and can't be later used.

So, if you can't store both the old and new array (or 2 x new), then you can't REALLOCATE the array. The first sub_resize I posted is probably the only practical solution, which should work for arrays up to about 1gb in size. Certainly, reducing a 1.9gb array to a 1.2gb array will not work (in memory).

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



Joined: 17 Jul 2009
Posts: 560
Location: UK

PostPosted: Tue Apr 09, 2013 4:57 pm    Post subject: Re: Reply with quote

JohnCampbell wrote:

The conclusion from this example is when you deallocate a large array, the memory it used is released from this process and can't be later used.


A Fortran Compiler doesn't have to carry out "Garbage Collection" (google it) that would be needed for DEALLOCATE to release memory back to the heap (for future ALLOCATE or STACK use). Instead, its allowed to leave the memory unaccessible, and let the Operating System tidy up when the program run finishes.

The only Fortran compiler I know that does "Garbage Collection" is NAG, which provides this as an option, though it increases run times when its enabled.
_________________
Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Tue Apr 09, 2013 10:39 pm    Post subject: Reply with quote

There appears to be two types of allocate.
1) small arrays (that fit) might be allocated on the heap/stack. (They certainly get addresses inside the existing memory footprint.)
2) Larger arrays are allocated elsewhere in available memory.
For large arrays that do not fit on the "heap", ALLOCATE still finds memory for them.

Certainly for the arrays that are allocated above address 2gb, these extend the memory footprint of the program. When they are released, the memory footprint changes.
This can be observed when running task manager.

It appears to be that when these large arrays are released, DEALLOCATE initiates a change in the memory allocation, which can be observed in task manager. There must be something manageing this "Garbage Collection".

This is my present understanding of why I am getting the access violation after releasing large size arrays.

There is a similar concept with MODULE, where large arrays in a module are given their own address in the .map report. I'm not sure if they can be located from the main part of the module, or just identified in the ,map report.

Certainly FTN95's implementation of ALLOCATE and the ability to use up to 4gb of memory is a useful addition, (now with /debug).

It would be good if LOC and the address that CORE4 etc use could be integer*8 or unsigned integer*4, so that the addresses above 2gb could be more easily managed. I'm not sure how this could be improved. I shall expand on my use of q_new in the last post to see how this is being managed at present.
(Could we have a BYTE type, say BYTE*4. BYTE*1 is also a useful option for colours. They could support == < > for comparison, + and - for abs value or mod of result)

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



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Wed Apr 10, 2013 4:43 am    Post subject: Reply with quote

The following example demonstrates the progressive allocation and use of large allocated arrays, then progressive release. I am using Win 7_64 OS.

You can track the memory usage in task manager. I have selected a number of memory usage measures, including:
Working Set (memory)
Peak Working Set (memory)
Memory (Private Working Set)
Commit Size
PF Delta

This shows that memory is being allocated and then released.
Resize also works, if the temporary array can be allocated.

Code:
      MODULE ARRAY_STORAGE
      integer*4, parameter :: million = 1000000
      integer*4 :: num_a = 500*million    ! 1.9gb
      integer*4 :: num_i = 12000   !  sqrt(150*million)    ! 0.6gb
!
!     REAL*8,    ALLOCATABLE :: ARRAY(:)
      integer*4, ALLOCATABLE :: ARRAY(:)
      real*4,    ALLOCATABLE :: a(:,:), b(:,:), c(:,:), d(:,:)
      integer*4 :: test_count = 0
!
      CONTAINS

       subroutine sub_report (name, aa)
       character name*(*)
       integer*4 aa(:), i
       integer*8 j
!
       write (*,*) ' ARRAY ',name,' at ',loc(aa),' size ',size(aa)
       do i = 1,10
         write (*,'(i5,i8)') i, aa(i)
       end do
       i = loc(aa)  ; write (*,*) 'loc(aa) ', i
       i = core4(i) ; write (*,*) 'core4(i)', i
       j = loc(aa)  ; write (*,*) 'loc(aa) ', j
       j = core4(j) ; write (*,*) 'core4(j)', j
        if (j < 0) j = j + 2_4**32
       write (*,*) ' '
       end subroutine sub_report
!
       subroutine sub_report2 (name, aa)
       character name*(*)
       real*4 aa(:,:)
       integer*4 i
       integer*8 jloc, j
       external  jloc
!
       write (*,*) ' ARRAY ',name,' at ',loc(aa),' size ',size(aa)
       do i = 1,10
         write (*,'(i5,f12.2)') i, aa(i,1)
       end do
       i = loc(aa)  ; write (*,*) 'loc(aa) ', i
       i = core4(i) ; write (*,*) 'core4(i)', i
       j = jloc(aa) ; write (*,*) 'jloc(aa)', j
       j = core4(j) ; write (*,*) 'core4(j)', j
        if (j < 0) j = j + 2_4**32
       write (*,*) ' '
       end subroutine sub_report2
!
      END MODULE ARRAY_STORAGE
!--------------------------------------------------------------------
      PROGRAM MAIN
      USE ARRAY_STORAGE
!
         call test_allocate
      call sub_allocate (0)
         call test_allocate
      call sub_set
         call test_allocate
      call sub_print
         call test_allocate
!
      call sub_resize (num_a/2)
!      call sub_resize_big (num_a/2)
         call test_allocate
!
      call sub_print
      call sub_deallocate
         call test_allocate
!
      END MAIN
!--------------------------------------------------------------------

      subroutine sub_allocate (pass)
      USE ARRAY_STORAGE
      integer*4 pass, stat
      integer*8 jloc
      external  jloc
!
!  test of 4 smaller arrays
    if (pass == 0) then
!
      allocate (a(num_i,num_i),stat=stat)
         write (*,11) ' a allocated as size ', size(a)*4./(2.**20),' mb at ',jloc(a), stat
       call sub_use (a, num_i)
       call sub_report2 ('a', a)
!
      allocate (b(num_i,num_i),stat=stat)
         write (*,11) ' b allocated as size ', size(b)*4./(2.**20),' mb at ',jloc(b), stat
       call sub_use (b, num_i)
       call sub_report2 ('b', b)
!
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Wed Apr 10, 2013 4:45 am    Post subject: Reply with quote

Code:
!
      allocate (c(num_i,num_i),stat=stat)
         write (*,11) ' c allocated as size ', size(c)*4./(2.**20),' mb at ',jloc(c), stat
       call sub_use (c, num_i)
       call sub_report2 ('c', c)
!
      allocate (d(num_i,num_i),stat=stat)
         write (*,11) ' d allocated as size ', size(d)*4./(2.**20),' mb at ',jloc(d), stat
       call sub_use (d, num_i)
       call sub_report2 ('d', d)
!
      deallocate (d)
       call sub_use (c, num_i)
      deallocate (c)
       call sub_use (b, num_i)
      deallocate (b)
       call sub_use (a, num_i)
      deallocate (a)
!
    end if
!
!  Now main array
      ALLOCATE (ARRAY(num_a),stat=stat)
      if (stat/=0) then
         write (*,*) 'problem allocating array : stat=',stat
         stop
      else
         write (*,11) ' array allocated as size ', size(array)*4./(2.**20),' mb at ',loc(array)
      end if
11    format (a,f0.3,a,b'--,---,---,--#',i5)
      end subroutine sub_allocate

      subroutine sub_resize (num_new)
      USE ARRAY_STORAGE
      integer*4 num_new
!
      integer*4 n
      integer*4 stat
      integer*4, ALLOCATABLE :: temp_array(:)
!
      write (*,*) 'Resizing array'
      num_a = size (array)
      n     = min (num_a, num_new)
      allocate (temp_array(n), stat=stat)
      if (stat/=0) then
         write (*,*) 'problem allocating temp_array : stat=',stat
         stop
      else
         write (*,11) ' temp_array allocated as size ', size(temp_array)*4./(2.**20),' mb at ', loc(temp_array)
      end if
11    format (a,f0.3,a,b'--,---,---,--#')
!
      temp_array(1:n) = array(1:n)
      deallocate (array)
!
      num_a = num_new 
      call sub_allocate (1)
!
      array(1:n)       = temp_array
      array(n+1:num_a) = 0               
      deallocate (temp_array)
!
      end subroutine sub_resize

      SUBROUTINE SUB_set
      USE ARRAY_STORAGE
      INTEGER*4 I
!
      write (*,*) 'Initialising array'
      DO I=1,num_a
        ARRAY(I) = REAL(I,KIND=2)
      END DO
      RETURN
      END SUBROUTINE SUB_set

      subroutine sub_print
      USE ARRAY_STORAGE
      integer*4 i
!
      write (*,*) 'First 10 values of array'
      DO I=1,10
        WRITE (*,*) ARRAY(I)
      END DO
      end subroutine sub_print

      subroutine sub_deallocate
      USE ARRAY_STORAGE
!
      write (*,*) 'Releasing array'
      DEALLOCATE (ARRAY)
      end subroutine sub_deallocate

      subroutine test_allocate
      USE ARRAY_STORAGE
!
      test_count = test_count+1
      if (ALLOCATED (ARRAY) ) then
         write (*,11) 'Test ',test_count,' ARRAY is allocated as ', size(array)*4./(2.**30),' gb at ',loc(array)
      else
         write (*,11) 'Test ',test_count,' ARRAY is NOT allocated'
      end if
11    format (20x,a,i0,a,f0.3,a,b'--,---,---,--#')
      end subroutine test_allocate

      subroutine sub_resize_big (num_new)
      USE ARRAY_STORAGE
      integer*4 num_new
!
      integer*4 i, p_old, p_new, ii
      integer*8 q_old, q_new, num_bits
!
      write (*,*) 'Resizing array'
!
      q_old = LOC (array) ; if (q_old < 0) Q_old = q_old + 2_4**32
      p_old = q_old
      write (*,*) 'core4(q_old)', core4(q_old)
!
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Wed Apr 10, 2013 4:49 am    Post subject: Reply with quote

Code:
      deallocate (array)
      write (*,*) 'core4(q_old)', core4(q_old)
!
      num_a = num_new 
      call sub_allocate (1)
!
      q_new = LOC (array) ; if (q_new < 0) Q_new = q_new + 2_4**32
      p_new = q_new
      write (*,*) Q_old, Q_new
      write (*,11) 'Moving array from ',Q_old,' to ',Q_new
11    format (a,b'--,---,---,--#',a,b'--,---,---,--#')
!
      if (q_new == q_old) return
      if (Q_new < Q_old) then
         num_bits = 4
         do i = 1,num_a
            write (*,*) i, q_old, p_old, q_new, p_new
            ii = CORE4(P_old)
            write (*,*) 'ii = CORE4(P_old)', ii
            CORE4(p_new) = ii
            write (*,*) 'CORE4(p_new) = ii'
            CORE4(p_new) = CORE4(P_old)
            write (*,*) 'CORE4(p_new) = CORE4(P_old)'
            q_new = q_new + num_bits
            q_old = q_old + num_bits
            p_new = q_new
            p_old = q_old
         end do
      else
         num_bits = 4
         q_old = q_old + num_a*num_bits
         q_new = q_new + num_a*num_bits
         do i = 1,num_a
            q_new = q_new - num_bits
            q_old = q_old - num_bits
            p_new = q_new
            p_old = q_old
            CORE4(p_new) = CORE4(P_old)
!            DCORE8(p_new) = DCORE8(P_old)
         end do
      end if         
!
      end subroutine sub_resize_big

      subroutine sub_use (a, num)
      integer*4 num
      real*4    a(num,num)
!
      real*4, allocatable, dimension(:) :: b, c
      integer*4 i,j
!
      allocate ( b(num), c(num) )
      write (*,*) 'processing array', loc(b), loc(c)
!
      a = 0
        do i = 1,num
          b(i) = i*3-2
          call random_number (c(i))
        end do
!
      do j = 1,num/500
        do i = 1,num
          a(i,j) = dot_product (b, c) * c(i) / num
        end do
      end do
!
      end

      integer*8 function jloc (a)
      integer*8 j
      integer a
!
      j = loc (a)
      if (j < 0) J = J + 2_4**32
!
      jloc = j
      end


( It would be good if we could attach code examples as text files )

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



Joined: 08 Apr 2011
Posts: 155

PostPosted: Fri Jun 07, 2013 4:15 pm    Post subject: To John.. Reply with quote

Hi John,

I tried compileing this code which you advised using ALLOCATABLE for large arrays.

However, it does not compile and gives em an error stating that:

Quote:
Warning 1 In a call to JLOC from another procedure, the first argument was of type REAL(KIND=1), it is now INTEGER(KIND=3) C:\Users\localadmin\Desktop\FortranApplication1\FortranApplication1\FreeFormat1.F95 280
Error 2 FUNCTION 'JLOC' called with argument no 1 as a REAL(KIND=1) when a INTEGER(KIND=3) was expected (from SUBROUTINE 'ARRAY_STORAGE!SUB_REPORT2') LINK


I'm very curious to understand your approach...
Back to top
View user's profile Send private message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Fri Jun 07, 2013 6:09 pm    Post subject: Reply with quote

John,

I solved the problem by declaring 'a' as real*4 instead of integer*4.


Code:

      integer*8 function jloc (a)
      integer*8 j
[b]      real*4 a [/b]!
      j = loc (a)
      if (j < 0) J = J + 2_4**32
!
      jloc = j
      end


Is it possible to briefly explain what is the basic difference between allocating small and large arrays?Did your code above work without any problems or did you face any 'access violation errors'?

Christy
Back to top
View user's profile Send private message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Sat Jun 08, 2013 12:53 pm    Post subject: Reply with quote

John, please can you explain what exactly you are trying to do in the routine sub_resize_big (num_new) ?

Gratefully appreciated...

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



Joined: 16 Feb 2006
Posts: 2621
Location: Sydney

PostPosted: Mon Jun 10, 2013 12:53 pm    Post subject: Reply with quote

Christy,

In sub_resize_big, I was trying to demonstrate resizing a large array in Win_32, but I think it was not a good solution. I was trying to retain the address of the old large array, to obtain the information from it. However, the problem is that when releasing the large array, the OS releases the memory from this process and so it is no longer available.

If you compile with no options you should get 3gb memory on Win7_64. /debug with a recent version of FTN95 also gives 3gb.

It is a good extension of memory capacity.

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



Joined: 08 Apr 2011
Posts: 155

PostPosted: Mon Jun 10, 2013 2:29 pm    Post subject: Reply with quote

Thanks John. Ok, but with the help of the temporary array, you ahve achieved the resizing in
Code:
sub_resize (num_new)


Right?

This does not seem a burden except an (just 'one' through the whole process) additioanl array-Isn't it?

You said:

Quote:
In sub_resize_big, I was trying to demonstrate resizing a large array in Win_32, but I think it was not a good solution. I was trying to retain the address of the old large array, to obtain the information from it. However, the problem is that when releasing the large array, the OS releases the memory from this process and so it is no longer available.


Ok, that is whay you say it is not a good solution

Quote:

If you compile with no options you should get 3gb memory on Win7_64. /debug with a recent version of FTN95 also gives 3gb.


I did not get thsi sentence- is this something different from what you said above?

Christy
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  Next
Page 2 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