public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/48351] New: [OOP]  Realloc on assignment fails if parent component is CLASS
@ 2011-03-30  6:51 burnus at gcc dot gnu.org
  2011-03-30  8:33 ` [Bug fortran/48351] " burnus at gcc dot gnu.org
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-03-30  6:51 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

           Summary: [OOP]  Realloc on assignment fails if parent component
                    is CLASS
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: burnus@gcc.gnu.org
                CC: janus@gcc.gnu.org


http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/b7a36eba5ef7f68b
 by Nasser M. Abbasi

In the following program "%u" is allocatable. For

        this%u = u

the LHS should be allocated, but this only happens if "this" is a TYPE and not
a CLASS - but that should be completely unrelated to (re)alloc on assignment.

The program works with ifort 11.1.


module foo
    implicit none
    type :: foo_t
!      private
      DOUBLE PRECISION , ALLOCATABLE :: u(:)
      contains
        PROCEDURE :: make  ! or procedure, pass, same effect
    end type foo_t

    contains
    subroutine make(this,u)
        implicit none
        CLASS(foo_t) :: this
        DOUBLE PRECISION, intent(in) :: u(:)  ! must be CLASS
!           allocate(this%u(size(u)))  ! Must allocate now, else crash
        this%u = u
    end subroutine make
    end module foo

program main2
 use foo
 implicit none
 TYPE(foo_t) :: o
 DOUBLE PRECISION , ALLOCATABLE :: u(:)

 u=[1,2,3,4]
 CALL o%make(u)
 print *, o%u
end program main2


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

* [Bug fortran/48351] [OOP]  Realloc on assignment fails if parent component is CLASS
  2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
@ 2011-03-30  8:33 ` burnus at gcc dot gnu.org
  2011-03-30  8:39 ` burnus at gcc dot gnu.org
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-03-30  8:33 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-03-30 08:04:13 UTC ---
trans-array.c's gfc_is_reallocatable_lhs fails at:

6859      /* All that can be left are allocatable components.  */
6860      if ((expr->symtree->n.sym->ts.type != BT_DERIVED
6861           && expr->symtree->n.sym->ts.type != BT_CLASS)
6862            || !expr->symtree->n.sym->ts.u.derived->attr.alloc_comp)
6863        return false;

The reason is that the CLASS wrapper does not set:

(gdb) p expr->symtree->n.sym->ts.u.derived->attr.alloc_comp
$3 = 0

Only the "_data" component has this value set for its type:

(gdb) p expr->symtree->n.sym->ts.u.derived->components->ts.u.derived->name
$12 = 0x2aaaaab42f98 "foo_t"
(gdb) p
expr->symtree->n.sym->ts.u.derived->components->ts.u.derived->attr.alloc_comp
$13 = 1


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

* [Bug fortran/48351] [OOP]  Realloc on assignment fails if parent component is CLASS
  2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
  2011-03-30  8:33 ` [Bug fortran/48351] " burnus at gcc dot gnu.org
@ 2011-03-30  8:39 ` burnus at gcc dot gnu.org
  2011-07-07  2:34 ` townsend at astro dot wisc.edu
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-03-30  8:39 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu.org

