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

TYPE vars with ALLOCATABLE attribute

Key__Samuel
Beginner
266 Views

(1) My TYPE declaration:

      TYPE :: eflow_data_type
        INTEGER(ITYPE)              :: SegID ! Boundary segment ID
        INTEGER(ITYPE)              :: Mel   ! Solid element w/w segment is associated
        INTEGER(ITYPE)              :: Type  ! Element_Type_XXXX, see shared_common_data.f
        INTEGER(ITYPE)              :: KNP   ! Count of nodes in INP(1:MXEFN)
        INTEGER(ITYPE), DIMENSION(:), ALLOCATABLE :: INP! El node subset, 1 .le. INP(*) .le. MXEFN
      END TYPE

      TYPE (eflow_data_type), DIMENSION(:), ALLOCATABLE, SAVE :: EFLOW_DATA

(2) IVF Manual:

ALLOCATE ([type:] object[(s-spec)] ...

(3) My ALLOCATE statement:

        IF (NUMED .GT. 0) THEN

          MXEFN = MAX(4,MXPGN)
          ALLOCATE ( eflow_data_type::INP(MXEFN), STAT=IALLOC_FLAG )
          CALL REPORT_ALLOCATION_EVENT (IALLOC_FLAG,'EFLOW_DATA:INP(1:MXEFN)',MXEFN)

          ALLOCATE ( EFLOW_DATA(1:NUMED), STAT=IALLOC_FLAG )
          CALL REPORT_ALLOCATION_EVENT (IALLOC_FLAG,'EFLOW_DATA(1:NUMED)',NUMED)

          EFLOW_DATA(:) = eflow_data_type (0,0,0,0,(/(0,i=1,MXEFN)/))
        ENDIF

(4) ifort error message:

error #8235: If type specification appears, the type and kind type parameters of each object being allocated must be the same the same as type and kind type of the type specification. [INP]

Question: What am I overlooking from the User and Reference Guide for the Fortran Compiler 14.0 specification???

Question: Do I have the ALLOCATE (...) commands in the wrong execution order???

Question: Should I stuff both the mother and the child into one ALLOCATE ( EFLOW_DATA(NUMED)%INP(MXEFN),

 

 

0 Kudos
1 Solution
IanH
Honored Contributor II
266 Views

You need to allocated the parent object before you can allocate the subobject corresponding to the allocatable component.  When allocating the subobject that corresponds to an allocatable component, you designate the component using the typical part reference syntax `parent % component`.  The type spec syntax you have used is only useful when you are allocating polymorphic objects, that might have a dynamic type different from their declared type.

! Allocate the parent object (which is an array).
ALLOCATE ( EFLOW_DATA(1:NUMED), STAT=... )

! Allocate a component of an element of the parent array.
ALLOCATE( EFLOW_DATA(some_index) % INP( MXEFN ), STAT=... )

For the last statement above, to allocate every INP component of each element of EFLOW_DATA, you would have that last ALLOCATE statement in a loop where some_index goes from 1 to NUMED.

However, if the compiler is following Fortran 2003 semantics (this requires the /standard-semantics command line option), simple assignment is often all you need to allocate something.  After allocating the EFLOW_DATA array as per the first statement above, you could set the value of an element of that array (or all elements if you remove the `(some_index)`) with something like:

! Set value of all components (includes allocating the INP component) of one element.
EFLOW_DATA(some_index) = eflow_data_type(0, 0, 0, 0, [(0,i=1 MXEFN)])

You could even take further, and allocate and set the value of the whole EFLOW_DATA array in one step.  Note in the following that the left hand side of the assignment has no array subscripts - we are assigning to the entire allocatable array object, and not a section of the array.

! Allocate and set value of the whole array in one go.
EFLOW_DATA = [(eflow_data_type(0, 0, 0, 0, [(0,i=1 MXEFN)]), j = 1, NUMED)]

(The compiler may create temporaries in memory to hold the value of the array constructor on the right hand side of the above assignment statements.  If the value being assigned requires a large amount of storage space, this can create problems - in which case you are better off with the explicit allocation and separate setting of value.)

With allocate on assignment you don't get access to a STAT error result - if the allocation fails for any reason, the program terminates.

~~

(This sort of situation, where every component has the same allocation status, is better handled through length type parameters.)

View solution in original post

0 Kudos
1 Reply
IanH
Honored Contributor II
267 Views

You need to allocated the parent object before you can allocate the subobject corresponding to the allocatable component.  When allocating the subobject that corresponds to an allocatable component, you designate the component using the typical part reference syntax `parent % component`.  The type spec syntax you have used is only useful when you are allocating polymorphic objects, that might have a dynamic type different from their declared type.

! Allocate the parent object (which is an array).
ALLOCATE ( EFLOW_DATA(1:NUMED), STAT=... )

! Allocate a component of an element of the parent array.
ALLOCATE( EFLOW_DATA(some_index) % INP( MXEFN ), STAT=... )

For the last statement above, to allocate every INP component of each element of EFLOW_DATA, you would have that last ALLOCATE statement in a loop where some_index goes from 1 to NUMED.

However, if the compiler is following Fortran 2003 semantics (this requires the /standard-semantics command line option), simple assignment is often all you need to allocate something.  After allocating the EFLOW_DATA array as per the first statement above, you could set the value of an element of that array (or all elements if you remove the `(some_index)`) with something like:

! Set value of all components (includes allocating the INP component) of one element.
EFLOW_DATA(some_index) = eflow_data_type(0, 0, 0, 0, [(0,i=1 MXEFN)])

You could even take further, and allocate and set the value of the whole EFLOW_DATA array in one step.  Note in the following that the left hand side of the assignment has no array subscripts - we are assigning to the entire allocatable array object, and not a section of the array.

! Allocate and set value of the whole array in one go.
EFLOW_DATA = [(eflow_data_type(0, 0, 0, 0, [(0,i=1 MXEFN)]), j = 1, NUMED)]

(The compiler may create temporaries in memory to hold the value of the array constructor on the right hand side of the above assignment statements.  If the value being assigned requires a large amount of storage space, this can create problems - in which case you are better off with the explicit allocation and separate setting of value.)

With allocate on assignment you don't get access to a STAT error result - if the allocation fails for any reason, the program terminates.

~~

(This sort of situation, where every component has the same allocation status, is better handled through length type parameters.)

0 Kudos
Reply