public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/34143]  New: alloc_comp_constructor.f90 fails with -fdefault-integer-8
@ 2007-11-18 20:02 tkoenig at gcc dot gnu dot org
  2007-11-18 21:48 ` [Bug fortran/34143] " jvdelisle at gcc dot gnu dot org
                   ` (17 more replies)
  0 siblings, 18 replies; 19+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2007-11-18 20:02 UTC (permalink / raw)
  To: gcc-bugs

Reduced from a failure of alloc_comp_constructor.f90
with -fdefault-integer-8 on i686-pc-linux-gnu:

$ cat alloc_1.f90 
Program test_constructor

    implicit none

    type :: thytype
        integer(4) :: a(2,2)
    end type thytype

    type :: mytype
        integer(4), allocatable :: a(:, :)
        type(thytype), allocatable :: q(:)
    end type mytype

    type (mytype) :: x
    integer, allocatable :: yy(:,:)
    type (thytype), allocatable :: bar(:)

    ! Check that unallocated allocatables work
    x = mytype(yy, bar)
    if (allocated(x%a) .or. allocated(x%q)) call abort()

end program test_constructor
$ gfortran alloc_1.f90 
$ ./a.out
$ gfortran -fdefault-integer-8 alloc_1.f90 
$ ./a.out
Fortran runtime error: Attempt to allocate a negative amount of memory.


-- 
           Summary: alloc_comp_constructor.f90 fails with -fdefault-integer-
                    8
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: tkoenig at gcc dot gnu dot org
OtherBugsDependingO 32770
             nThis:


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
@ 2007-11-18 21:48 ` jvdelisle at gcc dot gnu dot org
  2007-11-18 22:04 ` tkoenig at gcc dot gnu dot org
                   ` (16 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: jvdelisle at gcc dot gnu dot org @ 2007-11-18 21:48 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from jvdelisle at gcc dot gnu dot org  2007-11-18 21:48 -------
The test case given here passes for me on x86-64 with both -m32 and -m64 and
with or without -fdefault-integer-8. hmm!


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
  2007-11-18 21:48 ` [Bug fortran/34143] " jvdelisle at gcc dot gnu dot org
