Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs have moved to the Altera Community. Existing Intel Community members can sign in with their current credentials.
29317 Discussions

More annoying regressions in ifort 17.0

Juergen_R_R
Valued Contributor II
1,394 Views

Seems that v17 was not the most lucky of all releases. In our code, link, we now see several of our unit and functional tests producing double free or corruption errors or simply just hang. Note that you need OCaml to compile the code, but otherwise it is just ./configure, make, make check. Til roughly a year ago our code was regularly checked for regressions by a person of the Intel support, but with the stop the code doesn't work any more now. Maybe at some point I might provide a smaller test case, but I'm not so highly motivated to do so. 

 

 

 

0 Kudos
9 Replies
Kevin_D_Intel
Employee
1,394 Views

I'm sorry to learn there are new issues. I think the answer is probably "Yes", but to confirm, is the double free/corruption error occurring with 17.0 update 2?

I believe I know who the Intel person was so I will inquire whether that testing was continued by someone else.

Please let us know if you learn anything further about this issue.

0 Kudos
Juergen_R_R
Valued Contributor II
1,394 Views

Here is the reproducer (you need just an empty file sf_data_14.ref). With gfortran 4.8/4.9/5/6/7, ifort 16, PGF 17, nagfor 6 it works,

for ifort v17 it just hangs. 

module unit_tests
  implicit none
  private
  public :: unit_test
  public :: test

  abstract interface
     subroutine unit_test (u)
       integer, intent(in) :: u
     end subroutine unit_test
  end interface


contains

  subroutine test (test_proc, u_log)
    procedure(unit_test) :: test_proc
    integer, intent(in) :: u_log
    integer :: u_test, u_ref, u_err
    logical :: exist
    character(256) :: buffer1, buffer2
    integer :: iostat1, iostat2
    logical :: success
    write (*, "(A)", advance="no")  "Running test: "
    write (u_log, "(A)")  "Test: " 
    u_test = 12
    open (u_test, status="scratch", action="readwrite")
    call test_proc (u_test)
    rewind (u_test)
    inquire (file="sf_base_14.ref", exist=exist)
    if (exist) then
       u_ref = 13
       open (u_ref, file="sf_base_14.ref", status="old", action="read")
       COMPARE_FILES: do
          read (u_test, "(A)", iostat=iostat1)  buffer1
          read (u_ref, "(A)", iostat=iostat2)  buffer2
          if (iostat1 /= iostat2) then
             success = .false.
             exit COMPARE_FILES
          else if (iostat1 < 0) then
             success = .true.
             exit COMPARE_FILES
          else if (buffer1 /= buffer2) then
             success = .false.
             exit COMPARE_FILES
          end if
       end do COMPARE_FILES
       close (u_ref)
    else
       write (*, "(A)", advance="no") " ... no reference output available"
       write (u_log, "(A)") "  No reference output available."
       success = .false.
    end if
    write (*, "(A)") " ... success."
    write (u_log, "(A)")  "  Success."
    close (u_test)
  end subroutine test


end module unit_tests


!!!!!

