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.
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)
!