2

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.


  PROGRAM 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 at 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.

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.

  • 1
    Your code is **NOT** FORTRAN 77. Not even close. It is absolutely incompatible with FORTRAN 77. There is nothing like `allocatable` or `::` or `type` in FORTRAN 77. – Vladimir F Героям слава Mar 01 '17 at 11:29
  • ok.................. – Pankaj Pandya Mar 01 '17 at 11:54
  • ok..................so can you compile the program with your corrections in it.... and post your suggestion........... i dont care...... till this particular small program runs in f90 or f77........... – Pankaj Pandya Mar 01 '17 at 12:04
  • 1
    *I want to stay away from common blocks or modules* But modules are precisely what you should want in this situation. By the way, the type `ss` declared in the subroutine is not the type `ss` declared in the program. – High Performance Mark Mar 01 '17 at 12:33

1 Answers1

1

You can do what you want to do without modules, but that doesn't mean that you should. But first, let's look at the thing the compiler is complaining about.

Consider the derived type definition

type t
  real x(i)
end type

This type has an array component x (with bound i); it is an explicit-shape array. In such a case the bound i must be a specification expression. Here, that essentially means that i must be a constant.

In the subroutine pass_arg of the question, the bounds of the component are not constants, but dummy arguments. This is why the compiler complains.

To solve this, you should again make the component in the type of the subroutine allocatable. You then needn't even pass a and b: the bounds will be available from the array's allocation status.


Now, you say you want to do this without using modules. With the correction above that is what you can do. I strongly advise that you don't, however: this works only because the derived type is a sequence type. Using a sequence type is limiting and error-prone:

  • sequence types are limited in what their components may be, and cannot have type-bound procedures;
  • you must repeat exactly the definition of the type in each place it is used;
  • you cannot have private components in the type.

Much better to create a module and define once the derived type (and make it a non-sequence type).


A second option for the example of the question is to used a parameterized derived type:

type ss(a,b)
  type, len :: a, b
  ! Not a sequence type, define once in a module
  double precision, dimension(a,b) :: s1
end type

In the main program this can be used like (using named constants for clarity)

use mod_with_type_ss
implicit none
integer, parameter :: a=10, b=10
type(ss(a,b)) ss_(a,b)
call pass_arg(ss)
end

The subroutine could then be like

subroutine pass_arg(ss_)
  use mod_with_type_ss
  type(ss(*,*)), intent(in) :: ss_  ! The type parameters are assumed
  ...
end subroutine
francescalus
  • 30,576
  • 16
  • 61
  • 96