Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28597 Discussions

define and use an apriori unknown number of allocatable arrays

bassano
Beginner
373 Views

Dear Steve, dear all,

I would like to define an apriori unspecified number of allocatable arrays having the same number of dimensions but different size and using all of them more than once in an iterative cycle. The number N of arrays depends on the problem at hand. So it can be specified as an input data or in a parameter declaration. The solutions I conceived seem to be quite unelegant and unefficient from several view points.

1. My first problem is how to allocate the N arrays. I could:

define a large number M > N of alloactable arrays and allocate only N arrays:

Allocatable a1( : , : , : ,), a2( : , : , : ,),, aN( : , : , : ,), , aM( : , : , : ,)

Read dimensions of a1,.,aN

Allocate a1( : , : , : ,), a2( : , : , : ,),, aN( : , : , : ,)

or

Allocate (a(1:N, min_dim_1 : max_dim_1, min_dim_ 2 : max_dim_2, ) )

but this last solution is impractical since could lead to large unused memory allocation for arrays of different number of components in each dimension.

2. My second problem is how to call the N arrays in the iterative cycle in the case of multiple arrays allocation (a1, ..,aN)

do iter = 1, 1000

do k = 1,N

allocate( a( : , : , : ,)) !use same dimensions of ak

select case (k)

case(1);a=a1

case(2);a=a2

....

case(M);a=aM

end select

!use a

deallocate(a)

enddo

do k = 1,N

as above

enddo

enddo

I could define a single array with an additional dimension ranging from 1 to N, but I should allocate (a(1 : N, min_dim_1 : max_dim_1, min_dim_2 : max_dim_2, ) which is also impractical since could lead to large memory allocation for arrays of different number of components in each dimension.

3. I could create automatically an include file with N declarations and recompile each timeb (but should be forced to recompile a thing that I would avoid)

I hope someone could help me

Thanks in advance

0 Kudos
3 Replies
Steven_L_Intel1
Employee
373 Views

Derived types are your friend. Something like this:

type array_type
real, allocatable :: a(:)
end type array_type

type(array_type), allocatable :: arrays(:)

! Allocate N arrays
allocate (arrays(n))

! Allocate each of the arrays to a different length
do i=1,size(array)
allocate (arrays(i)%a(i*2))
end do

This requires a Fortran 2003 feature which most F95+ compilers support.

0 Kudos
lars_mossberg
Beginner
373 Views

Hi!

Is it something like this you are after:

PROGRAM

example

IMPLICIT NONE

TYPE alloc_type

REAL, ALLOCATABLE, DIMENSION(:,:,:) :: a

END TYPE alloc_type

TYPE (alloc_type), ALLOCATABLE, DIMENSION(:) :: arr

INTEGER :: i, iter

ALLOCATE (arr(1:2))

ALLOCATE (arr(1)%a(2,3,4))

ALLOCATE (arr(2)%a(3,4,5))

DO iter=1, 1000

DO i=1, SIZE(arr)

CALL use_arr (arr(i)%a)

END DO

IF (iter>10) THEN

EXIT ! ---------------->

ENDIF

END DO

CONTAINS

SUBROUTINE use_arr (a)

REAL, DIMENSION(:,:,:), INTENT(IN) :: a

WRITE (*, *) SHAPE(a)

END SUBROUTINE use_arr

END

PROGRAM example

I have thus made a type, "alloc_type"that consists of an allocatable array and then declared an allocatable array of that type, "arr". Allocation, as you can see, occurs in two steps. First on the "alloc_type" array "arr" and then on its component, "a", for each array element of "arr".

Best wishes

Lars M

0 Kudos
jimdempseyatthecove
Honored Contributor III
373 Views

The following is what Lars wrote, but it also illustrates the use of pointer types as well.

I did not illustrate all the advantages of using pointers, I will leave that discovery up to you. One advantage is it makes things easire if you desire to have the array of arrays grow/shrink during runtime.

program AllocatableArrays

implicit none

interface

integer function iSomeNumber()

end function iSomeNumber

end interface

interface

subroutine foo(A)

implicit none

real :: A(:,:,:,:)

end subroutine foo

end interface

! Variables

! -------------- method 1 -----------

! Body of AllocatableArrays

type YourArrayTemplate

real, allocatable :: A(:,:,:,:)

end type YourArrayTemplate

! Array Of Arrays

type(YourArrayTemplate), allocatable :: ArrayOfArrays(:)

! --------------- end method 1 ---------------

! --------------- method 2 ----------

! Or use pointer to Array Of Arrays

type YourArrayTemplateViaPointer

real, pointer :: A(:,:,:,:)

end type YourArrayTemplateViaPointer

type(YourArrayTemplate), pointer :: ArrayOfArraysViaPointer(:)

! --------------- end method 2 ----------

integer :: NumberOfArrays

< P>
integer :: Dim1, Dim2, Dim3, Dim4

integer :: i

! Obtain number of arrays (read from file/console redirected)

NumberOfArrays = iSomeNumber()

! Allocate ArrayOfArrays

allocate(ArrayOfArrays(NumberOfArrays))

do i=1,NumberOfArrays

! read dims

Dim1 = iSomeNumber()

Dim2 = iSomeNumber()

Dim3 = iSomeNumber()

Dim4 = iSomeNumber()

! allocate

allocate(ArrayOfArrays(i).A(Dim1,Dim2,Dim3,Dim4))

! populate

! ...

end do

! Obtain number of arrays (read from file/console redirected)

NumberOfArrays = iSomeNumber()

! Allocate ArrayOfArraysViaPointer

allocate(ArrayOfArraysViaPointer(NumberOfArrays))

do i=1,NumberOfArrays

! read dims

Dim1 = iSomeNumber()

Dim2 = iSomeNumber()

Dim3 = iSomeNumber()

Dim4 = iSomeNumber()

! allocate

allocate(ArrayOfArraysViaPointer(i).A(Dim1,Dim2,Dim3,Dim4))

! populate

! ...

end do

! sample allocatable

do i=1,size(ArrayOfArrays)

call foo(ArrayOfArrays(i).A)

end do

! sample via pointers (same syntax)

do i=1,size(ArrayOfArraysViaPointer)

call foo(ArrayOfArraysViaPointer(i).A)

end do

write(*,*) "Done"

< B>end program AllocatableArrays

integer function iSomeNumber()

implicit none

real :: aRandomNumber

aRandomNumber = 0.0

do while(aRandomNumber .lt. 2.)

call random_number(aRandomNumber)

aRandomNumber = aRandomNumber * 6.

end do

iSomeNumber = aRandomNumber

end function iSomeNumber

subroutine foo(A)

implicit none

real :: A(:,:,:,:)

integer :: Dims(4)

Dims =

shape(A)

write(*,*) Dims

end subroutine foo

0 Kudos
Reply