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

Possible bug on abstract type

Stefano_Zaghi
Beginner
1,065 Views

Dear great Intel Fortran Developers team,

I would like to report a possible bug in ifort 15.0.3.

I am trying to develop an OOP library that takes advantage of Abstract Calculus Pattern by means of an abstract type definition. In a very few words, the library defines an abstract type with some operators overloading deferred and it provides a procedure that operates on the abstract type. The concrete extensions of the abstract type implement only the type bound procedures deferred whereas the overloaded operators are defined by the abstract type. The real code is here https://github.com/Fortran-FOSS-Programmers/FOODiE/blob/master/src/lib/type_integrand.f90

A minimal example raising the possible bug is reported below. There are 3 modules and 1 main program: 1) type_abstract_buggy provides the abstract type, 2) lib_abstract_buggy provides a procedure working on the abstract type that raises the possible bug, 3) type_buggy implements a concrete extension of the abstract type defining only the procedures for the operators overloading and 4) is the main program using the last 2 modules. 

The expected results are:

Array: 

  1.00000000
  2.00000000
  3.00000000
Scalar:     3
Array:
  2.00000000
  4.00000000
  6.00000000
Scalar:     3
Array:
  4.00000000
  8.00000000
  12.0000000
Scalar:     3

 

but when compiling with ifort 15.0.3 complains with following errors. 

ifort-bug.f90(58): error #6633: The type of the actual argument differs from the type of the dum

my argument.   [BUG]
 bug = scalar * bug
-----------------^
ifort-bug.f90(146): error #7013: This module file was not generated by any release of this compi
ler.   [LIB_ABSTRACT_BUGGY]
use lib_abstract_buggy, only : raise_bug
----^
ifort-bug.f90(149): error #6457: This derived type name has not been declared.   [BUGGY]
type(buggy) :: bug
-----^
ifort-bug.f90(151): error #6404: This name does not have a type, and must have an explicit type.
  [BUG]
bug = buggy(array=[1., 2., 3.], scalar=3)
^
ifort-bug.f90(151): error #6632: Keyword arguments are invalid without an explicit interface.   
[ARRAY]
bug = buggy(array=[1., 2., 3.], scalar=3)
------------^
ifort-bug.f90(151): error #6632: Keyword arguments are invalid without an explicit interface.   
[SCALAR]
bug = buggy(array=[1., 2., 3.], scalar=3)
--------------------------------^
ifort-bug.f90(152): error #6406: Conflicting attributes or multiple declaration of name.   [RAIS
E_BUG]
call raise_bug(bug=bug, scalar=2)
-----^
ifort-bug.f90(146): error #6580: Name in only-list does not exist.   [RAISE_BUG]
use lib_abstract_buggy, only : raise_bug
-------------------------------^
ifort-bug.f90(147): error #6580: Name in only-list does not exist.   [BUGGY]
use type_buggy, only : buggy
-----------------------^
compilation aborted for ifort-bug.f90 (code 1)

 

The compilation is done by: ifort -O0 -debug all -check all -warn all -traceback -assume realloc_lhs -std08 ifort-bug.f90

Note that the correct result is obtained by GNU gfortran 5.2.

Minimal example raising the possible compiler bug

 
module type_abstract_buggy
implicit none
private
public :: abstract_buggy

type, abstract :: abstract_buggy
  contains
    ! public methods
    procedure(abstract_printf), public, deferred :: printf
    generic,                    public           :: operator(*) => buggy_multiply_scalar, scalar_multiply_buggy
    generic,                    public           :: assignment(=) => buggy_assign_buggy
    ! private methods
    procedure(abstract_buggy_multiply_scalar),       pass(lhs), private, deferred :: buggy_multiply_scalar
    procedure(scalar_multiply_abstract_buggy),       pass(rhs), private, deferred :: scalar_multiply_buggy
    procedure(abstract_buggy_assign_abstract_buggy), pass(lhs), private, deferred :: buggy_assign_buggy
