Silverfrost Forums

Welcome to our forums

Allocate/Deallocate

4 Apr 2013 7:50 #11961

I craete ararys in FORTRAN using ALLOCATE.

  1. Do these arrays created using ALLOCATE act as 'global variables'.

  2. I need really huge arrays (I know the size of these arrays prior to creating them)- 6- 10 million.Is ALLOCATE Right ways to create these?

Christy

4 Apr 2013 8:10 #11962

Allocate creates arrays on the heap. They are not global variables.

You can create very large arrays using Allocate, but if you want really big ones you may need to use the SAVE attribute, like the code below. This causes the compiler to put the array in static storage.

double precision, SAVE :: BIG_ARRAY(1000000)
4 Apr 2013 8:31 #11964

This little snipped of code might be of help. Ken

      MODULE ARRAY_STORAGE
      IMPLICIT NONE
      REAL*8, ALLOCATABLE :: ARRAY(:)
      END MODULE ARRAY_STORAGE
!--------------------------------------------------------------------
      PROGRAM MAIN
      USE ARRAY_STORAGE
      IMPLICIT NONE
      INTEGER*4 I
      ALLOCATE (ARRAY(1:10))
      CALL SUB
      DO I=1,10
        WRITE(6,*)ARRAY(I)
      ENDDO
      DEALLOCATE (ARRAY)
      END MAIN
!--------------------------------------------------------------------
      SUBROUTINE SUB
      USE ARRAY_STORAGE
      IMPLICIT NONE
      INTEGER*4 I
      DO I=1,10
        ARRAY(I)=REAL(I,KIND=2)
      ENDDO
      RETURN
      END SUBROUTINE SUB

      
4 Apr 2013 10:25 #11967

Does that mean defining the arrays using ALLOCATABLE in module makes them as global variables?

4 Apr 2013 12:22 #11969

Using allocatable arrays in a module does effectively make them global. It is a very effective way of manageing your arrays. Allocatable arrays are not limited by the heap or stack, as they can be allocated anywhere where there is sufficient memory. With FTN95 there is up to 3.8gb of available memory, although the largest array that can be allocated is about 2gb. I have modified Kenneth's example to show how it can work for a large array. The scope of the module might be non-standard, but works very well. John

      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 
!
         call test_allocate
      call sub_allocate
         call test_allocate
      call sub_set
         call test_allocate
      call sub_print
         call test_allocate
      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
      else
         write (*,*) 'array allocated as size', size(array)*8./(2.**20),' mb'
      end if
      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'
      else
         write (*,11) 'Test ',test_count,' ARRAY is NOT allocated'
      end if
11    format (20x,a,i0,a,f0.3,a)
      end subroutine test_allocate
4 Apr 2013 12:36 #11970

Further to the last example, this example has 2 arrays and successfully uses nearly 3gb of memory. You can compile with /debug as from FTN95 Ver 6.2.

      MODULE ARRAY_STORAGE 
      integer*4, parameter :: million = 1000000
      integer*4 :: num_a = 250*million    ! 1.9gb
      integer*4 :: num_b = 150*million    ! 0.9gb
      REAL*8, ALLOCATABLE :: ARRAY(:)
      REAL*8, ALLOCATABLE :: BRRAY(:)
      integer*4 :: test_count = 0
      END MODULE ARRAY_STORAGE 
!-------------------------------------------------------------------- 
      PROGRAM MAIN 
!
         call test_allocate
      call sub_allocate
         call test_allocate
      call sub_set
         call test_allocate
      call sub_print
         call test_allocate
      call sub_deallocate
         call test_allocate
!
      END MAIN 
!-------------------------------------------------------------------- 
      subroutine sub_allocate
      USE ARRAY_STORAGE 
      integer*4 stat
!
      ALLOCATE (ARRAY(num_a),stat=stat) 
      if (stat/=0) then
         write (*,*) 'problem allocating array : stat=',stat
      else
         write (*,*) 'array allocated as size', size(array)*8./(2.**20),' mb at LOC',loc(array)
      end if
