public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails
@ 2015-04-17 12:40 dominiq at lps dot ens.fr
  2015-04-17 19:33 ` [Bug fortran/65792] " mikael at gcc dot gnu.org
                   ` (9 more replies)
  0 siblings, 10 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-04-17 12:40 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65792

            Bug ID: 65792
           Summary: allocation of scalar elemental function with structure
                    constructor fails
           Product: gcc
           Version: 6.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: dominiq at lps dot ens.fr

The following test (extracted from the extended test in pr61831 comment 41)

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))
     deallocate (prt_in%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

end program main

fails at run time with

a.out(88248,0x7fff7a4fc300) malloc: *** mach_vm_map(size=18446603339116310528)
failed (error code=3)
*** error: can't allocate region
*** set a breakpoint in malloc_error_break to debug

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

For 4.6 up to 4.9.0, the failure is of the kind

a.out(45086) malloc: *** error for object 0x100201010: pointer being freed was
not allocated
*** set a breakpoint in malloc_error_break to debug


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
@ 2015-04-17 19:33 ` mikael at gcc dot gnu.org
  2015-04-17 20:16 ` mikael at gcc dot gnu.org
                   ` (8 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: mikael at gcc dot gnu.org @ 2015-04-17 19:33 UTC (permalink / raw)
  To: gcc-bugs

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.


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
  2015-04-17 19:33 ` [Bug fortran/65792] " mikael at gcc dot gnu.org
@ 2015-04-17 20:16 ` mikael at gcc dot gnu.org
  2015-04-17 22:48 ` dominiq at lps dot ens.fr
                   ` (7 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: mikael at gcc dot gnu.org @ 2015-04-17 20:16 UTC (permalink / raw)
  To: gcc-bugs

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=35346&action=edit
draft patch, untested


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
  2015-04-17 19:33 ` [Bug fortran/65792] " mikael at gcc dot gnu.org
  2015-04-17 20:16 ` mikael at gcc dot gnu.org
@ 2015-04-17 22:48 ` dominiq at lps dot ens.fr
  2015-04-17 22:49 ` dominiq at lps dot ens.fr
                   ` (6 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-04-17 22:48 UTC (permalink / raw)
  To: gcc-bugs

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.


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (2 preceding siblings ...)
  2015-04-17 22:48 ` dominiq at lps dot ens.fr
@ 2015-04-17 22:49 ` dominiq at lps dot ens.fr
  2015-04-18  7:48 ` dominiq at lps dot ens.fr
                   ` (5 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-04-17 22:49 UTC (permalink / raw)
  To: gcc-bugs

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


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (3 preceding siblings ...)
  2015-04-17 22:49 ` dominiq at lps dot ens.fr
@ 2015-04-18  7:48 ` dominiq at lps dot ens.fr
  2015-04-18  9:03 ` mikael at gcc dot gnu.org
                   ` (4 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-04-18  7:48 UTC (permalink / raw)
  To: gcc-bugs

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.


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (4 preceding siblings ...)
  2015-04-18  7:48 ` dominiq at lps dot ens.fr
@ 2015-04-18  9:03 ` mikael at gcc dot gnu.org
  2015-04-18  9:15 ` mikael at gcc dot gnu.org
                   ` (3 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: mikael at gcc dot gnu.org @ 2015-04-18  9:03 UTC (permalink / raw)
  To: gcc-bugs

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=35351&action=edit
draft patch variant, untested again

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


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (5 preceding siblings ...)
  2015-04-18  9:03 ` mikael at gcc dot gnu.org
@ 2015-04-18  9:15 ` mikael at gcc dot gnu.org
  2015-04-18 11:10 ` dominiq at lps dot ens.fr
                   ` (2 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: mikael at gcc dot gnu.org @ 2015-04-18  9:15 UTC (permalink / raw)
  To: gcc-bugs

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.


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (6 preceding siblings ...)
  2015-04-18  9:15 ` mikael at gcc dot gnu.org
@ 2015-04-18 11:10 ` dominiq at lps dot ens.fr
  2015-04-25 22:40 ` pault at gcc dot gnu.org
  2015-07-25 19:48 ` mikael at gcc dot gnu.org
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-04-18 11:10 UTC (permalink / raw)
  To: gcc-bugs

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=35352&action=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 r222212 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.


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (7 preceding siblings ...)
  2015-04-18 11:10 ` dominiq at lps dot ens.fr
@ 2015-04-25 22:40 ` pault at gcc dot gnu.org
  2015-07-25 19:48 ` mikael at gcc dot gnu.org
  9 siblings, 0 replies; 11+ messages in thread
From: pault at gcc dot gnu.org @ 2015-04-25 22:40 UTC (permalink / raw)
  To: gcc-bugs

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=35400&action=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 <dominiq@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


^ permalink raw reply	[flat|nested] 11+ messages in thread

* [Bug fortran/65792] allocation of scalar elemental function with structure constructor fails
  2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
                   ` (8 preceding siblings ...)
  2015-04-25 22:40 ` pault at gcc dot gnu.org
@ 2015-07-25 19:48 ` mikael at gcc dot gnu.org
  9 siblings, 0 replies; 11+ messages in thread
From: mikael at gcc dot gnu.org @ 2015-07-25 19:48 UTC (permalink / raw)
  To: gcc-bugs

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.


^ permalink raw reply	[flat|nested] 11+ messages in thread

end of thread, other threads:[~2015-07-25 19:48 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2015-04-17 12:40 [Bug fortran/65792] New: allocation of scalar elemental function with structure constructor fails dominiq at lps dot ens.fr
2015-04-17 19:33 ` [Bug fortran/65792] " mikael at gcc dot gnu.org
2015-04-17 20:16 ` mikael at gcc dot gnu.org
2015-04-17 22:48 ` dominiq at lps dot ens.fr
2015-04-17 22:49 ` dominiq at lps dot ens.fr
2015-04-18  7:48 ` dominiq at lps dot ens.fr
2015-04-18  9:03 ` mikael at gcc dot gnu.org
2015-04-18  9:15 ` mikael at gcc dot gnu.org
2015-04-18 11:10 ` dominiq at lps dot ens.fr
2015-04-25 22:40 ` pault at gcc dot gnu.org
2015-07-25 19:48 ` mikael at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).