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

overloaded assignment will induce a temporary rhs copy ......... possible bug

may_ka
Beginner
346 Views

Hi,

when running the following code I noticed that the memory locations differ when using the overloaded assignment or the bound procedure directly, where the bound procedure is behaving as expected. it implies that when using the operator a temporary copy of the rhs is made, although compiling with -check arg_tmp_created did not report anything. the results can be produced with ifort 19.04, 19.05, 19.1.0 and 19.1.1. When the same code is compiled with gfortran both, the overloaded assignment operator and the bound procedure produce the same output.

module mod_t1
  implicit none
  type :: t1
    integer, allocatable :: i1(:)
  contains
    generic, public :: assignment(=) => cpi1
    procedure, public :: cpi1 => subcpi1
  end type t1
contains
  subroutine subcpi1(this,i1i)
    class(t1), intent(inout) :: this
    integer, intent(in) :: i1i(:)
    write(*,*) loc(i1i(1)), loc(i1i(size(i1i)))
    if(allocated(this%i1)) deallocate(this%i1)
    allocate(this%i1,source=i1i)
  end subroutine subcpi1
end module mod_t1
program test
  use mod_t1
  implicit none
  integer, allocatable :: a(:)
  class(t1), allocatable :: t
  allocate(t);a=(/1,2,3/)
  write(*,*) loc(a(1)), loc(a(size(a)))
  call t%cpi1(a)
  t=a
end program test

the output from ifort is:

       35083136              35083144
       35083136              35083144
       140725714160336       140725714160344

from gfortran:

94244671338848       94244671338856
94244671338848       94244671338856
94244671338848       94244671338856

if the compiler invokes a temporary copy it may cause difficult to trace performance issues when using the operator. I suspect a bug in ifort but seek confirmation before I report to intel.

cheers

0 Kudos
3 Replies
IanH
Honored Contributor II
346 Views

The standard doesn't discuss implementation details such as whether temporaries in memory are created or not - it specifies how statements will operate using Fortran concepts such as the execution sequence for statements or how the value of variables will change.

The standard specifies that the right hand side of an defined assignment statement is treated as if it was a parenthesised expression prior to the actual and dummy arguments being associated (F2018 15.4.3.4.3).  This is to avoid aliasing issues that would otherwise apply for a direct procedure call without parentheses, if the left and right hand sides of the assignment statement involved a common object in some way.  One way of implementing the handling of a parenthesised expression is to create a temporary.  Doing this regardless of whether there is the potential for a common object on the left and right hand sides of the assignment is not particularly efficient, but it does the job.

I have open bug reports (59202) with gfortran due to a failure to correctly handle left and right hand side parts of an assignment statement that are aliased.    Not creating a temporary in those cases is efficient from an execution point of view, but broken.

0 Kudos
may_ka
Beginner
346 Views

Thanks.

What means a common object?

If I expand the code to

module mod_t1
  implicit none
  type :: t1
    integer, allocatable :: i1(:)
  contains
    generic, public :: assignment(=) => cpi1,cpi2
    procedure, public :: cpi1 => subcpi1
    procedure, public :: cpi2 => subcpi2
  end type t1
contains
  subroutine subcpi1(this,i1i)
    class(t1), intent(inout) :: this
    integer, intent(in) :: i1i(:)
    write(*,*) loc(i1i(1)), loc(i1i(size(i1i)))
    if(allocated(this%i1)) deallocate(this%i1)
    allocate(this%i1,source=i1i)
  end subroutine subcpi1
  subroutine subcpi2(this,ot)
    class(t1), intent(inout) :: this
    class(t1), intent(in) :: ot
    write(*,*) loc(ot), loc(ot)
    if(allocated(this%i1)) deallocate(this%i1)
    allocate(this%i1,source=ot%i1)
  end subroutine subcpi2
end module mod_t1
program test
  use mod_t1
  implicit none
  integer, allocatable :: a(:)
  class(t1), allocatable :: x,y
  allocate(x,y);a=(/1,2,3/)
  write(*,*) loc(a(1)), loc(a(size(a)))
  call x%cpi1(a)
  x=a
  write(*,*) loc(x), loc(x)
  call y%cpi2(x)
  y=x
end program test

I get

              9892864               9892872
               9892864               9892872
       140732849527360       140732849527368
               9892608               9892608
               9892608               9892608
               9892608               9892608

which suggest when the operator is used between objects of the same class no temporary copy is made.

is this still consistent with what you wrote above?

0 Kudos
IanH
Honored Contributor II
346 Views

By common object I mean something (or part of something) that appears on both the left and right hand sides of the assignment statement.

Behaviour in the second example is consistent - if a temporary is not required to implement the semantics required by the standard, there's no requirement to create a temporary.  But the example is not sufficient to test the compiler is doing the right thing.

It is possible for a compiler (and this is the sort of thing I would expect ifort to do) to analyse the semantics in the code invoking the defined assignment and determine that there is no possibility of aliasing between x and y (x and y are both allocatable local variables).  If there is no possibility of aliasing, then a temporary is not required.

But ifort is not doing that analysis (or is not doing it correctly) - it is not defending against aliasing in circumstances where it needs to - the behaviour in the following, where there is aliasing, demonstrates a compiler bug for the polymorphic case (note the repeated 3 in the output).  In the non-polymorphic case the compiler has identified that the left and right are aliased, and has appropriately created a temporary.

 

module mod_t1
  implicit none
  type :: t1
    integer :: i1(3)
  contains
    generic, public :: assignment(=) => cpi2
    procedure, public :: cpi2 => subcpi2
  end type t1
contains
  subroutine subcpi2(this,ot)
    class(t1), intent(inout) :: this
    class(t1), intent(in) :: ot
    
    integer :: i
    
    write(*,"(*(Z16.16,:,1X))") loc(ot%i1)
    
    ! Flip the order - if the arguments are aliased this may 
    ! demonstrate an issue.
    do i = 1, size(this%i1)
      this%i1(i) = ot%i1(size(ot%i1)-i+1)
    end do
  end subroutine subcpi2
end module mod_t1

program test
  use mod_t1
  implicit none
  class(t1), allocatable :: x
  type(t1), allocatable :: y
  
  allocate(x, y)
  
  x%i1 = [1, 2, 3]
  write(*,"(*(Z16.16,:,1X))") loc(x%i1)
  x=x        ! x=(x) gives an ICE
  print *, x%i1
  
  y%i1 = [1, 2, 3]
  write(*,"(*(Z16.16,:,1X))") loc(y%i1)
  y=y
  print *, y%i1
end program test

 

 

>ifort /Od /warn:all /check:all /traceback "2020-04-15 defined-assignment-2.f90" && "2020-04-15 defined-assignment-2.exe"
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 19.1.1.216 Build 20200306
Copyright (C) 1985-2020 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.25.28612.0
Copyright (C) Microsoft Corporation.  All rights reserved.

"-out:2020-04-15 defined-assignment-2.exe"
-subsystem:console
-incremental:no
"2020-04-15 defined-assignment-2.obj"
0000018DC2FA3930
0000018DC2FA3930
           3           2           3
0000018DC2FA3960
00000009AE3DF680
           3           2           1

 

0 Kudos
Reply