module sf_base
  implicit none
  private

  public :: sf_data_t
  public :: sf_config_t
  public :: sf_int_t
  public :: sf_chain_t
  public :: sf_chain_instance_t

  type, abstract :: sf_data_t
   contains
     procedure (sf_data_get_int), deferred :: get_n_par
     procedure (sf_data_allocate_sf_int), deferred :: allocate_sf_int
  end type sf_data_t

  type :: sf_config_t
     integer, dimension(:), allocatable :: i
     class(sf_data_t), allocatable :: data
   contains
     procedure :: init => sf_config_init
  end type sf_config_t

  type, abstract :: sf_int_t
     real, dimension(:), allocatable :: mi2
     real, dimension(:), allocatable :: mr2
     real, dimension(:), allocatable :: mo2
     integer, dimension(:), allocatable :: beam_index
     integer, dimension(:), allocatable :: par_index
   contains
     procedure :: base_init => sf_int_base_init
     procedure (sf_int_init), deferred :: init
  end type sf_int_t

  type :: sf_instance_t
     class(sf_int_t), allocatable :: int
     real, dimension(:,:), allocatable :: r
     real, dimension(:), allocatable :: f
     logical, dimension(:), allocatable :: m
     real, dimension(:), allocatable :: x
  end type sf_instance_t

  type :: sf_chain_t
     integer :: n_in = 0
     integer :: n_strfun = 0
     integer :: n_par = 0
     integer :: n_bound = 0
     type(sf_instance_t), dimension(:), allocatable :: sf
   contains
     procedure :: init => sf_chain_init
     procedure :: set_strfun => sf_chain_set_strfun
     procedure :: get_n_par => sf_chain_get_n_par
  end type sf_chain_t

  type :: sf_chain_instance_t
     type(sf_chain_t), pointer :: config => null ()
     type(sf_instance_t), dimension(:), allocatable :: sf
     integer :: selected_channel = 0
     real, dimension(:,:), allocatable :: p, pb
     real, dimension(:,:), allocatable :: r
     real, dimension(:), allocatable :: f
     real, dimension(:), allocatable :: x
     logical, dimension(:), allocatable :: bound
   contains
     procedure :: init => sf_chain_instance_init
  end type sf_chain_instance_t


  abstract interface
     function sf_data_get_int (data) result (n)
       import
       class(sf_data_t), intent(in) :: data
       integer :: n
     end function sf_data_get_int
  end interface

  abstract interface
     subroutine sf_data_allocate_sf_int (data, sf_int)
       import
       class(sf_data_t), intent(in) :: data
       class(sf_int_t), intent(inout), allocatable :: sf_int
     end subroutine sf_data_allocate_sf_int
  end interface

  abstract interface
     subroutine sf_int_init (sf_int, data)
       import
       class(sf_int_t), intent(out) :: sf_int
       class(sf_data_t), intent(in), target :: data
     end subroutine sf_int_init
  end interface

contains

  subroutine sf_config_init (sf_config, i_beam, sf_data)
    class(sf_config_t), intent(out) :: sf_config
    integer, dimension(:), intent(in) :: i_beam
    class(sf_data_t), intent(in) :: sf_data
    allocate (sf_config%i (size (i_beam)), source = i_beam)
    allocate (sf_config%data, source = sf_data)
  end subroutine sf_config_init

  subroutine sf_int_base_init &
       (sf_int, mi2, mr2, mo2)
    class(sf_int_t), intent(out) :: sf_int
    real, dimension(:), intent(in) :: mi2, mr2, mo2
    allocate (sf_int%mi2 (size (mi2)))
    sf_int%mi2 = mi2
    allocate (sf_int%mr2 (size (mr2)))
    sf_int%mr2 = mr2
    allocate (sf_int%mo2 (size (mo2)))
    sf_int%mo2 = mo2
  end subroutine sf_int_base_init

  subroutine sf_chain_init (sf_chain, sf_config)
    class(sf_chain_t), intent(out) :: sf_chain
    type(sf_config_t), dimension(:), intent(in), optional, target :: sf_config
    integer :: i
    if (present (sf_config)) then
       sf_chain%n_strfun = size (sf_config)
       allocate (sf_chain%sf (sf_chain%n_strfun))
       do i = 1, sf_chain%n_strfun
          call sf_chain%set_strfun (i, sf_config(i)%i, sf_config(i)%data)
       end do
    end if
  end subroutine sf_chain_init

  subroutine sf_chain_set_strfun (sf_chain, i, beam_index, data)
    class(sf_chain_t), intent(inout) :: sf_chain
    integer, intent(in) :: i
    integer, dimension(:), intent(in) :: beam_index
    class(sf_data_t), intent(in), target :: data
    integer :: n_par, j
    n_par = data%get_n_par ()
    call data%allocate_sf_int (sf_chain%sf(i)%int)
    associate (sf_int => sf_chain%sf(i)%int)
      call sf_int%init (data)
      sf_chain%n_par = sf_chain%n_par + n_par
    end associate
  end subroutine sf_chain_set_strfun

  function sf_chain_get_n_par (sf_chain) result (n)
    class(sf_chain_t), intent(in) :: sf_chain
    integer :: n
    n = sf_chain%n_par
  end function sf_chain_get_n_par

  subroutine sf_chain_instance_init (chain, config, n_channel)
    class(sf_chain_instance_t), intent(out), target :: chain
    type(sf_chain_t), intent(in), target :: config
    integer, intent(in) :: n_channel
    integer :: i, j
    integer :: n_par_tot, n_par, n_strfun
    chain%config => config
    n_strfun = config%n_strfun
    n_par_tot = 0
    if (n_strfun /= 0) then
       allocate (chain%sf (n_strfun))
       do i = 1, n_strfun
          associate (sf => chain%sf(i))
            allocate (sf%int, source=config%sf(i)%int)
            n_par = size (sf%int%par_index)
            allocate (sf%m (n_channel));         sf%m = .false.
            allocate (sf%x (n_par));             sf%x = 0
            n_par_tot = n_par_tot + n_par
          end associate
       end do
       allocate (chain%p (n_par_tot, n_channel));  chain%p = 0
       allocate (chain%pb(n_par_tot, n_channel));  chain%pb= 0
    end if
    allocate (chain%bound (n_par_tot), source = .true.)
  end subroutine sf_chain_instance_init

