[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-07-25 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

Mikael Morin mikael at gcc dot gnu.org changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #10 from Mikael Morin mikael at gcc dot gnu.org ---
I think this has been fixed, no need to keep it open.


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-05-16 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

--- Comment #9 from Paul Thomas pault at gcc dot gnu.org ---
Author: pault
Date: Sat May 16 08:09:52 2015
New Revision: 223234

URL: https://gcc.gnu.org/viewcvs?rev=223234root=gccview=rev
Log:
2015-05-16  Mikael Morin  mik...@gcc.gnu.org
Paul Thomas  pa...@gcc.gnu.org

PR fortran/65792
* trans-expr.c (gfc_trans_subcomponent_assign): Always assign
the expression component to the destination. In addition, if
the component has allocatable components, copy them and
deallocate those of the expression, if it is not a variable.
The expression is fixed if not a variable to prevent multiple
evaluations.

2015-05-16  Mikael Morin  mik...@gcc.gnu.org

PR fortran/65792
* gfortran.dg/derived_constructor_components_5: New test

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


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-25 Thread pault at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

Paul Thomas pault at gcc dot gnu.org changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #8 from Paul Thomas pault at gcc dot gnu.org ---
Created attachment 35400
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=35400action=edit
Draft Patch

The attached patch bootstraps and regtests with Andre's patch for .. and
pr65841 remains fixed. Have extended Mikael's test case to include a function
call to verify that there are no memory leaks.

! { dg-do run }
!
! PR fortran/65792
! The evaluation of the argument in the call to new_prt_spec2
! failed to properly initialize the comp component.
! While the array contents were properly copied, the array bounds remained
! uninitialized.
!
! Contributed by Dominique D'Humieres domi...@lps.ens.fr

program main
  implicit none

  integer, parameter :: n = 2

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

  type :: string_container_t
 type(string_t) :: comp
  end type string_container_t

  type(string_t) :: prt_in, tmp, tmpa(n)
  type(string_container_t) :: tmpc, tmpca(n)
  integer :: i, j, k

  do i=1,16

 ! scalar elemental function with structure constructor
 prt_in = string_t([D])
 tmpc = new_prt_spec2 (string_container_t(prt_in))
 print *, tmpc%comp%chars
 deallocate (prt_in%chars)
 deallocate(tmpc%comp%chars)
 tmpc = new_prt_spec2
(string_container_t(new_str_t([h,e,l,l,o])))
 print *, tmpc%comp%chars
 deallocate(tmpc%comp%chars)

  end do

contains

  impure elemental function new_prt_spec2 (name) result (prt_spec)
type(string_container_t), intent(in) :: name
type(string_container_t) :: prt_spec
prt_spec = name
  end function new_prt_spec2


  function new_str_t (name) result (prt_spec)
character (*), intent(in), dimension (:) :: name
type(string_t) :: prt_spec
prt_spec = string_t(name)
  end function new_str_t

end program main

I will submit tomorrow evening.

Paul


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-18 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

--- Comment #7 from Dominique d'Humieres dominiq at lps dot ens.fr ---
Created attachment 35352
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=35352action=edit
Cumulated patch for PR61831 and 65792

 Can you post a testcase for the remaining bug there?
 I have lost sight of what is missing.

I have attached the patch I have applied on top of a clean tree at r12 and
regtested. As said before the patch fixes also pr49324.

Note that I have tested with

! { dg-additional-options -fsanitize=address }

IIRC this is not available on all targets.


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-18 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

--- Comment #4 from Dominique d'Humieres dominiq at lps dot ens.fr ---
 The patch fixes the PR, but causes

 FAIL: gfortran.dg/class_19.f03   -O0  execution test
 ...

False alarm! The failures are due to a conflict with another patch.

The patch seems to fix also pr49324.


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-18 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

Mikael Morin mikael at gcc dot gnu.org changed:

   What|Removed |Added

 Status|NEW |ASSIGNED
   Assignee|unassigned at gcc dot gnu.org  |mikael at gcc dot 
gnu.org

--- Comment #5 from Mikael Morin mikael at gcc dot gnu.org ---
Created attachment 35351
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=35351action=edit
draft patch variant, untested again

This one is less invasive and can be preferred for backports.


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-18 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

--- Comment #6 from Mikael Morin mikael at gcc dot gnu.org ---
(In reply to Dominique d'Humieres from comment #4)
 The patch seems to fix also pr49324.

Can you post a testcase for the remaining bug there?
I have lost sight of what is missing.


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-17 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

--- Comment #2 from Mikael Morin mikael at gcc dot gnu.org ---
Created attachment 35346
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=35346action=edit
draft patch, untested


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-17 Thread mikael at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

Mikael Morin mikael at gcc dot gnu.org changed:

   What|Removed |Added

 CC||mikael at gcc dot gnu.org

--- Comment #1 from Mikael Morin mikael at gcc dot gnu.org ---
The problem is the initialization of string_container_t.6.comp in the dump.
The array itself (the data component) is properly initialized, but not the
array bounds.


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-17 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

--- Comment #3 from Dominique d'Humieres dominiq at lps dot ens.fr ---
 Created attachment 35346 [details]
 draft patch, untested

The patch fixes the PR, but causes

FAIL: gfortran.dg/class_19.f03   -O0  execution test
FAIL: gfortran.dg/class_19.f03   -O1  execution test
FAIL: gfortran.dg/class_19.f03   -O2  execution test
FAIL: gfortran.dg/class_19.f03   -O3 -fomit-frame-pointer  execution test
FAIL: gfortran.dg/class_19.f03   -O3 -fomit-frame-pointer -funroll-loops 
execution test
FAIL: gfortran.dg/class_19.f03   -O3 -fomit-frame-pointer -funroll-all-loops
-finline-functions  execution test
FAIL: gfortran.dg/class_19.f03   -O3 -g  execution test
FAIL: gfortran.dg/class_19.f03   -Os  execution test
FAIL: gfortran.dg/class_19.f03   -g -flto  execution test

reduced test

module foo_mod
  type foo_inner
integer, allocatable :: v(:)
  end type foo_inner
  type foo_outer
class(foo_inner), allocatable :: int
  end type foo_outer
contains
subroutine foo_checkit()
  implicit none
  type(foo_outer),allocatable :: try2

  allocate(try2)
  if (allocated(try2%int)) call abort()

end subroutine foo_checkit
end module foo_mod

program main

  use foo_mod
  implicit none

  call foo_checkit()

end program main

which gives at run time

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


[Bug fortran/65792] allocation of scalar elemental function with structure constructor fails

2015-04-17 Thread dominiq at lps dot ens.fr
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

Dominique d'Humieres dominiq at lps dot ens.fr changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Last reconfirmed||2015-04-17
 Ever confirmed|0   |1