[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-12-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #47 from Paul Thomas  ---
Author: pault
Date: Fri Dec 21 20:58:59 2018
New Revision: 267342

URL: https://gcc.gnu.org/viewcvs?rev=267342=gcc=rev
Log:
2018-12-21  Paul Thomas  

PR fortran/87359
* trans-array.c (gfc_is_reallocatable_lhs): Correct the problem
introduced by r264358, which prevented components of associate
names from being reallocated on assignment.


2018-12-21  Paul Thomas  

PR fortran/87359
* gfortran.dg/associate_40.f90 : New test.


Added:
branches/gcc-8-branch/gcc/testsuite/gfortran.dg/associate_40.f90
Modified:
branches/gcc-8-branch/gcc/fortran/ChangeLog
branches/gcc-8-branch/gcc/fortran/trans-array.c
branches/gcc-8-branch/gcc/testsuite/ChangeLog

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-10-01 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

Jürgen Reuter  changed:

   What|Removed |Added

 Status|REOPENED|RESOLVED
 Resolution|--- |FIXED

--- Comment #46 from Jürgen Reuter  ---
Checked (again) that with our code which triggered this reproducer everything
works fine again, taking as reference r264725.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-30 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #45 from Paul Thomas  ---
Author: pault
Date: Sun Sep 30 13:52:55 2018
New Revision: 264725

URL: https://gcc.gnu.org/viewcvs?rev=264725=gcc=rev
Log:
2018-09-30  Paul Thomas  

PR fortran/87359
* trans-array.c (gfc_is_reallocatable_lhs): Correct the problem
introduced by r264358, which prevented components of associate
names from being reallocated on assignment.


2018-09-30  Paul Thomas  

PR fortran/87359
* gfortran.dg/associate_40.f90 : New test.


Added:
trunk/gcc/testsuite/gfortran.dg/associate_40.f90
Modified:
trunk/gcc/fortran/ChangeLog
trunk/gcc/fortran/trans-array.c
trunk/gcc/testsuite/ChangeLog

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-28 Thread paul.richard.thomas at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #44 from paul.richard.thomas at gmail dot com  ---
Hi Jeurgen,

Thanks for the confirmation. I will take care of a composite fix over
the weeknd. (I get home tomorrow lunchtime.).

Cheers

Paul

On Fri, 28 Sep 2018 at 11:13, juergen.reuter at desy dot de
 wrote:
>
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359
>
> --- Comment #43 from Jürgen Reuter  ---
> I just checked that Paul's fix actually solves all problems that our code had
> with the current trunk of gcc/gfortran as of r264501.
>
> --
> You are receiving this mail because:
> You are on the CC list for the bug.
> You are the assignee for the bug.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-28 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #43 from Jürgen Reuter  ---
I just checked that Paul's fix actually solves all problems that our code had
with the current trunk of gcc/gfortran as of r264501.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-25 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #42 from Paul Thomas  ---
Created attachment 44746
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44746=edit
Patch for the PR

Many thanks Juergen for the reduced test. This is now DEJA-GNUified (see
below).

The patch regtests OK. Note that I cannot commit this until next week.

(Thomas or Dominique, are you in a position to do the honours?)

Best regards

Paul

! { dg-do compile }
! { dg-options "-fdump-tree-original" }
!
! Test the fix for the second part of PR87359 in which the reallocation on
! assignment for components of associate names was disallowed by r264358.
! -fcheck-all exposed the mismatch in array shapes.
!
! Contributed by Juergen Reuter  
!
module phs_fks
  implicit none
  private
  public :: phs_identifier_t
  public :: phs_fks_t
  type :: phs_identifier_t
 integer, dimension(:), allocatable :: contributors
  contains
procedure :: init => phs_identifier_init
  end type phs_identifier_t

  type :: phs_fks_t
 type(phs_identifier_t), dimension(:), allocatable :: phs_identifiers
  end type phs_fks_t
contains

  subroutine phs_identifier_init &
 (phs_id, contributors)
 class(phs_identifier_t), intent(out) :: phs_id
 integer, intent(in), dimension(:) :: contributors
 allocate (phs_id%contributors (size (contributors)))
 phs_id%contributors = contributors
   end subroutine phs_identifier_init

end module phs_fks

!

module instances
  use phs_fks
  implicit none
  private
  public :: process_instance_t

  type :: nlo_event_deps_t
 type(phs_identifier_t), dimension(:), allocatable :: phs_identifiers
  end type nlo_event_deps_t

  type :: process_instance_t
 type(phs_fks_t), pointer :: phs => null ()
 type(nlo_event_deps_t) :: event_deps
   contains
 procedure :: init => process_instance_init
 procedure :: setup_real_event_kinematics => pi_setup_real_event_kinematics
  end type process_instance_t

contains

  subroutine process_instance_init (instance)
class(process_instance_t), intent(out), target :: instance
integer :: i
integer :: i_born, i_real
print *, "Process instance init"
allocate (instance%phs)
  end subroutine process_instance_init

  subroutine pi_setup_real_event_kinematics (process_instance)
class(process_instance_t), intent(inout) :: process_instance
integer :: i_real, i
associate (event_deps => process_instance%event_deps)
   i_real = 2
   associate (phs => process_instance%phs)
  print *, "Type is phs_fks_t"
  allocate (phs%phs_identifiers (3))
  call phs%phs_identifiers(1)%init ([1])
  call phs%phs_identifiers(2)%init ([1,2])
  call phs%phs_identifiers(3)%init ([1,2,3])
  event_deps%phs_identifiers = phs%phs_identifiers  ! Error: mismatch
in array shapes.
   end associate
end associate
  end subroutine pi_setup_real_event_kinematics

end module instances

!

program main
  use instances, only: process_instance_t
  implicit none
  type(process_instance_t), allocatable, target :: process_instance
  allocate (process_instance)
  call process_instance%init ()
  call process_instance%setup_real_event_kinematics ()
end program main
! { dg-final { scan-tree-dump-times "__builtin_realloc" 2 "original" } }

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-25 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #41 from Paul Thomas  ---
(In reply to Jürgen Reuter from comment #40)
> (In reply to Dominique d'Humieres from comment #39)
> > The culprit for the second problem is r264358, exposed only once the
> > original problem is fixed, i.e. with the patch of r264485 (tested on both
> > reproducers).
> > 
> > It would have been better to open a new PR for it, but it's probably too
> > late!-(
> 
> Yes, I left this open to Paul. You could still disentangle, you have my
> blessings.

The problem is caused by my being too brutal in gfc_is_reallocatable_lhs. I
have a patch which is just now regtesting. I will post it here once it is done.

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-25 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #40 from Jürgen Reuter  ---
(In reply to Dominique d'Humieres from comment #39)
> The culprit for the second problem is r264358, exposed only once the
> original problem is fixed, i.e. with the patch of r264485 (tested on both
> reproducers).
> 
> It would have been better to open a new PR for it, but it's probably too
> late!-(

Yes, I left this open to Paul. You could still disentangle, you have my
blessings.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-25 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #39 from Dominique d'Humieres  ---
The culprit for the second problem is r264358, exposed only once the original
problem is fixed, i.e. with the patch of r264485 (tested on both reproducers).

It would have been better to open a new PR for it, but it's probably too
late!-(

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-25 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #38 from Jürgen Reuter  ---
Created attachment 44745
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44745=edit
Small reproducer for the second problem

And an 89 line small reproducer for the second problem.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-25 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #37 from Jürgen Reuter  ---
Paul, here is a simple reproducer of 89 lines, this should now make it
relatively
easy to debug, I am using gcc trunk revision r264501.
Here is the code (I will also attach it), it contains also a workaround for the
runtime error:
module phs_fks
  implicit none
  private
  public :: phs_identifier_t
  public :: phs_fks_t
  type :: phs_identifier_t
 integer, dimension(:), allocatable :: contributors
  contains
procedure :: init => phs_identifier_init
  end type phs_identifier_t

  type :: phs_fks_t
 type(phs_identifier_t), dimension(:), allocatable :: phs_identifiers
  end type phs_fks_t
contains

  subroutine phs_identifier_init &
 (phs_id, contributors)
 class(phs_identifier_t), intent(out) :: phs_id
 integer, intent(in), dimension(:) :: contributors
 allocate (phs_id%contributors (size (contributors)))
 phs_id%contributors = contributors
   end subroutine phs_identifier_init

end module phs_fks

!

module instances
  use phs_fks
  implicit none
  private
  public :: process_instance_t

  type :: nlo_event_deps_t
 type(phs_identifier_t), dimension(:), allocatable :: phs_identifiers
  end type nlo_event_deps_t

  type :: process_instance_t
 type(phs_fks_t), pointer :: phs => null ()
 type(nlo_event_deps_t) :: event_deps 
   contains
 procedure :: init => process_instance_init
 procedure :: setup_real_event_kinematics => pi_setup_real_event_kinematics
  end type process_instance_t

contains

  subroutine process_instance_init (instance)
class(process_instance_t), intent(out), target :: instance
integer :: i
integer :: i_born, i_real
print *, "Process instance init"
allocate (instance%phs)
  end subroutine process_instance_init

  subroutine pi_setup_real_event_kinematics (process_instance)
class(process_instance_t), intent(inout) :: process_instance
integer :: i_real, i
associate (event_deps => process_instance%event_deps)
   i_real = 2 
   associate (phs => process_instance%phs)
  print *, "Type is phs_fks_t"
  allocate (phs%phs_identifiers (3))
  call phs%phs_identifiers(1)%init ([1])
  call phs%phs_identifiers(2)%init ([1,2])
  call phs%phs_identifiers(3)%init ([1,2,3])  
  event_deps%phs_identifiers = phs%phs_identifiers
   Workaround
  ! allocate (event_deps%phs_identifiers (size (phs%phs_identifiers)))
  ! do i = 1, size (phs%phs_identifiers)
  !event_deps%phs_identifiers(i) = phs%phs_identifiers(i)
  ! end do  
   end associate
end associate
  end subroutine pi_setup_real_event_kinematics

end module instances

!

program main
  use instances, only: process_instance_t
  implicit none  
  type(process_instance_t), allocatable, target :: process_instance
  allocate (process_instance)
  call process_instance%init ()
  call process_instance%setup_real_event_kinematics () 
end program main

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-24 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #36 from Dominique d'Humieres  ---
> The test succeeds with r264348+patch of r264485, but not with r264349+patch.

I make a mistake in my bissection: r264349+patch is OK as well as
r264357+patch, but not r264358+patch.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-24 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #35 from Jürgen Reuter  ---
(In reply to Dominique d'Humieres from comment #34)
> > Created attachment 44739 [details]
> > Reproducer for the second problem.
> 
> The test succeeds with r264348+patch of r264485, but not with r264349+patch.
> 
> IMO it would be better to open a new PR for it (and close this one as FIXED).


I am working with r264501 at the moment. I am in the procedure of further
reducing the reproducer but I think it is rather obvious what goes wrong.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-24 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #34 from Dominique d'Humieres  ---
> Created attachment 44739 [details]
> Reproducer for the second problem.

The test succeeds with r264348+patch of r264485, but not with r264349+patch.

IMO it would be better to open a new PR for it (and close this one as FIXED).

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-23 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #33 from Jürgen Reuter  ---
Created attachment 44739
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44739=edit
Reproducer for the ICE.

Paul, here is a first (still massive) reproducer of the second problem. Though
it is still big, it is stripped from the whole configure and dynamic library
infrastructure of our code, and it doesn't need any generated Fortran code via
our OCaml-written code generator. I'll try to reduce it a little further.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-22 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #32 from Jürgen Reuter  ---
Paul, I found a workaround: in lines 530-533 in the file
src/transforms/evt_nlo.f90 there is an assignment of an allocatable array of
different DT components which apparently doesn't work any more. Changing 
   530 select type (phs => process_instance%term(i_real)%k_term%phs)
   531 type is (phs_fks_t)
   532event_deps%phs_identifiers = phs%phs_identifiers
   533 end select
into 
   530 select type (phs => process_instance%term(i_real)%k_term%phs)
   531 type is (phs_fks_t)
   532allocate (event_deps%phs_identifiers (size
(phs%phs_identifiers)))
   533do i = 1, size (phs%phs_identifiers)
   534   event_deps%phs_identifiers(i) = phs%phs_identifiers(i)
   535end do
   536! event_deps%phs_identifiers = phs%phs_identifiers
   537 end select
solves the issue of all four failing tests. 
phs_identifiers is an allocatable array of type phs_identifier_t as defined in
the type
nlo_event_deps_t (lines 62-72 of evt_nlo.f90).
integer, dimension(:), allocatable :: phs_identifiers
And the type phs_identifier_t is defined in src/phase_space/phs_fks.f90, lines
264-275:
   264type :: phs_identifier_t
   265   integer, dimension(:), allocatable :: contributors
   266   integer :: emitter = -1
   267   logical :: evaluated = .false.
   268contains
   269  generic :: init => init_from_emitter,
init_from_emitter_and_contributors
   270  procedure :: init_from_emitter => phs_identifier_init_from_emitter
   271  procedure :: init_from_emitter_and_contributors &
   272 => phs_identifier_init_from_emitter_and_contributors
   273  procedure :: check => phs_identifier_check
   274  procedure :: write => phs_identifier_write
   275end type phs_identifier_t
So it has an allocatable integer array as DT component. Maybe gfortran hiccups
on the allocation-on-assigment of something that is an allocatable DT with
allocatable DT components?

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-22 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #31 from Jürgen Reuter  ---
That is really strange, I never used fink, I use macports. But not for gcc, I
always compile them by myself on MACOSX. Clearly the C/Fortran I/O doesn't work
properly, the string parsing doesn't work properly in the main.f90 file of
WHIZARD, to be found in src/whizard-core. The PGI compiler had this problem for
1-2 years with our code. We are testing our code in a CI with gcc-8.2,
everything is fine there. I don't know whether the fink build is ok, though.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-22 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #30 from Dominique d'Humieres  ---
> This is really strange, is that after Paul's fix?

It is with gfortran 8.2 (from fink).

> This seems to be a hiccup with the I/O. Did you use gcc or clang
> as the underlying C compiler?

I use gcc.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-22 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #29 from Jürgen Reuter  ---
(In reply to Dominique d'Humieres from comment #28)
> I am trying to install a clean whizard-2.6.4 on x86_64-apple-darwin17, Xcode
> 9.4.1, SIP disabled, gfortran 8.2, ocaml 4.03.0. I got the following errors
> with make check:
> 
> FAIL: mci_vamp.run
> FAIL: integrations.run
> FAIL: simulations.run
> FAIL: integrations_history.run
> 
> Testsuite summary for WHIZARD 2.6.4
> 
> # TOTAL: 125
> # PASS:  113
> # SKIP:  8
> # XFAIL: 0
> # FAIL:  4
> # XPASS: 0
> # ERROR: 0


This is really strange, is that after Paul's fix?

> 
> FAIL: empty.run
> FAIL: fatal.run
> FAIL: structure_1.run
> ...
> FAIL: pythia6_1.run
> FAIL: pythia6_2.run
> FAIL: pythia6_3.run
> ...
> ==
>WHIZARD 2.6.4: tests/functional_tests/test-suite.log
> ==
> 
> # TOTAL: 277
> # PASS:  1
> # SKIP:  38
> # XFAIL: 2
> # FAIL:  235
> # XPASS: 1
> # ERROR: 0
> 
> The later seems due to
> 
> *** FATAL ERROR:  Option '--logfile' needs a value
> 
> Is this expected?
> 
> What is the recommended way to change the fortran compiler?

This seems to be a hiccup with the I/O. Did you use gcc or clang as the
underlying C compiler? I use GNU gcc, g++ and gfortran as underlying compilers,
I don't have to specify them because they are all in the dominant paths. When
you build WHIZARD, you specify they compilers by ../configure
FC= CC= CXX=<...>  FCFLAGS=<...>  
(optional F77=<...>, we have some legacy code from our field included).

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-22 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #28 from Dominique d'Humieres  ---
I am trying to install a clean whizard-2.6.4 on x86_64-apple-darwin17, Xcode
9.4.1, SIP disabled, gfortran 8.2, ocaml 4.03.0. I got the following errors
with make check:

FAIL: mci_vamp.run
FAIL: integrations.run
FAIL: simulations.run
FAIL: integrations_history.run

Testsuite summary for WHIZARD 2.6.4

# TOTAL: 125
# PASS:  113
# SKIP:  8
# XFAIL: 0
# FAIL:  4
# XPASS: 0
# ERROR: 0

FAIL: empty.run
FAIL: fatal.run
FAIL: structure_1.run
...
FAIL: pythia6_1.run
FAIL: pythia6_2.run
FAIL: pythia6_3.run
...
==
   WHIZARD 2.6.4: tests/functional_tests/test-suite.log
==

# TOTAL: 277
# PASS:  1
# SKIP:  38
# XFAIL: 2
# FAIL:  235
# XPASS: 1
# ERROR: 0

The later seems due to

*** FATAL ERROR:  Option '--logfile' needs a value

Is this expected?

What is the recommended way to change the fortran compiler?

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #27 from Jürgen Reuter  ---
Interesting: when I run with checking flags, I get the following error:
At line 532 of file evt_nlo.f90
Fortran runtime error: Array bound mismatch for dimension 1 of array
'event_deps' (0/2)
However, I have been running also with these flags since ages, and this never
raised a problem!?
The problem seems indeed to happen in the module src/transforms/evt_nlo.f90 
in the following 
subroutine subroutine evt_nlo_setup_real_event_kinematics (evt,
process_instance)
class(evt_nlo_t), intent(inout) :: evt
type(process_instance_t), intent(in) :: process_instance
integer :: n_real, n_phs
integer :: i_real
print *, "inside evt_nlo_setup_real_event_kinematics"
associate (event_deps => evt%event_deps)
   select type (pcm => process_instance%pcm)
   class is (pcm_instance_nlo_t)
  n_real = pcm%get_n_real ()
   end select
   print *, "n_real = ", n_real
   i_real = evt%process%get_first_real_term ()
   print *, "first real term = ", i_real
   select type (phs => process_instance%term(i_real)%k_term%phs)  
   type is (phs_fks_t)
  print *, "size (identif.) = ", size (phs%phs_identifiers)  
  event_deps%phs_identifiers = phs%phs_identifiers
   end select
   n_phs = size (event_deps%phs_identifiers)
   print *, "n_phs = ", n_phs
   call event_deps%p_real_cms%init (n_real, n_phs)
   print *, "init p_real_cms"
   call event_deps%p_real_lab%init (n_real, n_phs)
   print *, "init p_real_lab"
   select type (pcm => process_instance%pcm)
   type is (pcm_instance_nlo_t)
  select type (config => pcm%config)
  type is (pcm_nlo_t)
 if (allocated (config%region_data%alr_contributors)) then
allocate (event_deps%contributors (size
(config%region_data%alr_contributors)))
event_deps%contributors = config%region_data%alr_contributors
print *, size (config%region_data%alr_contributors)
 end if 
 if (allocated (config%region_data%alr_to_i_contributor)) then
allocate (event_deps%alr_to_i_con &
   (size (config%region_data%alr_to_i_contributor)))
event_deps%alr_to_i_con =
config%region_data%alr_to_i_contributor
 end if
  end select
   end select
end associate
  end subroutine evt_nlo_setup_real_event_kinematics

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread paul.richard.thomas at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #26 from paul.richard.thomas at gmail dot com  ---
Jeurgen,

We are extremely pleased that you do follow developments on trunk. It
really helps to catch regressions early, while the changes are fresh
in mind :-)

Sometime, I would appreciate a briefing on what you are up to. I left
high energy theory when lattice QCD calculations were just starting.

Cheers

Paul


On 21 September 2018 at 19:32, juergen.reuter at desy dot de
 wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359
>
> --- Comment #24 from Jürgen Reuter  ---
> Paul, enjoy your time in Wales. Maybe this other issue wasn't caused by 
> r263916
> but by something else (though it must have been also in the past 2-3 weeks).
> What our functional tests do: they call a code generator (written in OCaml) to
> generate Fortran code, compile it and link it into a dynamical library. This 
> is
> then run by the main program, does a Monte Carlo integration. I'll try to find
> out as much as possible but my time is limited the next 1-2 weeks. On my
> university computers I am working with older versions (5.4 mainly because of
> Ubuntu 16), so no problem in my current work. I only follow the strategy on my
> laptop to follow the gcc development closely to catch possible issues before
> your official releases.
>
> --
> You are receiving this mail because:
> You are on the CC list for the bug.
> You are the assignee for the bug.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #25 from Jürgen Reuter  ---
This is the part from the test-suite.log for the 4 failures, they are all in
one particular feature of our code, so I am pretty sure that this is only one
remaining open issue:
| Starting simulation for process 'nlo_4_p1'
| Simulate: using integration grids from file 'nlo_4_p1.m1.vg'
| Simulate: activating fixed-order NLO events
| QCD alpha: using a running strong coupling

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #24 from Jürgen Reuter  ---
Paul, enjoy your time in Wales. Maybe this other issue wasn't caused by r263916
but by something else (though it must have been also in the past 2-3 weeks).
What our functional tests do: they call a code generator (written in OCaml) to
generate Fortran code, compile it and link it into a dynamical library. This is
then run by the main program, does a Monte Carlo integration. I'll try to find
out as much as possible but my time is limited the next 1-2 weeks. On my
university computers I am working with older versions (5.4 mainly because of
Ubuntu 16), so no problem in my current work. I only follow the strategy on my
laptop to follow the gcc development closely to catch possible issues before
your official releases.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #23 from Paul Thomas  ---
(In reply to Jürgen Reuter from comment #21)
> In our functional test suite, the tests nlo_4, nlo_5, fks_res_1 and another
> test are still failing, they lead to segmentation faults. This will be
> really difficult to isolate, but maybe this is a different root cause!?

Hi Juergen,

If it is a different root cause, reverting to pre-r263916 might be a good
first-order check.

I'll set up to run your testsuite when I am back.

Cheers

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #22 from Paul Thomas  ---
(In reply to Jürgen Reuter from comment #20)
> Paul, thanks for the fix, our code test suite is still running, most of the
> problems are solved, the unit test suite is completely good now, but there
> are certain functional tests failing. This will be really, really hard to
> give you a small reproducer. I reopened, you can decide whether you want it
> on this PR or a new one.

Hi Juergen,

Blast! I am afraid that I am now away on a small break in Wales for the next
week. I suggest that you revert to pre-r263916 or reverse patch r263916 to keep
yourself moving forward. I'll give your new problems my full attention when I
return.

I apologise for the inconvenience.

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #21 from Jürgen Reuter  ---
In our functional test suite, the tests nlo_4, nlo_5, fks_res_1 and another
test are still failing, they lead to segmentation faults. This will be really
difficult to isolate, but maybe this is a different root cause!?

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

Jürgen Reuter  changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |---

--- Comment #20 from Jürgen Reuter  ---
Paul, thanks for the fix, our code test suite is still running, most of the
problems are solved, the unit test suite is completely good now, but there are
certain functional tests failing. This will be really, really hard to give you
a small reproducer. I reopened, you can decide whether you want it on this PR
or a new one.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #19 from Paul Thomas  ---
It helps to close it!

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #18 from Paul Thomas  ---
Hi Juergen,

Thanks for doing the reduction of the problem and thanks to Dominique for
testing the patch.

Fixed.

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #17 from Paul Thomas  ---
Author: pault
Date: Fri Sep 21 17:26:23 2018
New Revision: 264485

URL: https://gcc.gnu.org/viewcvs?rev=264485=gcc=rev
Log:
2018-09-21  Paul Thomas  

PR fortran/87359
* trans-stmt.c (gfc_trans_allocate): Don't deallocate alloc
components if must_finalize is set for expr3.

2018-09-21  Paul Thomas  

PR fortran/87359
* gfortran.dg/finalize_33.f90 : New test.


Added:
trunk/gcc/testsuite/gfortran.dg/finalize_33.f90
Modified:
trunk/gcc/fortran/ChangeLog
trunk/gcc/fortran/trans-stmt.c
trunk/gcc/testsuite/ChangeLog

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread paul.richard.thomas at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #16 from paul.richard.thomas at gmail dot com  ---
Hi Dominique,

Many thanks for coming back so promptly. I will package it up for a
commit this evening.

Best regards

Paul

On 21 September 2018 at 17:12, dominiq at lps dot ens.fr
 wrote:
> https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359
>
> --- Comment #15 from Dominique d'Humieres  ---
>> Could you please test the attached patch?
>
> The patch fixes both the reduced and the original tests.
>
> --
> You are receiving this mail because:
> You are on the CC list for the bug.
> You are the assignee for the bug.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #15 from Dominique d'Humieres  ---
> Could you please test the attached patch?

The patch fixes both the reduced and the original tests.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #14 from Paul Thomas  ---
Created attachment 44733
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44733=edit
Patch for the PR

Dear Juergen and Dominique,

Could you please test the attached patch? It eliminates the deallocation of one
of the temporaries produced by:
allocate (process%mci, source=process%component%extract_mci_template ())

but leaves the finalization call used on the other temporary.

When one of the temporaries is deallocated/finalized the other temporary is not
nulled. Hence the valgrind complaints.

Valgrind now shows no errors and that all memory is freed.

Regards

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-21 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #13 from Jürgen Reuter  ---
Created attachment 44732
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44732=edit
Promised shorted reproducer, 93 lines

This is the promised shortened reproducer, 93 lines long. This should make it
easier to find the problem.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-20 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #12 from Dominique d'Humieres  ---
The problem is with the file process_mci.f90: if I compile all the other files
with r264428 and process_mci.f90 with r263915, the test succeeds.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-20 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #11 from Dominique d'Humieres  ---
This is indeed caused by r263916.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #10 from Paul Thomas  ---
(In reply to Thomas Koenig from comment #7)
> Well, I can confirm this.  Output from valgrind shows as the first error:
> 
> Running test: event_transforms_1| Process library 'event_transforms_1_lib':
> initialized
> ==23957== Invalid read of size 8
> ==23957==at 0xB22334:
> __mci_midpoint_MOD___final_mci_midpoint_Mci_midpoint_t (mci_midpoint.f90:475)
> ==23957==by 0xA57C34: __process_mci_MOD_process_mci_entry_init
> (process_mci.f90:187)
> ==23957==by 0xA8E78B: __process_MOD_process_setup_mci (process.f90:1150)
> ==23957==by 0xB30828: __event_transforms_uti_MOD_event_transforms_1
> (event_transforms_uti.f90:85)
> ==23957==by 0x422BB9: __unit_tests_MOD_test (unit_tests.f90:175)
> ==23957==by 0xB4FF46: __event_transforms_ut_MOD_event_transforms_test
> (event_transforms_ut.f90:45)
> ==23957==by 0xB51801: whizard_check.3816 (in
> /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==by 0xB53255: MAIN__ (in /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==by 0xB535A9: main (in /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==  Address 0x61375a0 is 16 bytes inside a block of size 480 free'd
> ==23957==at 0x4C2B28A: free (vg_replace_malloc.c:530)
> ==23957==by 0xA57C03: __process_mci_MOD_process_mci_entry_init
> (process_mci.f90:187)
> ==23957==by 0xA8E78B: __process_MOD_process_setup_mci (process.f90:1150)
> ==23957==by 0xB30828: __event_transforms_uti_MOD_event_transforms_1
> (event_transforms_uti.f90:85)
> ==23957==by 0x422BB9: __unit_tests_MOD_test (unit_tests.f90:175)
> ==23957==by 0xB4FF46: __event_transforms_ut_MOD_event_transforms_test
> (event_transforms_ut.f90:45)
> ==23957==by 0xB51801: whizard_check.3816 (in
> /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==by 0xB53255: MAIN__ (in /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==by 0xB535A9: main (in /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==  Block was alloc'd at
> ==23957==at 0x4C2A0DD: malloc (vg_replace_malloc.c:299)
> ==23957==by 0xA4539B:
> __process_config_MOD_process_component_extract_mci_template
> (process_config.f90:834)
> ==23957==by 0xA579D2: __process_mci_MOD_process_mci_entry_init
> (process_mci.f90:187)
> ==23957==by 0xA8E78B: __process_MOD_process_setup_mci (process.f90:1150)
> ==23957==by 0xB30828: __event_transforms_uti_MOD_event_transforms_1
> (event_transforms_uti.f90:85)
> ==23957==by 0x422BB9: __unit_tests_MOD_test (unit_tests.f90:175)
> ==23957==by 0xB4FF46: __event_transforms_ut_MOD_event_transforms_test
> (event_transforms_ut.f90:45)
> ==23957==by 0xB51801: whizard_check.3816 (in
> /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==by 0xB53255: MAIN__ (in /home/ig25/Downloads/Whiz/whizard_test)
> ==23957==by 0xB535A9: main (in /home/ig25/Downloads/Whiz/whizard_test)
> 
> So, it is a finalizer problem.  The allocate statement was at
> 
>   function process_component_extract_mci_template (component) &
>  result (mci_template)
> class(mci_t), allocatable :: mci_template
> class(process_component_t), intent(in) :: component
> if (allocated (component%mci_template)) &
>allocate (mci_template, source = component%mci_template)
>   end function process_component_extract_mci_template
> 
> Hopefully, this can narrow things down a bit.

If this a finalizer problem, try reverting r263916.

I am not in a position to work on this right now, except to revert the above
revision on trunk. Please let me know if this does indeed fix your proble.

Cheers

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

Dominique d'Humieres  changed:

   What|Removed |Added

   Keywords||wrong-code
 Status|UNCONFIRMED |NEW
   Last reconfirmed||2018-09-19
  Known to work||8.2.0
 Ever confirmed|0   |1
  Known to fail||9.0

--- Comment #9 from Dominique d'Humieres  ---
AFAICT the change occurred between revisions r263787 (2018-08-22, OK) and
r263994 (2018-08-30, wrong code).

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread tkoenig at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #8 from Thomas Koenig  ---
Created attachment 44728
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=44728=edit
Makefile for the shortened reproducer

Hi,

if you want to compile the reproducer, you can use this Makefile,
it should have all the dependencies right (so rm *.o ; make -j8 make
can work).

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread tkoenig at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #7 from Thomas Koenig  ---
Well, I can confirm this.  Output from valgrind shows as the first error:

Running test: event_transforms_1| Process library 'event_transforms_1_lib':
initialized
==23957== Invalid read of size 8
==23957==at 0xB22334:
__mci_midpoint_MOD___final_mci_midpoint_Mci_midpoint_t (mci_midpoint.f90:475)
==23957==by 0xA57C34: __process_mci_MOD_process_mci_entry_init
(process_mci.f90:187)
==23957==by 0xA8E78B: __process_MOD_process_setup_mci (process.f90:1150)
==23957==by 0xB30828: __event_transforms_uti_MOD_event_transforms_1
(event_transforms_uti.f90:85)
==23957==by 0x422BB9: __unit_tests_MOD_test (unit_tests.f90:175)
==23957==by 0xB4FF46: __event_transforms_ut_MOD_event_transforms_test
(event_transforms_ut.f90:45)
==23957==by 0xB51801: whizard_check.3816 (in
/home/ig25/Downloads/Whiz/whizard_test)
==23957==by 0xB53255: MAIN__ (in /home/ig25/Downloads/Whiz/whizard_test)
==23957==by 0xB535A9: main (in /home/ig25/Downloads/Whiz/whizard_test)
==23957==  Address 0x61375a0 is 16 bytes inside a block of size 480 free'd
==23957==at 0x4C2B28A: free (vg_replace_malloc.c:530)
==23957==by 0xA57C03: __process_mci_MOD_process_mci_entry_init
(process_mci.f90:187)
==23957==by 0xA8E78B: __process_MOD_process_setup_mci (process.f90:1150)
==23957==by 0xB30828: __event_transforms_uti_MOD_event_transforms_1
(event_transforms_uti.f90:85)
==23957==by 0x422BB9: __unit_tests_MOD_test (unit_tests.f90:175)
==23957==by 0xB4FF46: __event_transforms_ut_MOD_event_transforms_test
(event_transforms_ut.f90:45)
==23957==by 0xB51801: whizard_check.3816 (in
/home/ig25/Downloads/Whiz/whizard_test)
==23957==by 0xB53255: MAIN__ (in /home/ig25/Downloads/Whiz/whizard_test)
==23957==by 0xB535A9: main (in /home/ig25/Downloads/Whiz/whizard_test)
==23957==  Block was alloc'd at
==23957==at 0x4C2A0DD: malloc (vg_replace_malloc.c:299)
==23957==by 0xA4539B:
__process_config_MOD_process_component_extract_mci_template
(process_config.f90:834)
==23957==by 0xA579D2: __process_mci_MOD_process_mci_entry_init
(process_mci.f90:187)
==23957==by 0xA8E78B: __process_MOD_process_setup_mci (process.f90:1150)
==23957==by 0xB30828: __event_transforms_uti_MOD_event_transforms_1
(event_transforms_uti.f90:85)
==23957==by 0x422BB9: __unit_tests_MOD_test (unit_tests.f90:175)
==23957==by 0xB4FF46: __event_transforms_ut_MOD_event_transforms_test
(event_transforms_ut.f90:45)
==23957==by 0xB51801: whizard_check.3816 (in
/home/ig25/Downloads/Whiz/whizard_test)
==23957==by 0xB53255: MAIN__ (in /home/ig25/Downloads/Whiz/whizard_test)
==23957==by 0xB535A9: main (in /home/ig25/Downloads/Whiz/whizard_test)

So, it is a finalizer problem.  The allocate statement was at

  function process_component_extract_mci_template (component) &
 result (mci_template)
class(mci_t), allocatable :: mci_template
class(process_component_t), intent(in) :: component
if (allocated (component%mci_template)) &
   allocate (mci_template, source = component%mci_template)
  end function process_component_extract_mci_template

Hopefully, this can narrow things down a bit.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #6 from Paul Thomas  ---
(In reply to Jürgen Reuter from comment #5)
> (In reply to Thomas Koenig from comment #4)
> > After generating a lot of module files with -fsyntax-only
> > so make succeeds, and then running "make check" on the
> > reproducer, I get
> **
> > *
> > *** FATAL ERROR: Self-test 'resonances' not implemented.
> 
> 
> Wait, you are talking about the tarball (attachment)? After make, please do
> ./whizard_test --check event_transforms
> Still in the procedure of reducing the issue, I already decoupled 10-12
> modules.

Hi Juergen,

Reducing this would make life a heck of a sight easier! Thanks :-) As it
happens, I have been somewhat active in the last few weeks and a clue, at
least, as to where the problem starts would be good.

Cheers

Paul

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #5 from Jürgen Reuter  ---
(In reply to Thomas Koenig from comment #4)
> After generating a lot of module files with -fsyntax-only
> so make succeeds, and then running "make check" on the
> reproducer, I get
**
> *
> *** FATAL ERROR: Self-test 'resonances' not implemented.


Wait, you are talking about the tarball (attachment)? After make, please do
./whizard_test --check event_transforms
Still in the procedure of reducing the issue, I already decoupled 10-12
modules.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread tkoenig at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

--- Comment #4 from Thomas Koenig  ---
After generating a lot of module files with -fsyntax-only
so make succeeds, and then running "make check" on the
reproducer, I get

|=|
|   WHIZARD 2.6.5
|=|
| 
| Running self-test: resonances
| 
**
**
*** FATAL ERROR: Self-test 'resonances' not implemented.
**
**
WHIZARD run aborted.

[Bug fortran/87359] [9 regression] pointer being freed was not allocated

2018-09-19 Thread rguenth at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87359

Richard Biener  changed:

   What|Removed |Added

   Priority|P3  |P4
Summary|[9.0 regression] pointer|[9 regression] pointer
   |being freed was not |being freed was not
   |allocated   |allocated