@ 2007-11-18 22:04 ` tkoenig at gcc dot gnu dot org
  2007-11-18 23:41 ` jvdelisle at gcc dot gnu dot org
                   ` (15 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2007-11-18 22:04 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from tkoenig at gcc dot gnu dot org  2007-11-18 22:04 -------
(In reply to comment #1)
> The test case given here passes for me on x86-64 with both -m32 and -m64 and
> with or without -fdefault-integer-8. hmm!

Does the original test case pass?


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
  2007-11-18 21:48 ` [Bug fortran/34143] " jvdelisle at gcc dot gnu dot org
  2007-11-18 22:04 ` tkoenig at gcc dot gnu dot org
@ 2007-11-18 23:41 ` jvdelisle at gcc dot gnu dot org
  2007-11-20 13:04 ` fxcoudert at gcc dot gnu dot org
                   ` (14 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: jvdelisle at gcc dot gnu dot org @ 2007-11-18 23:41 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from jvdelisle at gcc dot gnu dot org  2007-11-18 23:41 -------
OK, the original test case fails as reported.  Replacing aborts with printin
the line number that fails:

 fail 39
 fail 40
 fail 80
 fail 81


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2007-11-18 23:41 ` jvdelisle at gcc dot gnu dot org
@ 2007-11-20 13:04 ` fxcoudert at gcc dot gnu dot org
  2007-11-22  8:56 ` fxcoudert at gcc dot gnu dot org
                   ` (13 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-11-20 13:04 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from fxcoudert at gcc dot gnu dot org  2007-11-20 13:03 -------
The Intel and Sun compilers complain that this code is not legal, because you
can't do "x = mytype(yy, bar)" if yy is not allocated.

Otherwise, a reduced testcase on x86_64-linux is:

  type t
    integer, allocatable :: a(:)
  end type t

  type(t) :: x
  integer(kind=8), allocatable :: yy(:)

  x = t(yy)
  if (allocated(x%a)) print *, "bug"
end


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |fxcoudert at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2007-11-20 13:03:36
               date|                            |


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2007-11-20 13:04 ` fxcoudert at gcc dot gnu dot org
@ 2007-11-22  8:56 ` fxcoudert at gcc dot gnu dot org
  2007-11-22 13:18 ` burnus at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-11-22  8:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from fxcoudert at gcc dot gnu dot org  2007-11-22 08:56 -------
Erik, Paul, as authors of the original patch and testcases, can you confirm my
conclusion that the code in comment #4 (and thus, the
gfortran.dg/alloc_comp_constructor_1.f90 testcase) is not legal, for the reason
I indicate in the comment?


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |erik dot edelmann at iki dot
                   |                            |fi, pault at gcc dot gnu dot
                   |                            |org
             Status|NEW                         |WAITING


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2007-11-22  8:56 ` fxcoudert at gcc dot gnu dot org
@ 2007-11-22 13:18 ` burnus at gcc dot gnu dot org
  2007-11-29 11:25 ` fxcoudert at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-11-22 13:18 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from burnus at gcc dot gnu dot org  2007-11-22 13:18 -------
(In reply to comment #4)
> The Intel and Sun compilers complain that this code is not legal, because you
> can't do "x = mytype(yy, bar)" if yy is not allocated.

I cannot reproduce this with the Sun Compiler, only with ifort. Besides,
following the Fortran 2003 standard, I believe the program is valid.

"If a component of a derived type is allocatable, the corresponding constructor
expression shall either be a reference to the intrinsic function NULL with no
arguments, an allocatable entity of the same rank, or shall evaluate to an
entity of the same rank. If the expression is a reference to the intrinsic
function NULL, the corresponding component of the constructor has a status of
unallocated. If the expression is an allocatable entity, the corresponding
component of the constructor has the same allocation status as that allocatable
entity and, if it is allocated, the same dynamic type, bounds, and value;"

(Fortran 2003 standard, "4.5.9 Construction of derived-type values")


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2007-11-22 13:18 ` burnus at gcc dot gnu dot org
@ 2007-11-29 11:25 ` fxcoudert at gcc dot gnu dot org
  2007-11-30  7:49 ` pault at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-11-29 11:25 UTC (permalink / raw)
  To: gcc-bugs



-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|WAITING                     |NEW
   Last reconfirmed|2007-11-29 11:25:01         |2007-11-29 11:25:47
               date|                            |


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2007-11-29 11:25 ` fxcoudert at gcc dot gnu dot org
@ 2007-11-30  7:49 ` pault at gcc dot gnu dot org
  2008-02-05 12:58 ` pault at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-11-30  7:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2007-11-30 07:49 -------
(In reply to comment #5)
> Erik, Paul, as authors of the original patch and testcases, can you confirm my
> conclusion that the code in comment #4 (and thus, the
> gfortran.dg/alloc_comp_constructor_1.f90 testcase) is not legal, for the reason
> I indicate in the comment?
> 
Sorry - I missed this discussion compeletly.

Tobias' analysis is correct. It is legal.  In functional terms, the descriptor
with its null pointer is passed to the descriptor field of the derived type.

Cheers

Paul


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2007-11-30  7:49 ` pault at gcc dot gnu dot org
@ 2008-02-05 12:58 ` pault at gcc dot gnu dot org
  2008-02-05 13:05 ` pault at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-02-05 12:58 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from pault at gcc dot gnu dot org  2008-02-05 12:57 -------
I just noticed that this is due to incorrect or non-existent type/kind checking
in the constructor 'mytype'.  With -fdefault-integer-8, yy has KIND=8, whereas
the corresponding component has KIND=4, as given by the declaration. The
runtime segfault is an obvious outcome.

Is the correct thing to throw an error or to quietly do the conversion?

Paul


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2008-02-05 12:58 ` pault at gcc dot gnu dot org
@ 2008-02-05 13:05 ` pault at gcc dot gnu dot org
  2008-02-06  8:34 ` pault at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-02-05 13:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from pault at gcc dot gnu dot org  2008-02-05 13:05 -------
I've knocked back it's priority but have assigned it to myself to compensate.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
           Keywords|wrong-code                  |accepts-invalid, ice-on-
                   |                            |invalid-code
   Last reconfirmed|2007-11-29 11:25:47         |2008-02-05 13:05:08
               date|                            |


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2008-02-05 13:05 ` pault at gcc dot gnu dot org
@ 2008-02-06  8:34 ` pault at gcc dot gnu dot org
  2008-02-06  9:10 ` burnus at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-02-06  8:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from pault at gcc dot gnu dot org  2008-02-06 08:33 -------
This bug is caused by gfc_conv_intrinsic_conversion calling
gfc_conv_intrinsic_function_args, which builds a temporary without checking if
the allocatable array 'yy' has been allocated or not.

This can be cured by looking for a null data field of the argument and
converting that directly. Alternatively, the dimension 0 lbound and ubound
being set to the same value on scope entry would accomplish the same result. 
I'll see which looks the most economic.

Cheers

Paul  


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (10 preceding siblings ...)
  2008-02-06  8:34 ` pault at gcc dot gnu dot org
@ 2008-02-06  9:10 ` burnus at gcc dot gnu dot org
  2008-02-11 17:48 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-02-06  9:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from burnus at gcc dot gnu dot org  2008-02-06 09:09 -------
> Is the correct thing to throw an error or to quietly do the conversion?
I tried the example (with integer(4) and integer(8)) with several compilers and
none of them gave an error. (With -Wall g95 gives a conversion warning).

I thus think it is valid and one should do the conversion silently (except for
-Wconversion).

>From the Fortran 2003 standard:

"For a nonpointer component, the declared type and type parameters of the
component and expr shall conform in the same way as for a variable and expr in
an intrinsic assignment statement (7.4.1.2), as specified in Table 7.8."


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (11 preceding siblings ...)
  2008-02-06  9:10 ` burnus at gcc dot gnu dot org
@ 2008-02-11 17:48 ` pault at gcc dot gnu dot org
  2008-02-12 10:55 ` dominiq at lps dot ens dot fr
                   ` (4 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-02-11 17:48 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from pault at gcc dot gnu dot org  2008-02-11 17:48 -------
(In reply to comment #11)

OK I have a fix, up to a wrinkle that raises a standard question:

alloc_comp_constructor.f90 now compiles and runs OK but aborts because the
bounds are changed by the implicit conversion when -fdefault-integer-8 is used.

All that the standard says, as far as I can tell is that the descriptor be
copied.  In fact, Erik and I had temporaries renormalised to unity lbounds; I
am begining to think that this is incorrect.  If so, the bounds checks in the
testcase will fail, as they are doing with the implicit conversion.

Cheers

Paul


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (12 preceding siblings ...)
  2008-02-11 17:48 ` pault at gcc dot gnu dot org
@ 2008-02-12 10:55 ` dominiq at lps dot ens dot fr
  2008-11-24  6:37 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-02-12 10:55 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from dominiq at lps dot ens dot fr  2008-02-12 10:54 -------
The problem of conversion shows up even without -fdefault-integer-8 along with
bound problems as shown by the following code:

integer, parameter :: ik=4
type :: struct
   integer(4), allocatable :: ib(:)
end type struct
integer, parameter :: from=-1, to=2
integer(ik), allocatable :: ia(:)
type(struct) :: x
allocate(ia(from:to))
print *, 'bounds, full array           ', lbound(ia), ubound(ia)
print *, 'bounds, full implicit section', lbound(ia(:)), ubound(ia(:))
print *, 'bounds, full explicit section', lbound(ia(from:to)),
ubound(ia(from:to))
print *, 'derived type, ik=', ik
x=struct(ia)
print *, 'bounds, full array           ', lbound(x%ib), ubound(x%ib)
x=struct(ia(:))
print *, 'bounds, full implicit section', lbound(x%ib), ubound(x%ib)
x=struct(ia(from:to))
print *, 'bounds, full explicit section', lbound(x%ib), ubound(x%ib)
deallocate(ia)
end

with ik = 4, the ouput is:

 bounds, full array                     -1           2
 bounds, full implicit section           1           4
 bounds, full explicit section           1           4
 derived type, ik=           4
 bounds, full array                     -1           2
 bounds, full implicit section          -1           2    <-- should not it be
1 4 as above?
 bounds, full explicit section           1           4

with ik = 8:

...
 derived type, ik=           8
 bounds, full array                      1           4    <--- should not it be
-1 2 as for ik = 4?
 bounds, full implicit section           1           4
 bounds, full explicit section           1           4


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (13 preceding siblings ...)
  2008-02-12 10:55 ` dominiq at lps dot ens dot fr
@ 2008-11-24  6:37 ` pault at gcc dot gnu dot org
  2008-11-27 13:23 ` burnus at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-11-24  6:37 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from pault at gcc dot gnu dot org  2008-11-24 06:35 -------
Subject: Bug 34143

Author: pault
Date: Mon Nov 24 06:34:16 2008
New Revision: 142148

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=142148
Log:
2008-11-24  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/34820
        * trans-expr.c (gfc_conv_function_call): Remove all code to
        deallocate intent out derived types with allocatable
        components.
        (gfc_trans_assignment_1): An assignment from a scalar to an
        array of derived types with allocatable components, requires
        a deep copy to each array element and deallocation of the
        converted rhs expression afterwards.
        * trans-array.c : Minor whitespace.
        * trans-decl.c (init_intent_out_dt): Add code to deallocate
        allocatable components of derived types with intent out.
        (generate_local_decl): If these types are unused, set them
        referenced anyway but allow the uninitialized warning.

        PR fortran/34143
        * trans-expr.c (gfc_trans_subcomponent_assign): If a conversion
        expression has a null data pointer argument, nullify the
        allocatable component.

        PR fortran/32795
        * trans-expr.c (gfc_trans_subcomponent_assign): Only nullify
        the data pointer if the source is not a variable.

2008-11-24  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/34820
        * gfortran.dg/alloc_comp_constructor_6.f90 : New test.
        * gfortran.dg/alloc_comp_basics_1.f90 : Reduce expected refs to
        'builtin_free' from 24 to 18.

        PR fortran/34143
        * gfortran.dg/alloc_comp_constructor_5.f90 : New test.

        PR fortran/32795
        * gfortran.dg/alloc_comp_constructor_4.f90 : New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_auto_array_2.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constructor_4.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constructor_5.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constructor_6.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (14 preceding siblings ...)
  2008-11-24  6:37 ` pault at gcc dot gnu dot org
@ 2008-11-27 13:23 ` burnus at gcc dot gnu dot org
  2008-11-29 20:45 ` pault at gcc dot gnu dot org
  2008-11-30  7:51 ` pault at gcc dot gnu dot org
  17 siblings, 0 replies; 19+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-11-27 13:23 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #15 from burnus at gcc dot gnu dot org  2008-11-27 13:21 -------
I think PR is fixed on the trunk (4.4) [-> back porting?], except of the issue
of comment 13 (-> different PR?).


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (15 preceding siblings ...)
  2008-11-27 13:23 ` burnus at gcc dot gnu dot org
@ 2008-11-29 20:45 ` pault at gcc dot gnu dot org
  2008-11-30  7:51 ` pault at gcc dot gnu dot org
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-11-29 20:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #16 from pault at gcc dot gnu dot org  2008-11-29 20:43 -------
Subject: Bug 34143

Author: pault
Date: Sat Nov 29 20:42:22 2008
New Revision: 142284

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=142284
Log:
2008-11-24  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/34820
        * trans-expr.c (gfc_conv_function_call): Remove all code to
        deallocate intent out derived types with allocatable
        components.
        (gfc_trans_assignment_1): An assignment from a scalar to an
        array of derived types with allocatable components, requires
        a deep copy to each array element and deallocation of the
        converted rhs expression afterwards.
        * trans-array.c : Minor whitespace.
        * trans-decl.c (init_intent_out_dt): Add code to deallocate
        allocatable components of derived types with intent out.
        (generate_local_decl): If these types are unused, set them
        referenced anyway but allow the uninitialized warning.

        PR fortran/34143
        * trans-expr.c (gfc_trans_subcomponent_assign): If a conversion
        expression has a null data pointer argument, nullify the
        allocatable component.

        PR fortran/32795
        * trans-expr.c (gfc_trans_subcomponent_assign): Only nullify
        the data pointer if the source is not a variable.

2008-11-24  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/34820
        * gfortran.dg/alloc_comp_constructor_6.f90 : New test.
        * gfortran.dg/alloc_comp_basics_1.f90 : Reduce expected refs to
        'builtin_free' from 24 to 18.

        PR fortran/34143
        * gfortran.dg/alloc_comp_constructor_5.f90 : New test.

        PR fortran/32795
        * gfortran.dg/alloc_comp_constructor_4.f90 : New test.

Added:
   
branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/alloc_comp_auto_array_2.f90
   
branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/alloc_comp_constructor_4.f90
   
branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/alloc_comp_constructor_5.f90
   
branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/alloc_comp_constructor_6.f90
Modified:
    branches/gcc-4_3-branch/gcc/fortran/ChangeLog
    branches/gcc-4_3-branch/gcc/fortran/trans-array.c
    branches/gcc-4_3-branch/gcc/fortran/trans-decl.c
    branches/gcc-4_3-branch/gcc/fortran/trans-expr.c
    branches/gcc-4_3-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90


-- 


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


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

* [Bug fortran/34143] alloc_comp_constructor.f90 fails with -fdefault-integer-8
  2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
                   ` (16 preceding siblings ...)
  2008-11-29 20:45 ` pault at gcc dot gnu dot org
@ 2008-11-30  7:51 ` pault at gcc dot gnu dot org
  17 siblings, 0 replies; 19+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-11-30  7:51 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #17 from pault at gcc dot gnu dot org  2008-11-30 07:50 -------
Fixed on trunk and 4.3.

Comment #13 has migrated to PR38324.

Thanks for the report

Paul


-- 

pault at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2008-11-30  7:51 UTC | newest]

Thread overview: 19+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-11-18 20:02 [Bug fortran/34143] New: alloc_comp_constructor.f90 fails with -fdefault-integer-8 tkoenig at gcc dot gnu dot org
2007-11-18 21:48 ` [Bug fortran/34143] " jvdelisle at gcc dot gnu dot org
2007-11-18 22:04 ` tkoenig at gcc dot gnu dot org
2007-11-18 23:41 ` jvdelisle at gcc dot gnu dot org
2007-11-20 13:04 ` fxcoudert at gcc dot gnu dot org
2007-11-22  8:56 ` fxcoudert at gcc dot gnu dot org
2007-11-22 13:18 ` burnus at gcc dot gnu dot org
2007-11-29 11:25 ` fxcoudert at gcc dot gnu dot org
2007-11-30  7:49 ` pault at gcc dot gnu dot org
2008-02-05 12:58 ` pault at gcc dot gnu dot org
2008-02-05 13:05 ` pault at gcc dot gnu dot org
2008-02-06  8:34 ` pault at gcc dot gnu dot org
2008-02-06  9:10 ` burnus at gcc dot gnu dot org
2008-02-11 17:48 ` pault at gcc dot gnu dot org
2008-02-12 10:55 ` dominiq at lps dot ens dot fr
2008-11-24  6:37 ` pault at gcc dot gnu dot org
2008-11-27 13:23 ` burnus at gcc dot gnu dot org
2008-11-29 20:45 ` pault at gcc dot gnu dot org
2008-11-30  7:51 ` pault at gcc dot gnu dot 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).