end module sf_base


!!!!!

module sf_base_uti
  use sf_base
  implicit none
  private
  public :: sf_base_14

  type, extends (sf_data_t) :: sf_test_data_t
     integer :: mode = 0
     real :: m = 0
   contains
     procedure :: init => sf_test_data_init
     procedure :: get_n_par => sf_test_data_get_n_par
     procedure :: allocate_sf_int => sf_test_data_allocate_sf_int
  end type sf_test_data_t

  type, extends (sf_int_t) :: sf_test_t
     type(sf_test_data_t), pointer :: data => null ()
     real :: x = 0
   contains
     procedure :: init => sf_test_init
  end type sf_test_t

  type, extends (sf_data_t) :: sf_test_generator_data_t
     real :: m = 0
   contains
     procedure :: init => sf_test_generator_data_init
     procedure :: get_n_par => sf_test_generator_data_get_n_par
     procedure :: allocate_sf_int => &
          sf_test_generator_data_allocate_sf_int
  end type sf_test_generator_data_t

  type, extends (sf_int_t) :: sf_test_generator_t
     type(sf_test_generator_data_t), pointer :: data => null ()
   contains
     procedure :: init => sf_test_generator_init
  end type sf_test_generator_t


contains


  subroutine sf_base_14 (u)
    integer, intent(in) :: u
    class(sf_data_t), allocatable, target :: data_strfun
    class(sf_data_t), allocatable, target :: data_generator
    type(sf_config_t), dimension(:), allocatable, target :: sf_config
    real, dimension(:), allocatable :: p_in
    type(sf_chain_t), target :: sf_chain
    type(sf_chain_instance_t), target :: sf_chain_instance

    allocate (sf_test_data_t :: data_strfun)
    select type (data_strfun)
    type is (sf_test_data_t)
       call data_strfun%init ()
    end select
    allocate (sf_test_generator_data_t :: data_generator)
    select type (data_generator)
    type is (sf_test_generator_data_t)
       call data_generator%init ()
    end select

    allocate (sf_config (2))
    call sf_config(1)%init ([1,2], data_generator)
    call sf_config(2)%init ([2], data_strfun)

    call sf_chain%init (sf_config)
    call sf_chain_instance%init (sf_chain, n_channel = 1)
  end subroutine sf_base_14

  subroutine sf_test_data_init (data, mode)
    class(sf_test_data_t), intent(out) :: data
    integer, intent(in), optional :: mode
    if (present (mode))  data%mode = mode
  end subroutine sf_test_data_init

  function sf_test_data_get_n_par (data) result (n)
    class(sf_test_data_t), intent(in) :: data
    integer :: n
    n = 1
  end function sf_test_data_get_n_par

  subroutine sf_test_data_allocate_sf_int (data, sf_int)
    class(sf_test_data_t), intent(in) :: data
    class(sf_int_t), intent(inout), allocatable :: sf_int
    if (allocated (sf_int)) deallocate (sf_int)
    allocate (sf_test_t :: sf_int)
  end subroutine sf_test_data_allocate_sf_int

  subroutine sf_test_init (sf_int, data)
    class(sf_test_t), intent(out) :: sf_int
    class(sf_data_t), intent(in), target :: data
    select type (data)
    type is (sf_test_data_t)
       call sf_int%base_init (&
            [data%m**2], [0.], [data%m**2])
    end select
  end subroutine sf_test_init

  subroutine sf_test_generator_data_init (data)
    class(sf_test_generator_data_t), intent(out) :: data
  end subroutine sf_test_generator_data_init

  function sf_test_generator_data_get_n_par (data) result (n)
    class(sf_test_generator_data_t), intent(in) :: data
    integer :: n
    n = 2
  end function sf_test_generator_data_get_n_par

  subroutine sf_test_generator_data_allocate_sf_int (data, sf_int)
    class(sf_test_generator_data_t), intent(in) :: data
    class(sf_int_t), intent(inout), allocatable :: sf_int
    allocate (sf_test_generator_t :: sf_int)
  end subroutine sf_test_generator_data_allocate_sf_int

  subroutine sf_test_generator_init (sf_int, data)
    class(sf_test_generator_t), intent(out) :: sf_int
    class(sf_data_t), intent(in), target :: data
    select type (data)
    type is (sf_test_generator_data_t)
       call sf_int%base_init ( &
            [data%m**2, data%m**2], &
            [real :: ], &
            [data%m**2, data%m**2])
       sf_int%data => data
    end select
  end subroutine sf_test_generator_init

