 |
forums.silverfrost.com Welcome to the Silverfrost forums
|
View previous topic :: View next topic |
Author |
Message |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Thu Apr 04, 2013 8:50 am Post subject: Allocate/Deallocate |
|
|
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 |
|
Back to top |
|
 |
davidb
Joined: 17 Jul 2009 Posts: 560 Location: UK
|
Posted: Thu Apr 04, 2013 9:10 am Post subject: |
|
|
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.
Code: |
double precision, SAVE :: BIG_ARRAY(1000000)
|
_________________ Programmer in: Fortran 77/95/2003/2008, C, C++ (& OpenMP), java, Python, Perl |
|
Back to top |
|
 |
Kenneth_Smith
Joined: 18 May 2012 Posts: 815 Location: Hamilton, Lanarkshire, Scotland.
|
Posted: Thu Apr 04, 2013 9:31 am Post subject: |
|
|
This little snipped of code might be of help. Ken
Code: |
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
|
|
|
Back to top |
|
 |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Thu Apr 04, 2013 11:25 am Post subject: |
|
|
Does that mean defining the arrays using ALLOCATABLE in module makes them as global variables? |
|
Back to top |
|
 |
JohnCampbell
Joined: 16 Feb 2006 Posts: 2615 Location: Sydney
|
Posted: Thu Apr 04, 2013 1:22 pm Post subject: |
|
|
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
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
!
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
|
|
|
Back to top |
|
 |
JohnCampbell
Joined: 16 Feb 2006 Posts: 2615 Location: Sydney
|
Posted: Thu Apr 04, 2013 1:36 pm Post subject: |
|
|
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.
Code: | 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
|
|
|
Back to top |
|
 |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Thu Apr 04, 2013 2:48 pm Post subject: |
|
|
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 |
|
Back to top |
|
 |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Thu Apr 04, 2013 3:08 pm Post subject: |
|
|
Code: | 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
Code: | #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 |
|
Back to top |
|
 |
jalih
Joined: 30 Jul 2012 Posts: 196
|
Posted: Thu Apr 04, 2013 6:28 pm Post subject: Re: |
|
|
christyleomin wrote: |
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. |
|
Back to top |
|
 |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Thu Apr 04, 2013 7:32 pm Post subject: |
|
|
No-I need to allocate in FORTTRAN only for some pther reasons.
Any tips on this ?Thanks |
|
Back to top |
|
 |
jalih
Joined: 30 Jul 2012 Posts: 196
|
Posted: Fri Apr 05, 2013 8:16 am Post subject: Re: |
|
|
christyleomin wrote: | 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:
Code: |
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
|
|
|
Back to top |
|
 |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Sat Apr 06, 2013 6:55 pm Post subject: For John and others |
|
|
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? |
|
Back to top |
|
 |
jalih
Joined: 30 Jul 2012 Posts: 196
|
Posted: Sat Apr 06, 2013 8:18 pm Post subject: Re: For John and others |
|
|
christyleomin wrote: | 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. |
|
Back to top |
|
 |
christyleomin
Joined: 08 Apr 2011 Posts: 155
|
Posted: Sun Apr 07, 2013 11:31 pm Post subject: |
|
|
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? |
|
Back to top |
|
 |
JohnCampbell
Joined: 16 Feb 2006 Posts: 2615 Location: Sydney
|
Posted: Mon Apr 08, 2013 4:46 am Post subject: |
|
|
The following is a simple example of taking a copy and then resizing, releasing memory for later use. Code: | MODULE ARRAY_STORAGE
integer*4, parameter :: million = 1000000
integer*4 :: num = 150*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 (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_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
|
|
|
Back to top |
|
 |
|
|
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
|