endtype abstract_buggy
abstract interface
  subroutine abstract_printf(self)
  import :: abstract_buggy
  class(abstract_buggy), intent(IN) :: self
  endsubroutine abstract_printf

  function abstract_buggy_multiply_scalar(lhs, rhs) result(multy)
  import :: abstract_buggy
  class(abstract_buggy), intent(IN)  :: lhs
  integer,               intent(IN)  :: rhs
  class(abstract_buggy), allocatable :: multy
  endfunction abstract_buggy_multiply_scalar

  function scalar_multiply_abstract_buggy(lhs, rhs) result(multy)
  import :: abstract_buggy
  integer,               intent(IN)  :: lhs
  class(abstract_buggy), intent(IN)  :: rhs
  class(abstract_buggy), allocatable :: multy
  endfunction scalar_multiply_abstract_buggy

  pure subroutine abstract_buggy_assign_abstract_buggy(lhs, rhs)
  import :: abstract_buggy
  class(abstract_buggy), intent(INOUT) :: lhs
  class(abstract_buggy), intent(IN)    :: rhs
  endsubroutine abstract_buggy_assign_abstract_buggy
endinterface
endmodule type_abstract_buggy

module lib_abstract_buggy
use type_abstract_buggy, only : abstract_buggy
implicit none
private
public :: raise_bug
contains
  subroutine raise_bug(bug, scalar)
  class(abstract_buggy), intent(INOUT) :: bug
  integer,               intent(IN)    :: scalar

  call bug%printf()
  bug = bug * scalar
  call bug%printf()
  bug = scalar * bug
  call bug%printf()
  endsubroutine raise_bug
endmodule lib_abstract_buggy

module type_buggy
use type_abstract_buggy, only : abstract_buggy
implicit none
private
public :: buggy

type, extends(abstract_buggy) :: buggy
  private
  real, dimension(:), allocatable :: array
  integer                         :: scalar=0
  contains
    ! public methods
    procedure, pass(self), public :: printf
    ! private methods
    procedure, pass(lhs), private :: buggy_multiply_scalar
    procedure, pass(rhs), private :: scalar_multiply_buggy
    procedure, pass(lhs), private :: buggy_assign_buggy
endtype buggy
interface buggy
  procedure create_buggy
endinterface
contains
  pure function create_buggy(array, scalar) result(bug)
  real, dimension(:), intent(IN) :: array
  integer,            intent(IN) :: scalar
  type(buggy)                    :: bug

  bug%array = array
  bug%scalar = scalar
  return
  endfunction create_buggy

  subroutine printf(self)
  class(buggy), intent(IN) :: self
  integer      :: i

  print "(A)", "Array:"
  do i=1, size(self%array)
    print*, self%array(i)
  enddo
  print "(A,I5)", "Scalar: ", self%scalar
  endsubroutine printf

  function buggy_multiply_scalar(lhs, rhs) result(multy)
  class(buggy), intent(IN)           :: lhs
  integer,      intent(IN)           :: rhs
  class(abstract_buggy), allocatable :: multy
  type(buggy),           allocatable :: multy_tmp

  allocate(buggy :: multy_tmp)
  multy_tmp%array = lhs%array * rhs
  multy_tmp%scalar = lhs%scalar
  call move_alloc(multy_tmp, multy)
  return
  endfunction buggy_multiply_scalar

  pure function scalar_multiply_buggy(lhs, rhs) result(multy)
  integer,      intent(IN)           :: lhs
  class(buggy), intent(IN)           :: rhs
  class(abstract_buggy), allocatable :: multy
  type(buggy),           allocatable :: multy_tmp

  allocate(buggy :: multy_tmp)
  multy_tmp%array = rhs%array * lhs
  multy_tmp%scalar = rhs%scalar
  call move_alloc(multy_tmp, multy)
  return
  endfunction scalar_multiply_buggy

  pure subroutine buggy_assign_buggy(lhs, rhs)
  class(buggy),          intent(INOUT) :: lhs
  class(abstract_buggy), intent(IN)    :: rhs

  select type(rhs)
  class is(buggy)
    if (allocated(rhs%array)) lhs%array = rhs%array
    lhs%scalar = rhs%scalar
  endselect
  return
  endsubroutine buggy_assign_buggy
