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

IPO optimization failure at run with generic type-bound procedures ??

Frederic_C_
Beginner
361 Views

Dear everyone,

I found a possible big bug in ipo optimzation using "sophisticated" derived type with generic-type bound procedures

Find the codes here,

MODULE m_vec2d

   USE, intrinsic :: iso_fortran_env

   implicit none

   integer, parameter :: ip = INT32
   integer, parameter :: rp = REAL64

   TYPE vec2d

      real(rp) :: x = 0._rp
      real(rp) :: y = 0._rp

   CONTAINS

      procedure, pass( self ) :: equal_vec2d
      procedure               :: rot_vec2d
      procedure               :: invrot_vec2d

      generic :: assignment(=) => equal_vec2d

      generic :: operator(.rot.)     => rot_vec2d
      generic :: operator(.invrot.)  => invrot_vec2d

   END TYPE vec2d

CONTAINS

   ELEMENTAL SUBROUTINE equal_vec2d( self , from )

      class(vec2d), intent(inout) :: self

      type(vec2d), intent(in) :: from

      self%x = from%x
      self%y = from%y

   END SUBROUTINE equal_vec2d

   ELEMENTAL FUNCTION rot_vec2d( self , n ) RESULT( this )

      class(vec2d), intent(in) :: self , n

      type(vec2d) :: this

      this%x = self%x * n%x + self%y * n%y
      this%y = self%y * n%x - self%x * n%y

   END FUNCTION rot_vec2d

   ELEMENTAL FUNCTION invrot_vec2d( self , n ) RESULT( this )

      class(vec2d), intent(in) :: self , n

      type(vec2d) :: this

      this%x = self%x * n%x - self%y * n%y
      this%y = self%y * n%x + self%x * n%y

   END FUNCTION invrot_vec2d

END MODULE m_vec2d
MODULE m_model

   USE m_vec2d

   implicit none

   TYPE primvar

      real(rp) :: h

      type(vec2d) :: u

   CONTAINS

      procedure, pass( self ) :: equal_primvar
      procedure, pass( self ) :: rot_primvar
      procedure, pass( self ) :: invrot_primvar

      generic :: assignment(=) => equal_primvar

      generic :: operator(.rot.)     => rot_primvar
      generic :: operator(.invrot.)  => invrot_primvar

   END TYPE primvar

   TYPE unk

      type(primvar), allocatable :: var(:)

   END TYPE unk

CONTAINS

   ELEMENTAL SUBROUTINE equal_primvar( self , from )

      class(primvar), intent(inout) :: self

      type(primvar), intent(in) :: from

      self%h   = from%h
      self%u%x = from%u%x
      self%u%y = from%u%y

   END SUBROUTINE equal_primvar

   ELEMENTAL FUNCTION rot_primvar( self , normal ) RESULT( this )

      class(primvar), intent(in) :: self

      type(vec2d), intent(in) :: normal

      type(primvar) :: this

      this%h = self%h
      this%u = self%u .rot. normal

   END FUNCTION rot_primvar

   ELEMENTAL FUNCTION invrot_primvar( self , normal ) RESULT( this )

      class(primvar), intent(in) :: self

      type(vec2d), intent(in) :: normal

      type(primvar) :: this

      this%h = self%h
      this%u = self%u .invrot. normal

   END FUNCTION invrot_primvar

END MODULE m_model
PROGRAM main

   USE m_vec2d
   USE m_model

   implicit none

   integer(ip), parameter :: n = 10

   integer(ip) :: i

   type(vec2d) :: normal , flux

   type(unk) :: dof

   type(primvar) :: x

   allocate( dof%var(n) )

   normal%x = 1._rp / sqrt(2._rp)
   normal%y = 1._rp / sqrt(2._rp)

   dof%var(:)%h   = 1._rp
   dof%var(:)%u%x = 1._rp
   dof%var(:)%u%y = 2._rp

   do i = 1,n

      x = dof%var(i) .rot. normal

      x = x .invrot. normal

   end do

   do i = 1,n

      write(6,*) x%h , x%u%x , x%u%y

   end do

END PROGRAM

At execution, the vector part of my primvar structure is set to zero ! whereas normal result is produced without ipo compilation option as with gfortran with or without lfto compilation option

there seems to be something bad in interprocedural optimization with an inter dependency of two structures separated in two source files (primvar derivedtype rot and invrot operators depend on the derived type vec2d rot and invrot operators)

ifort --version
ifort (IFORT) 18.0.2 20180210
Copyright (C) 1985-2018 Intel Corporation.  All rights reserved.

Note a normal result with the version 17 ... don't know with last version 19 ...

0 Kudos
3 Replies
Juergen_R_R
Valued Contributor I
361 Views

Dear Frederic,

I didn't go through your code in detail, but only noticed that the code gives the results 1, 1, 2   (10 times) with ifort 19, gfortran 5.4, nagfor 6.2 and PGI fortran 18.7. With ifort 17.0.8 and 18.0.5 it gives different results. So this could possibly be an old bug in ifort that has been fixed for the 19 release series.

Cheers,

      Juergen

0 Kudos
Frederic_C_
Beginner
361 Views

Juergen R. wrote:

Dear Frederic,

I didn't go through your code in detail, but only noticed that the code gives the results 1, 1, 2   (10 times) with ifort 19, gfortran 5.4, nagfor 6.2 and PGI fortran 18.7. With ifort 17.0.8 and 18.0.5 it gives different results. So this could possibly be an old bug in ifort that has been fixed for the 19 release series.

Cheers,

      Juergen

Thanks very much, you confirm the issue ...

I just find a way to resolve the problem reducing the = assigment for the primvar derived type to self%u = from%u

very strange optimization bug

0 Kudos
Frederic_C_
Beginner
361 Views

Frederic C. wrote:

Quote:

Juergen R. wrote:

 

Dear Frederic,

I didn't go through your code in detail, but only noticed that the code gives the results 1, 1, 2   (10 times) with ifort 19, gfortran 5.4, nagfor 6.2 and PGI fortran 18.7. With ifort 17.0.8 and 18.0.5 it gives different results. So this could possibly be an old bug in ifort that has been fixed for the 19 release series.

Cheers,

      Juergen

 

 

Thanks very much, you confirm the issue ...

I just find a way to resolve the problem reducing the = assigment for the primvar derived type to self%u = from%u

very strange optimization bug

edit: no, the bug is already here with this manipulation

not for this example, much more complex ...

I must strictly not overload operators with dependant other overload to use ipo optimization ...

0 Kudos
Reply