!
      ALLOCATE (BRRAY(num_b),stat=stat) 
      if (stat/=0) then
         write (*,*) 'problem allocating Brray : stat=',stat
      else
         write (*,*) 'Brray allocated as size', size(Brray)*8./(2.**20),' mb at LOC',loc(brray)
      end if
      end subroutine sub_allocate

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

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

      subroutine sub_deallocate
      USE ARRAY_STORAGE 
!
      write (*,*) 'Releasing arrays'
      DEALLOCATE (ARRAY) 
      DEALLOCATE (BRRAY) 
      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'
      else
         write (*,11) 'Test ',test_count,' ARRAY is NOT allocated'
      end if
!
      if (ALLOCATED (BRRAY) ) then
         write (*,11) 'Test ',test_count,' BRRAY is allocated as ', size(brray)*8./(2.**30),' gb'
      else
         write (*,11) 'Test ',test_count,' BRRAY is NOT allocated'
      end if
11    format (20x,a,i0,a,f0.3,a)
      end subroutine test_allocate
4 Apr 2013 1:48 #11972

John,

I am calling fortran from C++ and trying to declare module within externC.

IT is unfortumnately not allowing me to do so

Any tips?

Christy

4 Apr 2013 2:08 #11973
MODULE ARRAY_STORAGE 
      
      REAL*8, ALLOCATABLE :: ARRAY(:) 
      
      END MODULE ARRAY_STORAGE 

      
      function ffunc(n1,n2)
      
      USE ARRAY_STORAGE 

      integer ffunc
      character*256 filename
      integer n1,n2,iret
      integer*4 stat
      
      ALLOCATE (ARRAY(10),stat=stat) 
      if (stat/=0) then 
         write (*,*) 'problem allocating array : stat=',stat 
      else 
         write (*,*) 'array allocated as size', size(array)*8./(2.**20),
     +' mb at LOC',loc(array) 
      end if 

      
      ffunc = n1+n2
      
      return
      
      end
 

I am calling ffunc from C+ usign extern C

#include <iostream>
extern 'C' 
{
	//int __stdcall  ffunc(int*, int*);
	float ARRAY_STORAGE_mp_ARRAY();
	//int ffunc(int*, int*);
	
    
}

extern 'C' 
{
	//int __stdcall  ffunc(int*, int*);
	//float ARRAY_STORAGE_mp_ARRAY();
	int ffunc(int*, int*);
	
    
}

int main()
{
    int n1 = 1;
    int n2 = 2;
    
	std::cout << 'Calling from C++ to Fortran, arguments: ' << n1 << ', ' << n2 << '\\n';
    
	int r = ffunc(&n1,&n2);
    
	//std::cout << 'THe return value from fortran was ' << r << '\\n';


	

}

It does not work

4 Apr 2013 5:28 #11976

Quoted from christyleomin

I am calling fortran from C++ Christy

As your main program is written in C++, it's probably more straightforward to allocate and release data directly in a C++ program. Just pass a pointer into allocated array and it's size for the Fortran routine.

4 Apr 2013 6:32 #11977

No-I need to allocate in FORTTRAN only for some pther reasons. Any tips on this ?Thanks

5 Apr 2013 7:16 #11979

Quoted from christyleomin No-I need to allocate in FORTTRAN only for some other reasons. Any tips on this ?Thanks

Your code should work, there is probably some kind of an error in DLL-imports. I personally don't use FTN95 for writing C callable DLL's. Maybe someone with more experience with FTN95 DLL creation can help.

I tested this with GFortran and it compiles and executes fine as follows:

module array_storage
  use iso_c_binding, only: c_double 
     
  real(kind=C_DOUBLE), allocatable :: array(:)
     
end module array_storage