endmodule type_buggy

program ifort_bug
use lib_abstract_buggy, only : raise_bug
use type_buggy, only : buggy
implicit none
type(buggy) :: bug

bug = buggy(array=[1., 2., 3.], scalar=3)
call raise_bug(bug=bug, scalar=2)
stop
endprogram ifort_bug

 

0 Kudos
1 Solution
FortranFan
Honored Contributor II
1,065 Views

Stefano Zaghi wrote:

.. I will check the progress of this possible bug (maybe my code is wrong and gfortran is bugged :-)) ..

My opinion is your code is correct and so is gfortran.  The bug is in Intel Fortran.  Besides, compiler version 16, update 2 gives an internal compiler error for your main program in which case the burden lies entirely on the compiler, as alluded to by Steve.  I have noticed such problems previously in Intel Fortran with the "constructor" facility in Fortran whereby a interface name can be the same as a derived type; I may have even reported a couple of such issues going as far back as compiler 14.  But even without such problems, I have become uninterested in such a constructor facility and I now prefer "initialization" or set accesors which basically boils down to a preference for subroutines with an INTENT(INOUT) attribute for an object (especially when with allocatable subcomponents are present) over a function returning such an object and which will normally be present on the right-hand side of an assignment.  As you may have noticed in threads on comp.lang.fortran, the use of such functions has certain implications pertaining to array temporaries and reallocation on left-hand side on assignment, etc. and I find it rather harrowing to chase down all the details and ensure no ill-effects, especially in optimization.

So if you make such a simple modification to include a set accesor,  you will find your code works with Intel Fortran and gives the same results as with gfortran.  See details below with the set_buggy type-bound procedure in your buggy extended type.

module type_buggy

   use type_abstract_buggy, only : abstract_buggy

   implicit none

   private

   public :: buggy

   type, extends(abstract_buggy) :: buggy
      private
      real, dimension(:), allocatable :: array
      integer                         :: scalar=0
   contains
      ! public methods
      procedure, pass(self), public :: printf
      procedure, pass(self), public :: set => set_buggy
      ! private methods
      procedure, pass(lhs), private :: buggy_multiply_scalar
      procedure, pass(rhs), private :: scalar_multiply_buggy
      procedure, pass(lhs), private :: buggy_assign_buggy
   end type buggy

   interface buggy
      procedure create_buggy
   end interface

contains

   pure function create_buggy(array, scalar) result(bug)
      real, dimension(:), intent(IN) :: array
      integer,            intent(IN) :: scalar
      type(buggy)                    :: bug

      bug%array = array
      bug%scalar = scalar
      return
   end function create_buggy

   pure subroutine set_buggy(self, array, scalar)

      class(buggy), intent(inout)    :: self
      real, dimension(:), intent(IN) :: array
      integer,            intent(IN) :: scalar

      self%array = array
      self%scalar = scalar

      return

   end subroutine set_buggy

   subroutine printf(self)
      class(buggy), intent(IN) :: self
      integer      :: i

      print "(A)", "Array:"
      do i=1, size(self%array)
         print*, self%array(i)
      enddo
      print "(A,I5)", "Scalar: ", self%scalar
   end subroutine printf

   function buggy_multiply_scalar(lhs, rhs) result(multy)
      class(buggy), intent(IN)           :: lhs
      integer,      intent(IN)           :: rhs
      class(abstract_buggy), allocatable :: multy
      type(buggy),           allocatable :: multy_tmp

      allocate(buggy :: multy_tmp)
      multy_tmp%array = lhs%array * rhs
      multy_tmp%scalar = lhs%scalar
      call move_alloc(multy_tmp, multy)
      return
   end function buggy_multiply_scalar

   pure function scalar_multiply_buggy(lhs, rhs) result(multy)
      integer,      intent(IN)           :: lhs
      class(buggy), intent(IN)           :: rhs
      class(abstract_buggy), allocatable :: multy
      type(buggy),           allocatable :: multy_tmp

      allocate(buggy :: multy_tmp)
      multy_tmp%array = rhs%array * lhs
      multy_tmp%scalar = rhs%scalar
      call move_alloc(multy_tmp, multy)
      return
   end function scalar_multiply_buggy

   pure subroutine buggy_assign_buggy(lhs, rhs)
      class(buggy),          intent(INOUT) :: lhs
      class(abstract_buggy), intent(IN)    :: rhs

      select type(rhs)
         class is(buggy)
            if (allocated(rhs%array)) lhs%array = rhs%array
            lhs%scalar = rhs%scalar
      endselect
      return
   end subroutine buggy_assign_buggy

