Canadianphysics216
Canadianphysics216

Reputation: 41

Can I pass a variable to a derived type such that each instance of my derived type could have arrays of different lengths?

What is the best way to organize 11 similar but varying size arrays in a program, without the allocatable property?

I'm imagining something like this:

TYPE MyType(i)
   integer, intent(in) :: i

   integer, dimension(i,i) :: A
   integer, dimension(2*i,i) :: B
   integer, dimension(i,2*i) :: C

end type MyType

Then in the main program I can declare something like this:

type(mytype), dimension(N) :: Array

Wherein the i'th element of 'Array' has access to three arrays A, B, and C and each of these three arrays have different sizes.

The problem I have currently is I am solving a QM problem and I have 11 different arrays that vary in size but all depend on the same parameter (as the size A, B and C all depend on i). The actually values of these arrays don't change either.

My program looks at different kinds of systems, each with their own A, B and C (just to keep the analogy going) and in each system A, B and C have a unique size.

If I knew I was looking at 6 different kinds of systems, I'd need 6 different copies of A, B and C.

Currently, A, B and C are not part of a derived type but instead are allocatable and recalculated at each iteration. This calculation takes upwards of a tenth of a second for the larger systems. But I average my results ~100,000 times which means this could offer some serious time savings. In addition, memory is not something I lack.

I tried calculating these arrays in another program and writing them to file and reading them when needed but unfortunately this was not faster than recalculating at the same time.

Note: Here is what my actual arrays look like:

  integer, dimension(:,:), allocatable :: fock_states      
  integer, dimension(:,:), allocatable :: PES_down, PES_up  
  integer, dimension(:,:), allocatable :: IPES_down, IPES_up 
  integer, dimension(:,:), allocatable :: phase_PES_down, phase_PES_up    
  integer, dimension(:,:), allocatable :: phase_IPES_down, phase_IPES_up 
  integer, dimension(:,:), allocatable :: msize       
  integer, dimension(:,:), allocatable :: mblock      

Each array is a different size for each system.

Edit:

So what I really need is N copies of the arrays in the list just above this edit. The arrays belonging to the i'th copy have size that scales with i (e.g. PES_down has dimension (i,4**i)). As I understand it, this means that I need N different declarations of variables with type 'MyType'. This would normally be ok but the issue is that N is defined at compile time but can change between runs.

N does have a defined maximum but it seems like a lot of wasted memory when I know I won't be using the arrays.

Upvotes: 1

Views: 224

Answers (2)

Rodrigo Rodrigues
Rodrigo Rodrigues

Reputation: 8546

(Relate to this answer for a more detailed explanation).

As @roygvib said in his comment, yes, using parameterized derived types in this case is not only possible, it is a perfect match. This is one of the main problem-cases PDT aims to solve.

type :: MyType(i)
  integer, len :: i
  integer, dimension(i,i) :: A
  integer, dimension(2*i,i) :: B
  integer, dimension(i,2*i) :: C
  ! (...)
end type

Then, in the main program, you would declare your object like this (where i is the known length parameter for the current kind of system):

type(mytype(i)), dimension(N) :: Array

But first, check the availability of this feature in your compiler.

Upvotes: 2

roygvib
roygvib

Reputation: 7385

I guess it would be most straightforward to use a derived type containing A, B, and C with the size variable i and allocate them for each i using some initialization routine (here, MyType_init()).

module mytype_mod
    implicit none

    type MyType
        integer :: i
        integer, dimension(:,:), allocatable :: A, B, C
    end type
contains

    subroutine MyType_init( this, i )
        type(MyType), intent(inout) :: this
        integer, intent(in) :: i

        allocate( this % A( i,   i   ), &
                  this % B( 2*i, i   ), &
                  this % C( i,   2*i ) )

        this % A = 0  !! initial values
        this % B = 0
        this % C = 0
    end subroutine

end module

program main
    use mytype_mod
    implicit none
    integer, parameter :: N = 2
    type(MyType) :: array( N )
    integer i

    do i = 1, N
        call MyType_init( array( i ), i )

        array( i ) % A(:,:) = i * 10   !! dummy data for check
        array( i ) % B(:,:) = i * 20
        array( i ) % C(:,:) = i * 30
    enddo

    do i = 1, N
        print *
        print *, "i = ", i
        print *, "    A = ", array( i ) % A(:,:)
        print *, "    B = ", array( i ) % B(:,:)
        print *, "    C = ", array( i ) % C(:,:)
    enddo

end program

Result (with gfortran 8.1):

 i =            1
     A =           10
     B =           20          20
     C =           30          30

 i =            2
     A =           20          20          20          20
     B =           40          40          40          40          40          40          40          40
     C =           60          60          60          60          60          60          60          60

The array(:) in the main program can be allocatable, such that

type(MyType), allocatable :: array(:)

N = 6
allocate( array( N ) )

which may be useful when N is read in from an input file. Further, we can create a type-bound procedure from MyType_init() by changing the lines with (*) below (to use an OO style).

module mytype_m
    implicit none

    type MyType
        integer :: i
        integer, dimension(:,:), allocatable :: A, B, C
    contains
        procedure :: init => MyType_init   ! (*) a type-bound procedure
    end type

contains

    subroutine MyType_init( this, i )
        class(MyType), intent(inout) :: this   ! (*) use "class" instead of "type"
        ...
    end subroutine
end module

program main
    ...
    do i = 1, N
        call array( i ) % init( i )  ! (*) use a type-bound procedure
        ...
    enddo
    ...
end program

Upvotes: 1

Related Questions