function ffunc(n1, n2)
  use iso_c_binding, only: c_int
  use array_storage
  integer(kind=c_int) :: ffunc
  integer(kind=c_int), value :: n1, n2
  integer :: stat
     
  allocate (array(10),stat=stat)
  if (stat/=0) then
    write (*,*) 'Problem allocating array : stat=',stat
  else
    write (*,*) 'Array allocated as size',(size(array)*8)/1024.0,' mb at location',loc(array)
  end if

  ffunc = n1+n2
     
end
6 Apr 2013 5:55 #11985

Is something like this possible:

1)I use module like in Johns example 2)Declare an array called 'my_array' in module using allocatable (it is one dimensional array) 3) USe allocate to make my_array a one dimensional 1 array with 10 elements in a sub-routine (sub-routine A) 4) In another sub-routine B I define the first five lemnts of my_array 5)Now in a sub-routine C I want to mae my_array as a 5 eleemnt arary and retain my defiend elements (That is I want to re-size my_array to 5 eleemnts instead of 10 as well as rertain the defined data)

IS this possible?

6 Apr 2013 7:18 #11986

Quoted from christyleomin Is something like this possible: 3) USe allocate to make my_array a one dimensional 1 array with 10 elements in a sub-routine (sub-routine A) 4) In another sub-routine B I define the first five lemnts of my_array 5)Now in a sub-routine C I want to mae my_array as a 5 eleemnt arary and retain my defiend elements (That is I want to re-size my_array to 5 eleemnts instead of 10 as well as rertain the defined data)

IS this possible?

You can just allocate temporary array, copy stuff from original array to temporary array, deallocate original array, reallocate original array and copy stuff back from temporary array. Don't forget to deallocate temporary array.

Other approach would be to allocate maximum sized array and keep the upper array index in a variable, so no moving of data is necessary when resizing.

7 Apr 2013 10:31 #11987

Yes. I was trying to find is there is some means of re-sizing (making it lesser size) without losing the stored data than creating temporary array

Is there any intrinsic function for copying between arrays?

8 Apr 2013 3:46 #11989

The following is a simple example of taking a copy and then resizing, releasing memory for later use. MODULE ARRAY_STORAGE integer4, parameter :: million = 1000000 integer4 :: num = 150million ! 1.9gb REAL8, ALLOCATABLE :: ARRAY(:) integer4 :: 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 (num/2) call test_allocate ! call sub_print call sub_deallocate call test_allocate ! END MAIN !-------------------------------------------------------------------- subroutine sub_allocate USE ARRAY_STORAGE integer4 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_resize (num_new)
      USE ARRAY_STORAGE 
      integer*4 num_new
!
      integer*4 n
      integer*4 stat 
      REAL*8, ALLOCATABLE :: temp_array(:) 
! 
      write (*,*) 'Resizing array' 
      num = size (array)
      n   = min (num, 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)*8./(2.**20),' mb at ', loc(temp_array) 
      end if
11    format (a,f0.3,a,b'z,zzz,zzz,zz#') 
!
      temp_array(1:n) = array(1:n)
      deallocate (array)
!
      num = num_new  
      call sub_allocate
!
      array(n+1:num) = 0                
      array(1:n) = temp_array
      deallocate (temp_array)
!
      end subroutine sub_resize

      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 
8 Apr 2013 3:57 #11990

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 MODULE ARRAY_STORAGE integer4, parameter :: million = 1000000 integer4 :: num = 250million ! 1.9gb REAL8, ALLOCATABLE :: ARRAY(:) integer4 :: 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 integer4 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 
8 Apr 2013 4:35 #11991
      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

8 Apr 2013 10:00 #11996

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

9 Apr 2013 1:20 #11997

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. integer4, allocatable :: array(:) integer4 :: num = 10 integer4 :: 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 ? integer4, allocatable :: array(:) integer4 :: num = 10000000 integer4 :: 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

9 Apr 2013 3:49 #11998

An attempt to extend the active address did not succeed. There is more to the access violation test ? integer4, allocatable :: array(:), b(:) integer4 :: num = 10000000 integer4 :: 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

Please login to reply.