end module type_buggy
program ifort_bug

   use lib_abstract_buggy, only : raise_bug
   use type_buggy, only : buggy

   implicit none

   type(buggy) :: bug

   call bug%set( array=[1., 2., 3.], scalar=3 )

   call raise_bug(bug=bug, scalar=2)

   stop

end program ifort_bug

Upon execution with gfortran (GCC 6.0 development version),

Array:
   1.00000000
   2.00000000
   3.00000000
Scalar:     3
Array:
   2.00000000
   4.00000000
   6.00000000
Scalar:     3
Array:
   4.00000000
   8.00000000
   12.0000000
Scalar:     3

Process returned 0 (0x0)   execution time : 0.047 s
Press any key to continue.

Upon execution with Intel Fortran, compiler 16 update 2:

Array:
 1.000000
 2.000000
 3.000000
Scalar:     3
Array:
 2.000000
 4.000000
 6.000000
Scalar:     3
Array:
 4.000000
 8.000000
 12.00000
Scalar:     3
Press any key to continue . . .

 

View solution in original post

0 Kudos
12 Replies
Steven_L_Intel1
Employee
1,065 Views

Thanks for the cut down test case - that helps a lot. I note that while 15.0 complains about a type mismatch, the 16.0 compiler gets an internal compiler error for this, which is even worse. I have escalated this as issue DPD200374902 and will let you know of any progress.

0 Kudos
Stefano_Zaghi
Beginner
1,065 Views

Dear Steve,

thank you very much for your extremely fast replay and thank you also for your great work on Intel Fortran!

I will check the progress of this possible bug (maybe my code is wrong and gfortran is bugged :-))

My best regards. 

0 Kudos
Steven_L_Intel1
Employee
1,065 Views

I must admit that it made my head hurt to contemplate the code in raise_bug which references only abstract types and deferred type-bound procedures. But I suppose this should work...

0 Kudos
Stefano_Zaghi
Beginner
1,065 Views

I am sorry, but this just what Abstract Calculus Pattern imposes...

The aim is: develop a library that knows only the abstract type and let clients extend the abstract type for implementing their own concrete types that will use the library... it seems cumbersome, but has a lot of sense. If you are interested in why I am so crazy see these pages

https://github.com/Fortran-FOSS-Programmers/FOODiE/wiki

https://github.com/Fortran-FOSS-Programmers/FOODiE/wiki/Background-and-Motivations

https://github.com/Fortran-FOSS-Programmers/FOODiE/wiki/High-Level-Programming

 

0 Kudos
Steven_L_Intel1
Employee
1,065 Views

I understand the concept - I was just trying to imagine what the compiler had to do in order to support it.

0 Kudos
FortranFan
Honored Contributor II
1,066 Views

Stefano Zaghi wrote:

.. I will check the progress of this possible bug (maybe my code is wrong and gfortran is bugged :-)) ..