--- Comment #2 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-03-30 08:32:55 UTC ---
(In reply to comment #1)
> The reason is that the CLASS wrapper does not set:
> (gdb) p expr->symtree->n.sym->ts.u.derived->attr.alloc_comp

If I set that variable manually in the debugger, the generated code contains
(re)assignment calls, but the program crashes nevertheless :-(


[I do not want to rule out issues with my local tree, which has some scalarizer
coarray patches, though they should not affect this result.]


Admittedly, I also do not understand the dump (with explicit size "4" to make
the dump easier to read):

        if ((real(kind=8)[0:] * restrict) this->_data->u.data == 0B) goto L.1;

        L.1:;
        D.1608 = MAX_EXPR <(this->_data->u.dim[0].ubound -
this->_data->u.dim[0].lbound) + 1, 0>;

[...]
        if ((real(kind=8)[0:] * restrict) this->_data->u.data == 0B)
          {
            this->_data->u.data = (void * restrict) __builtin_malloc (32);


What's D.1608 for? If u.data == NULL, the bounds should not be looked at --
admittedly, this information is only used later in the else branch of the "if"
shown above.

Other than that, the dump looks OK as far as I could see.

Valgrind claims - before the crash - "Invalid write of size 8" in the
assignment line of "make". (Write 8 could be a pointer or an array index.) The
actual crash is in the same line - and valgrind shows: "Access not within
mapped region at address 0x0", which means something like "(NULL).value" or
"(NULL)->value" access.


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

* [Bug fortran/48351] [OOP]  Realloc on assignment fails if parent component is CLASS
  2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
  2011-03-30  8:33 ` [Bug fortran/48351] " burnus at gcc dot gnu.org
  2011-03-30  8:39 ` burnus at gcc dot gnu.org
@ 2011-07-07  2:34 ` townsend at astro dot wisc.edu
  2012-01-13 20:58 ` pault at gcc dot gnu.org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: townsend at astro dot wisc.edu @ 2011-07-07  2:34 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

Rich Townsend <townsend at astro dot wisc.edu> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |townsend at astro dot
                   |                            |wisc.edu

--- Comment #3 from Rich Townsend <townsend at astro dot wisc.edu> 2011-07-07 02:34:41 UTC ---
(In reply to comment #0)
> http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/b7a36eba5ef7f68b
>  by Nasser M. Abbasi
> 
> In the following program "%u" is allocatable. For
> 
>         this%u = u
> 
> the LHS should be allocated, but this only happens if "this" is a TYPE and not
> a CLASS - but that should be completely unrelated to (re)alloc on assignment.
> 
> The program works with ifort 11.1.
> 
> 
> module foo
>     implicit none
>     type :: foo_t
> !      private
>       DOUBLE PRECISION , ALLOCATABLE :: u(:)
>       contains
>         PROCEDURE :: make  ! or procedure, pass, same effect
>     end type foo_t
> 
>     contains
>     subroutine make(this,u)
>         implicit none
>         CLASS(foo_t) :: this
>         DOUBLE PRECISION, intent(in) :: u(:)  ! must be CLASS
> !           allocate(this%u(size(u)))  ! Must allocate now, else crash
>         this%u = u
>     end subroutine make
>     end module foo
> 
> program main2
>  use foo
>  implicit none
>  TYPE(foo_t) :: o
>  DOUBLE PRECISION , ALLOCATABLE :: u(:)
> 
>  u=[1,2,3,4]
>  CALL o%make(u)
>  print *, o%u
> end program main2

I've run into what appears to be this bug with 4.7 (Mac OS 10.6). My sample
code is as follows:

module realloc_lhs_m

  implicit none

  type mytype
     real, allocatable :: a(:)
   contains
     procedure :: set_a
  end type mytype

contains

  subroutine set_a (this, a)
    class(mytype), intent(out) :: this
    real, intent(in)           :: a(:)
    this%a = a
  end subroutine set_a

end module realloc_lhs_m

program realloc_lhs

  use realloc_lhs_m
  implicit none

  real, allocatable :: a(:)
  type(mytype)      :: m

  a = [1.,2.,3.,4.,5.]

  call m%set_a(a)
  print *, m%a

end program realloc_lhs

This can be easily worked around -- but of course should nevertheless be fixed.

cheers,

Rich


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

* [Bug fortran/48351] [OOP]  Realloc on assignment fails if parent component is CLASS
  2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2011-07-07  2:34 ` townsend at astro dot wisc.edu
@ 2012-01-13 20:58 ` pault at gcc dot gnu.org
  2012-01-13 21:25 ` burnus at gcc dot gnu.org
  2012-01-13 21:41 ` burnus at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: pault at gcc dot gnu.org @ 2012-01-13 20:58 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

--- Comment #4 from Paul Thomas <pault at gcc dot gnu.org> 2012-01-13 20:42:07 UTC ---
Author: pault
Date: Fri Jan 13 20:42:01 2012
New Revision: 183162

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=183162
Log:
2012-01-13  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/48351
    * trans-array.c (structure_alloc_comps): Suppress interative
    call to self, when current component is deallocated using
    gfc_trans_dealloc_allocated.
    * class.c (gfc_build_class_symbol): Copy the 'alloc_comp'
    attribute from the declared type to the class structure.

2012-01-13  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/48351
    * gfortran.dg/alloc_comp_assign.f03: New.
    * gfortran.dg/allocatable_scalar_9.f90: Reduce count of
    __BUILTIN_FREE from 38 to 32.

Added:
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_assign_12.f03
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/class.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/allocatable_scalar_9.f90


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

* [Bug fortran/48351] [OOP]  Realloc on assignment fails if parent component is CLASS
  2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2012-01-13 20:58 ` pault at gcc dot gnu.org
@ 2012-01-13 21:25 ` burnus at gcc dot gnu.org
  2012-01-13 21:41 ` burnus at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-01-13 21:25 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

--- Comment #5 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-01-13 21:14:42 UTC ---
FIXED on the trunk (4.7).


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

* [Bug fortran/48351] [OOP]  Realloc on assignment fails if parent component is CLASS
  2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2012-01-13 21:25 ` burnus at gcc dot gnu.org
@ 2012-01-13 21:41 ` burnus at gcc dot gnu.org
  5 siblings, 0 replies; 7+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-01-13 21:41 UTC (permalink / raw)
  To: gcc-bugs

http://gcc.gnu.org/bugzilla/show_bug.cgi?id=48351

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |FIXED

--- Comment #6 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-01-13 21:24:00 UTC ---
Really mark as fixed.


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

end of thread, other threads:[~2012-01-13 21:25 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-03-30  6:51 [Bug fortran/48351] New: [OOP] Realloc on assignment fails if parent component is CLASS burnus at gcc dot gnu.org
2011-03-30  8:33 ` [Bug fortran/48351] " burnus at gcc dot gnu.org
2011-03-30  8:39 ` burnus at gcc dot gnu.org
2011-07-07  2:34 ` townsend at astro dot wisc.edu
2012-01-13 20:58 ` pault at gcc dot gnu.org
2012-01-13 21:25 ` burnus at gcc dot gnu.org
2012-01-13 21:41 ` burnus 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).