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

Passing a user defined data type allocatable array

pankaj_p_
Novice
707 Views

I can define a user defined data type with allocatable array as its data type. Allocation works perfectly while we are still in the same subroutine. But i don't know how to pass this type of user defined data type as a subroutine argument. Intel compiler shows the error # 6530:

"Error 1 error #6530: The array spec for this component must be of explicit shape and each bound must be an initialization expression."

The code has been shared below to show the error. It is written in FORTRAN 77. I am working in FORTRAN 77, as i will have to append this code in user subroutine of abaqus that accepts only FORTRAN 77 files.

-------------------------

SUBROUTINE DERIVED_DATA_TYPE_CHECK

      IMPLICIT NONE

      INTEGER :: I,J,A,B
      TYPE SS
          SEQUENCE
          DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: S1
      END TYPE SS

      TYPE (SS),DIMENSION(:,:),ALLOCATABLE :: SS_

      A=10
      B=10

      ALLOCATE (SS_(A,B))
      ! ALLOCATING THE VARIABLE S1 DIMENSIONS
      ! EVERY ALLOCATABLE VARIABLE HAS THE SAME SIZE AS
      ! THE TOTAL NUMBER OF STRUCTURE (TYPE)
      DO I = 1,A
          DO J = 1,B
              ALLOCATE(SS_(I,J)%S1(A,B))
          ENDDO
      ENDDO

      CALL PASS_ARG(SS_,A,B)

      END



      SUBROUTINE PASS_ARG(SS_,A,B)

      IMPLICIT NONE

      INTEGER :: A,B

      TYPE SS
          SEQUENCE
          DOUBLE PRECISION, DIMENSION(A,B) :: S1
      END TYPE SS

      TYPE (SS), DIMENSION (A,B) :: SS_

      END

 

----------------------------------

The program on compilation gives the error as shown below:

 

Error 2 error #6530: The array spec for this component must be of explicit shape and each bound must be an initialization expression. [S1]

There must be a way to solve this problem. I want to stay away from common blocks or modules. Anyway i cant use module in FORTRAN 77.

In order to avoid this error, I had used allocatable variables in main program as well as called subroutine. Program is then compiled, but on execution, it show the error "that allocation has been done more than once".

At last i think i will have to use some global constants..... i guess. Thanks

0 Kudos
3 Replies
mecej4
Honored Contributor III
707 Views

If you have more than one instance of a type declaration, those types are not considered the same, even if the multiple declarations match one another exactly.

When you call a subroutine with certain types of actual arguments, you need to provide an explicit interface to the subroutine.

It is incorrect to conflate "fixed form source" with "Fortran 77". Standard Fortran-77 certainly did not have modules, derived types and modules.

      MODULE SS_MOD
      TYPE SS
          SEQUENCE
          DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: S1
      END TYPE SS
      END MODULE

      MODULE PASS_ARG_INT
         INTERFACE
            SUBROUTINE PASS_ARG(SS_,A,B)
               USE SS_MOD
               IMPLICIT NONE
               INTEGER :: A, B
               TYPE(SS), dimension(:,:) :: SS_
            END SUBROUTINE
         END INTERFACE
      END MODULE

      SUBROUTINE DERIVED_DATA_TYPE_CHECK
      USE SS_MOD
      USE PASS_ARG_INT
      IMPLICIT NONE

      INTEGER :: I,J,A,B
      TYPE (SS),DIMENSION(:,:),ALLOCATABLE :: SS_

      A=10
      B=10

      ALLOCATE (SS_(A,B))
      ! ALLOCATING THE VARIABLE S1 DIMENSIONS
      ! EVERY ALLOCATABLE VARIABLE HAS THE SAME SIZE AS
      ! THE TOTAL NUMBER OF STRUCTURE (TYPE)
      DO I = 1,A
          DO J = 1,B
              ALLOCATE(SS_(I,J)%S1(A,B))
          ENDDO
      ENDDO

      CALL PASS_ARG(SS_,A,B)

      END

      SUBROUTINE PASS_ARG(SS_,A,B)
      USE SS_MOD
      IMPLICIT NONE
      INTEGER :: A,B
      TYPE (SS), DIMENSION (A,B) :: SS_
      END

 

0 Kudos
pankaj_p_
Novice
707 Views

 

0 Kudos
JVanB
Valued Contributor II
707 Views

Actually, you can get by with separate but identical definitions of a derived type provided the type has the SEQUENCE or BIND attribute. Thus the syntax in the original post would be OK except for the fact that the declaration of type(SS) in subroutine PASS_ARG is inconsistent with that of type(SS) in subroutine DERIVED_TYPE_DATA_CHECK not to mention being syntactically incorrect. Just copy the derived type definition for the latter subroutine to the former and everything should fly.

BTW, if component S1 in all elements of an array of type(SS) are to be allocated and the same shape, you might be better served by making SS a parameterized derived type although that definitely would require a module to propagate the derived type definition to both subroutines.

 

0 Kudos
Reply