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

catastrophic error for expressions involving polimorphic operators

Salvadore__Francesco
525 Views

Hello,

I am experiencing problems using expressions with polymorphic objects and operators.

I managed to reproduce the error in a small code which I post below. 

Basically the type ta is abstract with =, +, * (real*obj) deferred operators while type tb implements them. While a+b and k*a work, if I try to do k*(a+b) it cannot compile reporting internal compiler error. I cannot understand the reason of such behavior.

module ma
    type, abstract :: ta
        contains
            procedure(abs_ass),     private, deferred :: ass
            procedure(abs_add),     private, deferred :: add
            procedure(abs_realmul), private, deferred, pass(a) :: realmul
            generic, public :: assignment(=) => ass
            generic, public :: operator(+) => add
            generic, public :: operator(*) => realmul
    endtype
    abstract interface
        subroutine abs_ass(a, b)
            import :: ta
            class(ta), intent(inout) :: a
            class(ta), intent(in) :: b
        end subroutine abs_ass
        function abs_add(a, b) result(r)
            import :: ta
            class(ta), intent(in) :: a, b
            class(ta), allocatable :: r
        end function abs_add
        function abs_realmul(k, a) result(r)
            import :: ta
            real, intent(in) :: k
            class(ta), intent(in) :: a
            class(ta), allocatable :: r
        end function abs_realmul
    end interface
end module ma

module mb
    use ma
    type, extends(ta) :: tb
        real :: x
        contains
            procedure, private :: add
            procedure, private :: ass
            procedure, private, pass(a) :: realmul
    endtype
contains
    subroutine ass(a, b)
        class(tb), intent(inout) :: a
        class(ta), intent(in) :: b
        select type(b)
           type is(tb)
               a%x = b%x
           class default
               print*,"Error"
        endselect
    end subroutine ass
    function add(a, b) result(r)
        class(tb), intent(in) :: a
        class(ta), intent(in) :: b
        class(ta), allocatable :: r
        allocate(tb :: r)
        select type(b)
           type is(tb)
               select type(r)
                   type is(tb)
                       r%x = a%x + b%x
               end select
           class default
               print*,"Error"
        endselect
    end function add

    function realmul(k, a) result(r)
        real, intent(in) :: k
        class(tb), intent(in) :: a
        class(ta), allocatable :: r
        allocate(tb :: r)
        select type(r)
           type is(tb)
               r%x = k * a%x
           class default
               print*,"Error"
        endselect
    end function realmul
end module mb

program mt
    use ma
    use mb
    class(ta), allocatable :: va1, va2, va3
    allocate(tb :: va1)
    allocate(tb :: va2)
    allocate(tb :: va3)
    select type(va1)
        type is(tb)
            va1%x = 10.
    endselect
    select type(va2)
        type is(tb)
            va2%x = 20.
    endselect
    !IT WORKS va3 = va1 + va2
    !IT WORKS va3 = 3.*va1
    ! CATASTROPHIC ERROR
    va3 = 1.*(va1 + va2)
    select type(va3)
        type is(tb)
            print*,"it should be 30: ",va3%x
    endselect
end program mt

 

Thanks,

Francesco

 

 

 

0 Kudos
6 Replies
Steven_L_Intel1
Employee
525 Views

Thanks for the report. I can reproduce this in 16.0.3 but the 17.0 compiler, due out later this year, reports:

U671994.f90(99): error #6633: The type of the actual argument differs from the type of the dummy argument.
    va3 = 1.*(va1 + va2)
------------------^

This is clearly wrong as well, but at least no internal compiler error! I will send this on to the developers.Issue ID is DPD200413156.

0 Kudos
Steven_L_Intel1
Employee
525 Views

We're still working on this, but we discovered that there's an error in your source that the current compiler doesn't detect - our development version does.

The deferred bindings in type ta are marked private, this makes them inaccessible when type tb extends type ta. This was clarified in interpretation F08/0052 part of F08 Corrigendum 1.

0 Kudos
Salvadore__Francesco
525 Views

Thanks for the support. Any news on the compiler version fixing the problem?

Francesco

0 Kudos
Kevin_D_Intel
Employee
525 Views

As Steve noted, the internal compiler error you experienced with the 16.0 compiler is fixed in the latest 17.0 compiler release; however, the 17.0 compiler issues the error note in post #2. There is no fix currently available for that error.

To avoid the internal error you need to upgrade to 17.0, but to avoid the error in post #2 still requires a source code workaround similar to what is noted at source lines 96-97 of the test case. Rewriting line 99 as noted below compiles successfully with the latest 17.0 update 1 compiler.

   va3 = va1 + va2
   va3 = 1.*va3

I inquired with the developer for a current status of a fix for the error in post #2 and will post again with any update that I receive.

0 Kudos
Stefano_Zaghi
Beginner
525 Views

Dear all,

I have just joined the 2018 beta testing initiative and I can confirm that also the parallel studio xe 2018 beta has the same bug, here my log

┌╼ stefano@zaghi(01:21 PM Thu Apr 13) desk {intel-18.0.0.beta - Intel Parallel Studio XE 2018.0.0 beta}
├───╼ ~/fortran/compilers_bug/intel_abstract_types_operators/salvadore 7 files, 40Kb
└──────╼ ifort abstract_types_operator-salvadore-mt.f90
abstract_types_operator-salvadore-mt.f90(20): error #6633: The type of the actual argument differs from the type of the dummy argument.
    va3 = 1.*(va1 + va2)
------------------^
compilation aborted for abstract_types_operator-salvadore-mt.f90 (code 1)

My best regards.

0 Kudos
Kevin_D_Intel
Employee
525 Views

The internal tracking id linked to this case (DPD200413156) is not fixed yet and I have not heard back from Development on the current status. I added another note re: 18.0.

(Internal tracking id: DPD200413156)

0 Kudos
Reply