end module sf_base_uti

!!!!!

program main_ut
  use unit_tests
  use sf_base_uti, only: sf_base_14
  implicit none

  call test (sf_base_14, 11)
end program main_ut

 

 

0 Kudos
Juergen_R_R
Valued Contributor II
1,394 Views

I attached the file. I will also make an official bug report. So sad that this was so utterly screwed up. 

0 Kudos
Kevin_D_Intel
Employee
1,394 Views

Thank you for the test case. I will go investigate it. Please let me know the case # and I'll take ownership of that too and keep it updated as well.

0 Kudos
Juergen_R_R
Valued Contributor II
1,394 Views

Apparently, the new platform for filing reports is a lot uglier than the previous one. When can I not just create another ticket????

 

0 Kudos
Kevin_D_Intel
Employee
1,394 Views

You don't have to create another ticket. I can work with you via this forum post. I'll try out the reproducer and send it to Development and keep you updated via this thread.

0 Kudos
Juergen_R_R
Valued Contributor II
1,394 Views

Looks like the support number #02641369. 

0 Kudos
Juergen_R_R
Valued Contributor II
1,394 Views

And, there is more behind the corner. By using the test case on the very top (our full code), I get this:

You do have the reproducer for this as well, where you don't even need OCaml. Just download the link,

http://whizard.hepforge.org/versions/unofficial/whizard-2.4.1_alpha-20170131.tar.gz

do ./configure, make, make install. Then go to the build dir, tests/functional_tests, do 'make testproc_1.run` and

then ./testproc_1.run   produces the problem below (shall a file another official report here?)

| Reading model file '/home/reuter/local/packages/whizard/trunk/share/models/SM_hadrons.mdl'
| Reading commands from file 'testproc_1.sin'
| Reading model file '/home/reuter/local/packages/whizard/trunk/share/models/Test.mdl'
| Loading model auxiliary library '/home/reuter/local/packages/whizard/trunk/_build_ifort17/src/models/external.Test.so.0'
| Switching to model 'Test'
?logging => true
?openmp_logging = false
?vis_history = false
?integration_timer = false
$method = "unit_test"
process_num_id = 42
| Process library 'default_lib': recorded process 'testproc_1_p1' (42)
seed = 0
| Process library 'default_lib': compiling ...
| Process library 'default_lib': ... success.
$phs_method = "single"
$integration_method = "midpoint"
sqrts =  1.000000000000E+03
| RNG: Initializing TAO random-number generator
| RNG: Setting seed for random-number generator to 0
| Initializing integration for process testproc_1_p1:
| Beam structure: [any particles]
| Beam data (collision):
|   s  (mass = 1.2500000E+02 GeV)
|   s  (mass = 1.2500000E+02 GeV)
|   sqrts = 1.000000000000E+03 GeV
| ------------------------------------------------------------------------
| Process [scattering]: 'testproc_1_p1'
|   ID (num)      = 42
|   Library name  = 'default_lib'
|   Process index = 1
|   Process components:
|     1: 'testproc_1_p1_i1':   s, s => s, s [unit_test]
| ------------------------------------------------------------------------
| Phase space: 1 channels, 2 dimensions
| Phase space: single-particle
 Beam structure: [any particles]