My opinion is your code is correct and so is gfortran.  The bug is in Intel Fortran.  Besides, compiler version 16, update 2 gives an internal compiler error for your main program in which case the burden lies entirely on the compiler, as alluded to by Steve.  I have noticed such problems previously in Intel Fortran with the "constructor" facility in Fortran whereby a interface name can be the same as a derived type; I may have even reported a couple of such issues going as far back as compiler 14.  But even without such problems, I have become uninterested in such a constructor facility and I now prefer "initialization" or set accesors which basically boils down to a preference for subroutines with an INTENT(INOUT) attribute for an object (especially when with allocatable subcomponents are present) over a function returning such an object and which will normally be present on the right-hand side of an assignment.  As you may have noticed in threads on comp.lang.fortran, the use of such functions has certain implications pertaining to array temporaries and reallocation on left-hand side on assignment, etc. and I find it rather harrowing to chase down all the details and ensure no ill-effects, especially in optimization.

So if you make such a simple modification to include a set accesor,  you will find your code works with Intel Fortran and gives the same results as with gfortran.  See details below with the set_buggy type-bound procedure in your buggy extended type.

module type_buggy

   use type_abstract_buggy, only : abstract_buggy

   implicit none

   private

   public :: buggy

   type, extends(abstract_buggy) :: buggy
      private
      real, dimension(:), allocatable :: array
      integer                         :: scalar=0
   contains
      ! public methods
      procedure, pass(self), public :: printf
      procedure, pass(self), public :: set => set_buggy
      ! private methods
      procedure, pass(lhs), private :: buggy_multiply_scalar
      procedure, pass(rhs), private :: scalar_multiply_buggy
      procedure, pass(lhs), private :: buggy_assign_buggy
   end type buggy

   interface buggy
      procedure create_buggy
   end interface

contains

   pure function create_buggy(array, scalar) result(bug)
      real, dimension(:), intent(IN) :: array
      integer,            intent(IN) :: scalar
      type(buggy)                    :: bug

      bug%array = array
      bug%scalar = scalar
      return
   end function create_buggy

   pure subroutine set_buggy(self, array, scalar)

      class(buggy), intent(inout)    :: self
      real, dimension(:), intent(IN) :: array
      integer,            intent(IN) :: scalar

      self%array = array
      self%scalar = scalar

      return

   end subroutine set_buggy

   subroutine printf(self)
      class(buggy), intent(IN) :: self
      integer      :: i

      print "(A)", "Array:"
      do i=1, size(self%array)
         print*, self%array(i)
      enddo
      print "(A,I5)", "Scalar: ", self%scalar
   end subroutine printf

   function buggy_multiply_scalar(lhs, rhs) result(multy)
      class(buggy), intent(IN)           :: lhs
      integer,      intent(IN)           :: rhs
      class(abstract_buggy), allocatable :: multy
      type(buggy),           allocatable :: multy_tmp

      allocate(buggy :: multy_tmp)
      multy_tmp%array = lhs%array * rhs
      multy_tmp%scalar = lhs%scalar
      call move_alloc(multy_tmp, multy)
      return
   end function buggy_multiply_scalar

   pure function scalar_multiply_buggy(lhs, rhs) result(multy)
      integer,      intent(IN)           :: lhs
      class(buggy), intent(IN)           :: rhs
      class(abstract_buggy), allocatable :: multy
      type(buggy),           allocatable :: multy_tmp

      allocate(buggy :: multy_tmp)
      multy_tmp%array = rhs%array * lhs
      multy_tmp%scalar = rhs%scalar
      call move_alloc(multy_tmp, multy)
      return
   end function scalar_multiply_buggy

   pure subroutine buggy_assign_buggy(lhs, rhs)
      class(buggy),          intent(INOUT) :: lhs
      class(abstract_buggy), intent(IN)    :: rhs

      select type(rhs)
         class is(buggy)
            if (allocated(rhs%array)) lhs%array = rhs%array
            lhs%scalar = rhs%scalar
      endselect
      return
   end subroutine buggy_assign_buggy

end module type_buggy
program ifort_bug

   use lib_abstract_buggy, only : raise_bug
   use type_buggy, only : buggy

   implicit none

   type(buggy) :: bug

   call bug%set( array=[1., 2., 3.], scalar=3 )

   call raise_bug(bug=bug, scalar=2)

   stop

end program ifort_bug

