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

Extended type and associated operations - different structure types?

Arjen_Markus
Honored Contributor I
341 Views

Hello, the program below is accepted by gfortran and PGI fortran, but not by Intel Fortran (versions 15, 17), unless I remove the "extends" clause.

The error message is:

Intel(R) Visual Fortran Intel(R) 64 Compiler XE for applications running on Intel(R) 64, Version 15.0.1.148 Build 20141023
Copyright (C) 1985-2014 Intel Corporation.  All rights reserved.

vs_intel.f90(64): error #6197: An assignment of different structure types is invalid.
    c = a + b
----------^
compilation aborted for vs_intel.f90 (code 1)

The program is this:

! vs_intel.f90 --
!     Problem with Intel 15 and 17 compiler
!
!     It seems the "extends(vector)" part is the problem!
!
module vectorspaces
    implicit none

    type :: vector
    end type vector

    interface operator(+)
        module procedure addition
    end interface

contains
function addition( a, b )
    class(vector), intent(in)  :: a
    class(vector), intent(in)  :: b
    class(vector), allocatable :: addition

    allocate( addition )
end function addition

end module vectorspaces

!
! Test this with an actual implementation
!
module vectors_3d
    use vectorspaces

    type, extends(vector) :: vector_3d !<== remove the "extends" clause and it is accepted
   !type :: vector_3d
        real, dimension(3) :: coords
    end type

    interface operator(+)
        module procedure add_3d
    end interface

contains
function add_3d( a, b )
    type(vector_3d), intent(in)  :: a
    type(vector_3d), intent(in)  :: b
    type(vector_3d)              :: add_3d

    add_3d%coords = a%coords + b%coords
end function add_3d

end module vectors_3d

! Test program for the vector space modules
!
program test_space
    use vectors_3d

    implicit none

    type(vector_3d)                :: a, b, c

    a = vector_3d( [1.0, 1.0, 1.0] )
    b = vector_3d( [2.0, 2.0, 2.0] )
    c = a + b
end program test_space

I do not see what is wrong with it. (I stumbled on this problem when preparing a slightly larger program) If I remove the interface block for operator(+), it is also accepted, but the error message does not hint at an ambiguity.

0 Kudos
5 Replies
FortranFan
Honored Contributor II
341 Views

Based on a quick glance, I think your code is non-conforming and all 3 compilers get it wrong because the generic operator (+) cannot be disambiguated between the addition and the add_3d subprograms.  Say with vectors_3d declared as an extension type of vector and given how your code is structured, a following simple change might be one way to get around the issue:

module vectors_3d

   use vectorspaces, only : vector !<-- note the ONLY keyword

   type, extends(vector) :: vector_3d 

 

0 Kudos
Arjen_Markus
Honored Contributor I
341 Views

You're quite right - using the ONLY clause solves the problem. In retrospect this is no more than logical. However, I started with an abstract interface and ran into a bunch of curious problems. So then I resorted to an approach that led to this problem. I now understand the issues I ran into. This has been instructive :).

0 Kudos
Arjen_Markus
Honored Contributor I
341 Views

Just to clarify the problems I had:

One of the type-bound routines required the PASS attribute. I had added that to the abstract type and then defined a concrete type based on that. I kept getting errors about the type of the first argument, whatever I did. So I stripped it down and ended up with the ancestor of the program I showed earlier.

It was only much later that I realised that the trouble was due to me not repeating the PASS attribute in the concrete type as well. Something like:

type, abstract :: vector
contains
    procedure(multiplication), deferred, pass(b) :: multiply
    generic, public                              :: operator(*)    => multiply
end type vector

type, extends(vector) :: vector_3d
    real, dimension(3) :: coords
contains
    procedure, pass(b) :: multiply => multiply_3d !<== PASS(b) repeated!
end type vector_3d

 

0 Kudos
FortranFan
Honored Contributor II
341 Views

Arjen Markus wrote:

.. It was only much later that I realised that the trouble was due to me not repeating the PASS attribute in the concrete type as well. ..

Note that repeating the characteristics of an implementation (e.g., DEFERRED procedure or MODULE function/subroutine) can have its benefits from a code readability perspective.  However the need to repeat the PASS attribute is only present when the passed object is not FIRST on the list of dummy arguments:

module a_m
   type, abstract :: a_t
   contains
      procedure(Isub1), pass(this), deferred :: sub1
      !procedure(Isub2), pass(this), deferred :: sub2
   end type
   abstract interface
      subroutine Isub1( this, s )
         import :: a_t
         implicit none
         class(a_t), intent(inout)    :: this
         character(len=*), intent(in) :: s
      end subroutine
      subroutine Isub2( s, this )
         import :: a_t
         implicit none
         character(len=*), intent(in) :: s
         class(a_t), intent(inout)    :: this
      end subroutine
   end interface
end module

module e_m
   use a_m, only : a_t
   type, extends(a_t) :: e_t
      character(len=:), allocatable :: s
   contains
      procedure :: sub1 => sub1_e  !<-- this is ok
      !procedure :: sub2 => sub2_e !<-- this won't work; PASS attribute needed here
   end type
contains
   subroutine sub1_e( this, s )
      class(e_t), intent(inout)    :: this
      character(len=*), intent(in) :: s
      this%s = s
      print *, "sub_e: ", s
   end subroutine
   subroutine sub2_e( s, this )
      character(len=*), intent(in) :: s
      class(e_t), intent(inout)    :: this
      this%s = s
      print *, "sub_e: ", s
   end subroutine
end module

 

0 Kudos
Arjen_Markus
Honored Contributor I
341 Views

Yes, the problem was that I did not realise that if PASS is required (in the abstract type), you need to add it also to the "procedure" clause in the extending class.

The error message was not very helpful, in that it made no reference to the PASS attribute: I had solved all the syntactical issues already and could not figure out what was wrong with the declaration. Just a mild form of programmer blindness ...

0 Kudos
Reply