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

problem with deferred assignment overloading

Alexis_R_
New Contributor I
1,604 Views

I believe the code below is "legal". However, ifort (14.0.1 20131008), with default options (i.e. "ifort -c") gives this error:

ifort_reproducer_140226.f90(90): error #6197: An assignment of different structure types is invalid.   [TEST_WAYPOINTS]
        test_points = test_waypoints
----------------------^
ifort_reproducer_140226.f90(91): error #6197: An assignment of different structure types is invalid.   [TEST_WAYPOINT]
        test_point = test_waypoint
---------------------^
compilation aborted for ifort_reproducer_140226.f90 (code 1)

For what it's worth, the NAG and Portland compilers do not have a problem with this code.

Is it indeed legal? If not, what is the correct way to do deferred assignment overloading?

Is there a workaround for ifort?

module coos
    implicit none

    type, abstract :: abstract_point
        real(kind=8)    ::  coo(3)  =   [0.0d0,0.0d0,0.0d0]
        contains
            private
            procedure(ass_abstract),    deferred        ::  my_assignment
            generic, public                             ::  assignment(=) => my_assignment
    end type abstract_point

    abstract interface
        pure elemental subroutine ass_abstract(lhs,rhs)
            import :: abstract_point
            class(abstract_point),   intent(inout)      ::  lhs
            class(abstract_point),   intent(in)         ::  rhs
        end subroutine
    end interface

    type, extends(abstract_point)       ::  point
        !
        contains
            procedure                   ::  my_assignment   => assign_point_to_point
    end type point

    type, extends(abstract_point)       ::  waypoint
        logical                         ::  refine      =   .true.
        real(kind=8)                    ::  path_length =   0.0d0
        contains
            procedure                   ::  my_assignment   =>  assign_point_to_waypoint
    end type

    contains

    pure elemental subroutine assign_point_to_point(lhs,rhs)
        ! arguments
        class(point),           intent(inout)       ::  lhs
        class(abstract_point),  intent(in)          ::  rhs
        ! start work
        lhs%coo = rhs%coo
    end subroutine assign_point_to_point

    pure elemental subroutine assign_point_to_waypoint(lhs,rhs)
        ! arguments
        class(waypoint),        intent(inout)       ::  lhs
        class(abstract_point),  intent(in)          ::  rhs
        ! start work
        lhs%coo = rhs%coo
        select type(rhs)
            class is (waypoint)
                call waypoint_assign(lhs,rhs)
        end select
    end subroutine assign_point_to_waypoint

    pure elemental subroutine waypoint_assign(wp_lhs,wp_rhs)
        ! arguments
        type(waypoint), intent(inout)   ::  wp_lhs
        type(waypoint), intent(in)      ::  wp_rhs
        ! start work
        wp_lhs%coo          =   wp_rhs%coo
        wp_lhs%path_length  =   wp_rhs%path_length
        wp_lhs%refine       =   wp_rhs%refine
    end subroutine waypoint_assign

    pure elemental subroutine waypoint_init(self)
        ! arguments
        type(waypoint),                 intent(inout)   ::  self
        ! start work
        self%coo = 0.0d0
        self%refine      =   .true.
        self%path_length =   0.0d0
    end subroutine waypoint_init


    subroutine coos_unit_test_1()
        ! private variables
        type(point),        allocatable ::  test_points(:)
        type(waypoint),     allocatable ::  test_waypoints(:)
        type(point)                     ::  test_point
        type(waypoint)                  ::  test_waypoint
        ! start work

        allocate(test_waypoints(10))
        call waypoint_init(test_waypoints)
        test_waypoints(2)%coo(1) = 12.3
        call waypoint_init(test_waypoint)
        test_waypoint%coo(1) = 12.3

        allocate(test_points(size(test_waypoints)))
        test_points = test_waypoints
        test_point = test_waypoint
    end subroutine coos_unit_test_1

end module coos

 

0 Kudos
9 Replies
Steven_L_Intel1
Employee
1,604 Views

