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

Array of Parameterized derived data types with different length type parameters

ScottBoyce
Novice
929 Views

I have been unable to find any documentation, so it may not be possible, about being able to make an array of parameterized derived data types with different length parameters. I have done some simple tests, but I get strange compiler results where multiple allocations seem to overwrite the preceding one, rather than raise an error.

 

TYPE MAT_TYPE(N)
     INTEGER,LEN::N
     REAL,DIMENSION(N    )::X
     REAL,DIMENSION(N,N  )::A
     REAL,DIMENSION(N,2*N)::B
END TYPE

TYPE ARRAY_OF_MAT
   TYPE(MAT_TYPE(:)),DIMENSION(:),ALLOCATABLE:: MAT
END TYPE

TYPE (ARRAY_OF_MAT) :: GRP

 

In the above example code, I'd like to be able to allocate MAT within GRP such that each has a different length parameter as follows:

 

!FIRST ALLOCATE MAIN DIMENSION --this sometimes causes a compiler error
ALLOCATE(TYPE(MAT_TYPE(:)::GRP%MAT(10))
!
!NEXT ALLOCATE EACH OF THE PARAMETERIZED DIMENSIONS --these work without the preceding allocation

ALLOCATE(TYPE(MAT_TYPE(50)::GRP%MAT(1))

ALLOCATE(TYPE(MAT_TYPE(80)::GRP%MAT(2))

ALLOCATE(TYPE(MAT_TYPE(40)::GRP%MAT(3))

 

That way I can have as data type of paramterized data types with the correct length factors for different array groups and I can have loops similar to the following:

 

DO I=1, 10
  !DO STUFF WITH 
  GRP%MAT(I)%X
  GRP%MAT(I)%A
  GRP%MAT(I)%B
END DO

 

The way I have my code currently is as follows:

 

TYPE MAT_TYPE
     INTEGER::N
     REAL,ALLOCATABLE,DIMENSION(:  )::X
     REAL,ALLOCATABLE,DIMENSION(:,:)::A
     REAL,ALLOCATABLE,DIMENSION(:,:)::B
END TYPE

TYPE ARRAY_OF_MAT
   TYPE(MAT_TYPE(:)),DIMENSION(:),ALLOCATABLE:: MAT
END TYPE

ALLOCATE(GRP%MAT(10))

DO I=1, 10
  ! THE VALUE OF "N" CHANGES FOR EACH LOOP TO REQUIRED VALUE (ie N=50, then 80, then 40, then ...)
  GRP%MAT(I)%N=N

  ALLOCATE(GRP%MAT(I)%X(N    ))
  ALLOCATE(GRP%MAT(I)%A(N,  N))
  ALLOCATE(GRP%MAT(I)%B(N,2*N))
END DO

 

The only way I can think of doing this with parameterized data types is with a linked list, but that to me seems like it would effect speed. (These arrays are used in a numerical model solver for different grids).


What would be the best way to handle this or should I stick with allocatable (non-parameterized data types) arrays as the second example shows.

Lastly is there any speed benefit beyond cleaner code with using parameterized data types that are allocatable versus a standard allocatable array within the data type. At least for several of my tests using the intel compiler I get strange allocatation results. For example the following causes very strange behavior.

 

ALLOCATE(TYPE(MAT_TYPE(50)::GRP%MAT(1))

ALLOCATE(TYPE(MAT_TYPE(80)::GRP%MAT(2))

ALLOCATE(TYPE(MAT_TYPE(40)::GRP%MAT(3))

 

In each case, it seems like the next allocation over writes the old one, thus GRP%MAT becomes dimension of length 1 with length parameter type 50,

then magically becomes dimension of length 2 with length parameter type 80 (ie GRP%MAT(1) and GRP%MAT(2) both have length parameters of 80 now),

and then the third statement changes it all to a dimension of length 3 with length parameter type 40.

 

Thanks for all your help and comments.

 

0 Kudos
3 Replies
IanH
Honored Contributor III
929 Views

I may not have completely understood what you are trying to do, but some notes:

  • All elements in an array (whether that be a "top level" array or an array that is a component of an object of derived type) have the same type parameters (whether kind or length).  Objects of derived type in an array may have allocatable components that can vary in parameters from element to element in the array.
  • The syntax for designating the type and parameters of the thing to allocate in an allocate statement is a type-spec, not a declaration-type-spec, that is, it is just the type name [and type parameters], there's no leading TYPE or CLASS keyword.  There is a mismatch in parentheses in some of your code - so perhaps the use of the TYPE/CLASS keyword is just a transcription error.
  • When you allocate an object, you must provide values for all deferred attributes, such as length type parameters and array dimensions.

Recasting those points, your code fragments appear to show a scalar object of type ARRAY_OF_MAT.  That scalar object has a single allocatable component, of type MAT_TYPE with a deferred length parameter.  You have one top level scalar object, you have one component - you have only one array subobject of type MAT_TYPE (designated GRP%MAT) - and all elements in that subobject array must have the same type parameters.

Should GRP be an array?  If it was, then you could allocate GRP(1)%MAT to have a type parameter of 10, GRP(2)%MAT to be 20, etc...Otherwise you need another component level in your type structure, along the lines of:

TYPE MAT_TYPE(N)
     INTEGER,LEN::N
     REAL,DIMENSION(N    )::X
     REAL,DIMENSION(N,N  )::A
     REAL,DIMENSION(N,2*N)::B
END TYPE

TYPE MAT_ELEMENT
  TYPE(MAT_TYPE), ALLOCATABLE :: ITEM
END TYPE MAT_ELEMENT

TYPE ARRAY_OF_MAT
   TYPE(MAT_ELEMENT),DIMENSION(:),ALLOCATABLE :: MAT
END TYPE

TYPE (ARRAY_OF_MAT) :: GRP

INTEGER :: i

ALLOCATE(GRP%MAT(10))
DO i = 1, SIZE(GRP%MAT)
  ALLOCATE(MAT_TYPE(I) :: GRP%MAT(I)%ITEM)
  GRP%MAT(i)%ITEM%X = ...
  GRP%MAT(i)%ITEM%A = ...
  GRP%MAT(i)%ITEM%B = ...
END DO

 

0 Kudos
ScottBoyce
Novice
929 Views

I wish you could edit posts. I wrote that code within that example to illustrate my problem. The parentheses mismatch is just a typo from writing in the fortran editor (wish I could fix stuff after I hit submit, always seems to get me into trouble when I try and write a simpler example compared to what I am doing).

 

Thanks a ton for your explanation. That was what I was afraid of where I can not have changing properties within an array of data types. My main reason for not going with another datatype (ie "ITEM") is mostly to keep from adding to many parts to the Data Type. I may try to use the ASSOCIATE construct to simplify blocks of code, but I have yet to use that feature of fortran.

 

 

0 Kudos
IanH
Honored Contributor III
929 Views

Herewith some rambling... ASSOCIATE may help, and I've certainly used it to overcome excessive depth of part references.  That said, depending on circumstances it may also be better to split out the relevant piece of code into a separate procedure, that operates on subobjects of the GRP type via argument association.  If you use associate to do this, then you have a procedure that operates on both high level objects (GRP) and low level detail - a mix of abstraction levels, which can have implications for the ability to document, re-use and test code, if you are into that sort of nonsense.

I think a reasonable guideline (not a rule) is for a particular procedure to only operate on the direct sub-objects of its arguments and local variables - so for a variable reference you only ever have one % in a designator.  The operation on subobjects may be through a binding, so in terms of syntax you might have two `%`'s in a procedure designator.  Consequently - I would be inclined to factor out the do loop in the code in my reply in #2.  But perhaps I just like typing too much.

I like the use of type parameters in this situation because the relationship between the components of the MAT_TYPE type are explicitly spelled out in the code defining the type, and you can only ever have a single specification of the length information for an object.  It is relatively early days for implementation of derived type parameters for ifort, so I wouldn't be counting on better/faster code generation arising from that explicit statement of the relationship between components, but that should come with time.

0 Kudos
Reply