Warning: No cuts have been defined.
*** Error in `/home/reuter/local/packages/whizard/trunk/_inst_ifort17/bin/whizard': double free or corruption (fasttop): 0x0000000000daa090 ***

Program received signal SIGABRT, Aborted.
0x00007fffef18dc37 in __GI_raise (sig=sig@entry=6) at ../nptl/sysdeps/unix/sysv/linux/raise.c:56
56    ../nptl/sysdeps/unix/sysv/linux/raise.c: No such file or directory.
(gdb) bt
#0  0x00007fffef18dc37 in __GI_raise (sig=sig@entry=6) at ../nptl/sysdeps/unix/sysv/linux/raise.c:56
#1  0x00007fffef191028 in __GI_abort () at abort.c:89
#2  0x00007fffef1ca2a4 in __libc_message (do_abort=do_abort@entry=1, fmt=fmt@entry=0x7fffef2d86b0 "*** Error in `%s': %s: 0x%s ***\n") at ../sysdeps/posix/libc_fatal.c:175
#3  0x00007fffef1d655e in malloc_printerr (ptr=<optimized out>, str=0x7fffef2d8878 "double free or corruption (fasttop)", action=1) at malloc.c:4996
#4  _int_free (av=<optimized out>, p=<optimized out>, have_lock=0) at malloc.c:3840
#5  0x000000000045e818 in for_dealloc_allocatable ()
#6  0x00007ffff48fa7bd in instances::term_instance_init (term=0xdb0f60, process=..., i_term=1, real_finite=.FALSE.) at instances.f90:509
#7  0x00007ffff49095e8 in instances::term_instance_init_from_process (term_instance=0xdb0f60, process=..., i=1, pcm_instance=..., sf_chain=...) at instances.f90:579
#8  0x00007ffff4954cba in instances::process_instance_init (instance=0xdb0320, process=...) at instances.f90:1584
#9  0x00007ffff3db95ce in integrations::integration_integrate (intg=0x7fffffff9d00, local=..., eff_reset=<error reading variable: Cannot access memory at address 0x0>)
    at integrations.f90:689
#10 0x00007ffff3dd00db in integrations::integrate_process (process_id=..., local=..., global=..., local_stack=<error reading variable: Cannot access memory at address 0x0>,
    init_only=<error reading variable: Cannot access memory at address 0x0>, eff_reset=<error reading variable: Cannot access memory at address 0x0>) at integrations.f90:880
#11 0x00007ffff3f16df8 in commands::cmd_integrate_execute (cmd=0xd68f60, global=...) at commands.f90:3124
#12 0x00007ffff3fe72d3 in commands::command_list_execute (cmd_list=0x7fffffffa7b0, global=...) at commands.f90:5862
#13 0x00007ffff4015121 in whizard::whizard_process_stream (whizard=0x789dc0, stream=..., lexer=..., quit=.FALSE., quit_code=0) at whizard.f90:348
#14 0x00007ffff4010644 in whizard::whizard_process_file (whizard=0x789dc0, file=..., quit=.FALSE., quit_code=0) at whizard.f90:323
#15 0x00007ffff7bcaba9 in main () at main.f90:415
#16 0x000000000040a71e in main ()

 

0 Kudos
Juergen_R_R
Valued Contributor II
1,394 Views

I submiited this a smaller reproducer (still couple of files though) with the report ticket #02641438.
I sincerely hope that this together with the other issue (which might [or might not] have the same root case), issue #2641369, will be fixed very soon. For the moment, we disabled usage with ifort 17 for our code. This is really annoying as ifort 16 (in all subversions) was after years the first ifort version that could compile and run our code as intended.

0 Kudos
Reply