I think this is the same issue as in http://software.intel.com/forums/topic/488776 ; It is our issue DPD200249796.

0 Kudos
Alexis_R_
New Contributor I
1,604 Views

Thanks - I'll keep an eye out for this issue.
 

0 Kudos
Izaak_Beekman
New Contributor II
1,604 Views

Assuming test_point and test_points are of type point and test_waypoint and test_waypoints are of type waypoint then then there is an issue resolving the generic assignment to the specific assignment procedures. One work around suggested by Kevin Davis was to add unused components to each derived type. As a temporary work around, you might try adding a component to your point type. 

[fortran]type ,extends(abstract_point) :: point

    private real :: ifort_dpd200249796_workaround = 0.0

  contains

    procedure :: my_assignment => assign_point_to_waypoint

end type [/fortran]

I'd be curious to know the results of this test and to see the contents of ifort_reproducer_140226.f90 if you are able to share them.

0 Kudos
Alexis_R_
New Contributor I
1,604 Views

Thanks Izaak for the comment. The content of ifort_reproducer_140226.f90 was exactly as in my post above.

I have added the component as you suggested, but I am seeing the same behaviour (this is ifort 14.0.1 20131008).

I attach the modified file, which includes your suggestion.

0 Kudos
Izaak_Beekman
New Contributor II
1,604 Views

I read your OP too quickly and thought you were getting a runtime error not a compile time error. The only thing that looks potentially dubious to me is declaring your procedures as [fortran] pure elemental subroutine [/fortran]. This may very well be legal F2008 (which I know added impure attribute for declaring elemental procedures, but the only place I've looked into this is in Modern Fortran Explained by MR&C, not the standard itself, and I can't find any mention of explicitly declaring an elemental procedure as pure) but I'm not sure about compiler support for adding the pure/impure attribute to elemental subroutines. At any rate, I couldn't find any work around for this bug. 

0 Kudos
FortranFan
Honored Contributor III
1,604 Views

Izaak Beekman wrote:

... The only thing that looks potentially dubious to me is declaring your procedures as

 pure elemental subroutine 

 ..

I don't think the PURE ELEMENTAL attribute has anything to do with this.  I use it often and I do have an example of a generic assignment that works well with the underlying procedure being declared as such.

In my case also, I have a concrete type extended from an abstract type and the procedure that implements the assignment is attributed as PURE ELEMENTAL  The only difference here is the OP is extending it one level further.  I don't think there is anything wrong with it; as Steve indicated, this appears to be a compiler bug.

0 Kudos
FortranFan
Honored Contributor III
1,604 Views

See a modified version of OP's code example below.  This modified code is effectively similar to some code I've used extensively.  It too gives a compiler error at line #143; a similar assignment at line 140 doesn't give an error.  I think this shows some issue within the compiler with defined assignments involving polymorphic objects:

[fortran]

module coos_mod

 

    implicit none

 

    type, abstract :: abstract_point

       real(kind=8) :: coo(3) = [0.0d0,0.0d0,0.0d0]

     contains

        private

        procedure(assign_abstract), pass(lhs), deferred :: my_assignment

        generic, public ::  assignment(=) => my_assignment

    end type abstract_point

 

    abstract interface

        pure elemental subroutine assign_abstract(lhs, rhs)

            import :: abstract_point

            class(abstract_point), intent(inout) :: lhs

            class(*), intent(in)                 :: rhs

        end subroutine

    end interface

 

end module coos_mod

 

module point_mod

 

    use coos_mod, only : abstract_point

 

    implicit none

 

    type, extends(abstract_point) ::  point

        !

    contains

        procedure, pass(lhs) ::  my_assignment => assign_point_to_point

    end type point

 

contains

 

    pure elemental subroutine assign_point_to_point(lhs, rhs)

        ! arguments

        class(point), intent(inout)      :: lhs

        class(*), intent(in)             :: rhs

        ! start work

        select type(rhs)

            type is (integer(kind=4))

               lhs%coo = 0.0d0

            type is (real(kind=8))

               lhs%coo = 0.0d0

            class is (point)

                lhs%coo = 0.0d0

            class default

        end select

    end subroutine assign_point_to_point

 