Upon execution with gfortran (GCC 6.0 development version),

Array:
   1.00000000
   2.00000000
   3.00000000
Scalar:     3
Array:
   2.00000000
   4.00000000
   6.00000000
Scalar:     3
Array:
   4.00000000
   8.00000000
   12.0000000
Scalar:     3

Process returned 0 (0x0)   execution time : 0.047 s
Press any key to continue.

Upon execution with Intel Fortran, compiler 16 update 2:

Array:
 1.000000
 2.000000
 3.000000
Scalar:     3
Array:
 2.000000
 4.000000
 6.000000
Scalar:     3
Array:
 4.000000
 8.000000
 12.00000
Scalar:     3
Press any key to continue . . .

 

0 Kudos
FortranFan
Honored Contributor II
1,065 Views

A clarification re: quote #7: I am not trying to say you should not use constructors nor trying to suggest Intel Fortran is ok as-is.  Simply that an alternate approach by and large validates your code, especially your abstract class design and that the problem is indeed on the Intel Fortran and that it may lie elsewhere and not have anything to do with the use of abstract derived types.  My suggestion for the Intel compiler team will be to investigate the constructor facility and its use in a calling program.

Re: the compiler error with version 15, they seem related to problems in Intel Fortran compiler in connection with generic resolutions of procedures.  There have been fixes for these (sorry I can't recall the forum threads where such problems were raised previously) and you are seeing them in action in compiler 16 beta.

 

0 Kudos
Stefano_Zaghi
Beginner
1,065 Views

Dear FortranFan thank you very much!

As you, I always prefer init subroutine without overloading type names, but in this case I follow the preferences of other collaborators. Indeed, I am very surprise that changing the constructor the "bug" vanishes... I was almost sure that the problem was the "passage" by the library completely based on the abstract type.

I do not understand if both versions 15.x and 16.x work with your patch or only the 16.x. Can you clarify which version works? I am out of office and with smartphone is difficult to read the code... does your patch consists in only constructor change?

Thank you again!

0 Kudos
FortranFan
Honored Contributor II
1,065 Views

Stefano Zaghi wrote:

.. I do not understand if both versions 15.x and 16.x work with your patch or only the 16.x. Can you clarify which version works? I am out of office and with smartphone is difficult to read the code... does your patch consists in only constructor change? ..

Stefano,

With Intel Fortran compiler 15, update 4 (i.e., v 15.0.4.221), your module lib_abstract_buggy fails to compile with an error message:

Compiling with Intel(R) Visual Fortran Compiler XE 15.0.4.221 [Intel(R) 64]...
m.f90
m.f90(71): error #6633: The type of the actual argument differs from the type of the dummy
argument.   [BUG]
compilation aborted for m.f90 (code 1)

The compiler is complaining about line #58 in your original post in the subroutine raise_bug where the generic operator * comes into play with a defined multiplication operation of an integer with your abstract_buggy type.  As I mentioned earlier, this problem seems to be related to problems in Intel Fortran compiler in connection with generic resolutions of procedures.  There have been fixes for these in Intel Fortran and my hunch is you are seeing them in action in compiler 16 beta

Note, just as a test, if line 58 is modified to be the same as line 56 (i.e., bug = bug * scalar) and if the set accessor approach is used, then compiler 15 (update 4) works the same as compiler 16 (update 2) and gives the same results as gfortran.

And to reconfirm, in the patch I posted in Quote #6, the only change I made was to add set_buggy subroutine to type buggy in type_buggy module; the main program then had one line change: line 151 became call bug%set( .. ) instead of the constructor function call of bug=buggy(..).

Hope this helps,

0 Kudos
Stefano_Zaghi
Beginner
1,065 Views

Dear FortranFan this helps a lot! Thank you very mucħ!

As soon as possible I will try to refactor the buggy program in order to obtain a really minimal bug-raising example. Thank you all!

0 Kudos
moral__ramon
Beginner
1,065 Views

Hello from 2019!  Gfortran still compiles this.

My screen for my other compiler looks like this:

sameissue.f90: error #8322: A deferred binding is inherited by non-abstract type; It must be overridden.   [BUGGY_MULTIPLY_SCALAR]

sameissue.f90(69): error #6136: Derived-type declared must be ABSTRACT   [BUGGY]

type, extends(abstract_buggy) :: buggy

---------------------------------^

sameissue.f90: error #8322: A deferred binding is inherited by non-abstract type; It must be overridden.   [SCALAR_MULTIPLY_BUGGY]

sameissue.f90: error #8322: A deferred binding is inherited by non-abstract type; It must be overridden.   [BUGGY_ASSIGN_BUGGY]

sameissue.f90(147): error #7002: Error in opening the compiled module file.  Check INCLUDE paths.   [TYPE_BUGGY]

use type_buggy, only : buggy

----^

sameissue.f90(149): error #6406: Conflicting attributes or multiple declaration of name.   [BUGGY]

type(buggy) :: bug

-----^

sameissue.f90(151): error #6404: This name does not have a type, and must have an explicit type.   [BUG]

bug = buggy(array=[1., 2., 3.], scalar=3)

^

sameissue.f90(151): error #6406: Conflicting attributes or multiple declaration of name.   [BUGGY]

bug = buggy(array=[1., 2., 3.], scalar=3)

------^

sameissue.f90(147): error #6580: Name in only-list does not exist or is not accessible.   [BUGGY]

use type_buggy, only : buggy

-----------------------^

compilation aborted for sameissue.f90 (code 1)

This is very strange.  Thanks for the example!

0 Kudos
FortranFan
Honored Contributor II
1,065 Views

moral, ramon wrote:

.. Gfortran still compiles this.

My screen for my other compiler looks like this: ..

This is very strange.  Thanks for the example!

Interpretation requests (independent) toward Fortran 2008 around the time of the original post of this thread and subsequent publication of Fortran 2018 have shown the code in the original example of be non-conforming and gfortran to be incorrect.  The issue is with the PRIVATE attributes applied to the 3 DEFERRED procedures in the abstract derived type 'abstract_buggy'.  PRIVATE attribute applies at the MODULE level so the extension type would need to be in the same module as the ABSTRACT type or else the DEFERRED procedures must be PUBLIC.  Here's a slightly modified version of the example in the original post.  This should be work with both compilers and give the results as shown below.

module type_abstract_buggy
   implicit none
   private
   public :: abstract_buggy

   type, abstract :: abstract_buggy
   contains
      private
      ! public methods
      procedure(abstract_printf), public, deferred :: printf
      generic,                    public           :: operator(*) => buggy_multiply_scalar, scalar_multiply_buggy
      generic,                    public           :: assignment(=) => buggy_assign_buggy
      ! public deferred methods
      procedure(abstract_buggy_multiply_scalar),       pass(lhs), public, deferred :: buggy_multiply_scalar
      procedure(scalar_multiply_abstract_buggy),       pass(rhs), public, deferred :: scalar_multiply_buggy
      procedure(abstract_buggy_assign_abstract_buggy), pass(lhs), public, deferred :: buggy_assign_buggy
   endtype abstract_buggy
   abstract interface
      subroutine abstract_printf(self)
         import :: abstract_buggy
         class(abstract_buggy), intent(IN) :: self
      endsubroutine abstract_printf

      function abstract_buggy_multiply_scalar(lhs, rhs) result(multy)
         import :: abstract_buggy
         class(abstract_buggy), intent(IN)  :: lhs
         integer,               intent(IN)  :: rhs
         class(abstract_buggy), allocatable :: multy
      endfunction abstract_buggy_multiply_scalar

      function scalar_multiply_abstract_buggy(lhs, rhs) result(multy)
         import :: abstract_buggy
         integer,               intent(IN)  :: lhs
         class(abstract_buggy), intent(IN)  :: rhs
         class(abstract_buggy), allocatable :: multy
      endfunction scalar_multiply_abstract_buggy

      pure subroutine abstract_buggy_assign_abstract_buggy(lhs, rhs)
         import :: abstract_buggy
         class(abstract_buggy), intent(INOUT) :: lhs
         class(abstract_buggy), intent(IN)    :: rhs
      endsubroutine abstract_buggy_assign_abstract_buggy
   endinterface
endmodule type_abstract_buggy
module lib_abstract_buggy
   use type_abstract_buggy, only : abstract_buggy
   implicit none
   private
   public :: raise_bug
contains
   subroutine raise_bug(bug, scalar)
      class(abstract_buggy), intent(INOUT) :: bug
      integer,               intent(IN)    :: scalar

      call bug%printf()
      bug = bug * scalar
      call bug%printf()
      bug = scalar * bug
      call bug%printf()
   endsubroutine raise_bug
endmodule lib_abstract_buggy
module type_buggy
   use type_abstract_buggy, only : abstract_buggy
   implicit none
   private
   public :: buggy

   type, extends(abstract_buggy) :: buggy
      private
      real, dimension(:), allocatable :: array
      integer                         :: scalar=0
   contains
      private
      ! public methods
      procedure, pass(self), public :: printf
      ! private methods
      procedure, pass(lhs), public :: buggy_multiply_scalar
      procedure, pass(rhs), public :: scalar_multiply_buggy
      procedure, pass(lhs), public :: buggy_assign_buggy
   endtype buggy
   interface buggy
      procedure create_buggy
   endinterface
contains
   pure function create_buggy(array, scalar) result(bug)
      real, dimension(:), intent(IN) :: array
      integer,            intent(IN) :: scalar
      type(buggy)                    :: bug

      bug%array = array
      bug%scalar = scalar
      return
   endfunction create_buggy

   subroutine printf(self)
      class(buggy), intent(IN) :: self
      integer      :: i

      print "(A)", "Array:"
      do i=1, size(self%array)
         print*, self%array(i)
      enddo
      print "(A,I5)", "Scalar: ", self%scalar
   endsubroutine printf

   function buggy_multiply_scalar(lhs, rhs) result(multy)
      class(buggy), intent(IN)           :: lhs
      integer,      intent(IN)           :: rhs
      class(abstract_buggy), allocatable :: multy
      type(buggy),           allocatable :: multy_tmp

      allocate(buggy :: multy_tmp)
      multy_tmp%array = lhs%array * rhs
      multy_tmp%scalar = lhs%scalar
      call move_alloc(multy_tmp, multy)
      return
   endfunction buggy_multiply_scalar

   pure function scalar_multiply_buggy(lhs, rhs) result(multy)
      integer,      intent(IN)           :: lhs
      class(buggy), intent(IN)           :: rhs
      class(abstract_buggy), allocatable :: multy
      type(buggy),           allocatable :: multy_tmp

      allocate(buggy :: multy_tmp)
      multy_tmp%array = rhs%array * lhs
      multy_tmp%scalar = rhs%scalar
      call move_alloc(multy_tmp, multy)
      return
   endfunction scalar_multiply_buggy

   pure subroutine buggy_assign_buggy(lhs, rhs)
      class(buggy),          intent(INOUT) :: lhs
      class(abstract_buggy), intent(IN)    :: rhs

      select type(rhs)
         class is(buggy)
            if (allocated(rhs%array)) lhs%array = rhs%array
            lhs%scalar = rhs%scalar
      endselect
      return
   endsubroutine buggy_assign_buggy
endmodule type_buggy
program ifort_bug
   use lib_abstract_buggy, only : raise_bug
   use type_buggy, only : buggy
   implicit none
   type(buggy) :: bug

   bug = buggy(array=[1., 2., 3.], scalar=3)
   call raise_bug(bug=bug, scalar=2)
   stop
endprogram ifort_bug
Array:
 1.000000
 2.000000
 3.000000
Scalar:     3
Array:
 2.000000
 4.000000
 6.000000
Scalar:     3
Array:
 4.000000
 8.000000
 12.00000
Scalar:     3
Press any key to continue . . .

 

0 Kudos
Reply