[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-27 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

--- Comment #6 from Jürgen Reuter  ---
Created attachment 40606
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=40606=edit
Reduced test case

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-27 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

--- Comment #5 from Jürgen Reuter  ---
Here is the promised reduced test case, 80 lines, and I do believe that this is
most likely causing the issues of all our 250 failing tests (hopefully).
Attached and plain:

module module1
  implicit none
  private

  public :: data_t
  public :: t1_t
  public :: t2_t

  type :: string_t
 private
 character(LEN=1), dimension(:), allocatable :: chars
  end type string_t

  type, abstract :: data_t
 type(string_t) :: name
  end type data_t

  type, extends (data_t) :: real_t
 real :: value
  end type real_t

  type :: t1_t
 character, dimension(:), allocatable :: name
 real, pointer :: width_val => null ()
 class(data_t), pointer :: width_data => null ()
   contains
 procedure :: set => t1_set
  end type t1_t

  type :: t2_t
 type(real_t), dimension(:), pointer :: par_real => null ()
 type(t1_t), dimension(:), allocatable :: field
   contains
 procedure :: get_par_real_ptr => t2_get_par_real_ptr_index
  end type t2_t


contains

  subroutine t1_set (prt, width_data)
class(t1_t), intent(inout) :: prt
class(data_t), intent(in), pointer :: width_data
real, pointer :: ptr
prt%width_data => width_data
if (associated (width_data)) then
   select type (width_data)
   type is (real_t)
  prt%width_val => width_data%value
   class default
  prt%width_val => null ()
   end select
end if
  end subroutine t1_set

  function t2_get_par_real_ptr_index (model, i) result (ptr)
class(t2_t), intent(inout) :: model
integer, intent(in) :: i
class(data_t), pointer :: ptr
ptr => model%par_real(i)
  end function t2_get_par_real_ptr_index

end module module1

!

program main_ut
  use module1
  implicit none
  call evaluator_1 ()  
contains
  subroutine evaluator_1 ()
type(t2_t), target :: model
type(t1_t), pointer :: field
allocate (model%par_real (1))
allocate (model%field (1))
field => model%field(1)
call field%set (width_data=model%get_par_real_ptr (7))
deallocate (model%par_real)
  end subroutine evaluator_1
end program main_ut

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-26 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

--- Comment #4 from Jürgen Reuter  ---
Here is our full test suite:
http://www.desy.de/~reuter/whizard_gfortran-170126-1131.tar.gz
Just unpack, do make, then it will produce two binaries, rt_error and
rt_error2.
The first one has ca. 60 tests implemented of the form 
./rt_error --check  
You find a list of them in the file main_ut.f90 in the last select case. the
second binary can be run as 
./rt_error empty.sin 
I suspect that all of these are the same error, but wanted to provide the
information for you guys. Now, I'll try to reduce the first test case.

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-26 Thread rguenth at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

Richard Biener  changed:

   What|Removed |Added

   Target Milestone|--- |7.0

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-25 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

Dominique d'Humieres  changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Last reconfirmed||2017-01-25
 Ever confirmed|0   |1

--- Comment #3 from Dominique d'Humieres  ---
The problem seems located to the file evaluators_uti.f90 and occurred between
revisions  r243430 (2016-12-08, OK) and r243621 (2016-12-13, segfault).

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-25 Thread juergen.reuter at desy dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

--- Comment #2 from Jürgen Reuter  ---
(In reply to Dominique d'Humieres from comment #1)
> *** Bug 79231 has been marked as a duplicate of this bug. ***

Sorry for the duplicate spam... seems the commit button was overly sensitive.

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-25 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

--- Comment #1 from Dominique d'Humieres  ---
*** Bug 79231 has been marked as a duplicate of this bug. ***

[Bug fortran/79230] [7 Regression] Run time error: malloc on valid code

2017-01-25 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=79230

Dominique d'Humieres  changed:

   What|Removed |Added

   Priority|P3  |P4
Summary|[Regression on 7.0.1] Run   |[7 Regression] Run time
   |time error: malloc on valid |error: malloc on valid code
   |code|