end module point_mod

 

module waypoint_mod

 

    use coos_mod, only : abstract_point

    use point_mod, only : point

 

    implicit none

 

    type, extends(abstract_point) :: waypoint

       logical      ::  refine      =   .true.

       real(kind=8) ::  path_length =   0.0d0

    contains

       procedure, pass(lhs) :: my_assignment => assign_point_to_waypoint

    end type

 

contains

 

    pure elemental subroutine assign_point_to_waypoint(lhs, rhs)

        ! arguments

        class(waypoint), intent(inout) :: lhs

        class(*),  intent(in)          :: rhs

        ! start work

        select type(rhs)

            type is (integer(kind=4))

               lhs%coo = 0.0d0

            type is (real(kind=8))

               lhs%coo = 0.0d0

            class is (waypoint)

               lhs%coo = 0.0d0

               call waypoint_assign(lhs, rhs)

        end select

    end subroutine assign_point_to_waypoint

 

    pure elemental subroutine waypoint_assign(wp_lhs,wp_rhs)

        ! arguments

        type(waypoint), intent(inout)   ::  wp_lhs

        type(waypoint), intent(in)      ::  wp_rhs

        ! start work

        wp_lhs%coo          =   wp_rhs%coo

        wp_lhs%path_length  =   wp_rhs%path_length

        wp_lhs%refine       =   wp_rhs%refine

    end subroutine waypoint_assign

 

    pure elemental subroutine waypoint_init(self)

        ! arguments

        type(waypoint),                 intent(inout)   ::  self

        ! start work

        self%coo = 0.0d0

        self%refine      =   .true.

        self%path_length =   0.0d0

    end subroutine waypoint_init

 

end module waypoint_mod

 

module type_int_mod

 

   implicit none

 

   type, public :: myint

      integer :: i

   end type myint

 

end module type_int_mod

 

module test_mod

 

    use point_mod, only : point

    use waypoint_mod, only : waypoint

    use type_int_mod, only : myint

 

contains

 

    subroutine testassign()

 

        ! private variables

        type(point)    :: test_point

        type(waypoint) :: test_waypoint

        type(myint) :: t

     

        !..

        test_point = 3         ! <-- This works

        test_waypoint = 0.0d0  ! <-- This works

     

        !..

        t%i = 3

        test_point = t     ! <-- This works

        test_waypoint = t  ! <-- This works

     

        !..

        test_point = test_waypoint ! <-- This doesn't work

     

    end subroutine testassign

 

end module test_mod

[/fortran]

0 Kudos
FortranFan
Honored Contributor III
1,604 Views

For whatever it's worth, the code in the original post as well as the modified one I posted in Quote #8 compile without errors in gfortran, MinGW Build 4.8.1

0 Kudos
Izaak_Beekman
New Contributor II
1,604 Views

FortranFan wrote:

Quote:

Izaak Beekman wrote:

... The only thing that looks potentially dubious to me is declaring your procedures as

 pure elemental subroutine 

 ..

 

I don't think the PURE ELEMENTAL attribute has anything to do with this.  I use it often and I do have an example of a generic assignment that works well with the underlying procedure being declared as such.

In my case also, I have a concrete type extended from an abstract type and the procedure that implements the assignment is attributed as PURE ELEMENTAL  The only difference here is the OP is extending it one level further.  I don't think there is anything wrong with it; as Steve indicated, this appears to be a compiler bug.

I was neither contradicting Steve's assertion that this is a compiler bug, nor was I claiming that pure elemental was the trigger of this bug. I was merely speculating that it must either be a new F2008 feature or illegal code. (I believe F2008 is when impure elemental was added, and prior to that all elemental subroutines had to be pure, and did not require the pure attribute to be explicitly added.) I have no experience with explicitly declaring elemental procedures as pure (or impure) and tend to avoid new language features which I don't really need because I worry about compiler support.

0 Kudos
Reply