public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/36932]  New: unneeded temporary (2x)
@ 2008-07-25 10:48 jv244 at cam dot ac dot uk
  2008-07-25 13:06 ` [Bug fortran/36932] " tkoenig at gcc dot gnu dot org
                   ` (13 more replies)
  0 siblings, 14 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2008-07-25 10:48 UTC (permalink / raw)
  To: gcc-bugs

The line 'a=pbc(p(i)%r)' warns twice about an array temporary, but none should
be needed:

MODULE M1
  IMPLICIT NONE
  TYPE particle
   REAL :: r(3)
  END TYPE
CONTAINS
  SUBROUTINE S1()
     TYPE(particle), POINTER, DIMENSION(:) :: p
     REAL :: a(3)
     INTEGER :: i
     a=pbc(p(i)%r)
  END SUBROUTINE S1
  FUNCTION pbc(a)
     REAL :: a(3)
     REAL :: pbc(3)
     pbc=a
  END FUNCTION
END MODULE M1


-- 
           Summary: unneeded temporary (2x)
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Keywords: missed-optimization
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jv244 at cam dot ac dot uk


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
@ 2008-07-25 13:06 ` tkoenig at gcc dot gnu dot org
  2008-08-17  0:06 ` pinskia at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2008-07-25 13:06 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from tkoenig at gcc dot gnu dot org  2008-07-25 13:05 -------
Confirmed.


-- 

tkoenig at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |tkoenig at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2008-07-25 13:05:18
               date|                            |


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
  2008-07-25 13:06 ` [Bug fortran/36932] " tkoenig at gcc dot gnu dot org
@ 2008-08-17  0:06 ` pinskia at gcc dot gnu dot org
  2010-02-10  8:57 ` jv244 at cam dot ac dot uk
                   ` (11 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2008-08-17  0:06 UTC (permalink / raw)
  To: gcc-bugs



-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |enhancement


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
  2008-07-25 13:06 ` [Bug fortran/36932] " tkoenig at gcc dot gnu dot org
  2008-08-17  0:06 ` pinskia at gcc dot gnu dot org
@ 2010-02-10  8:57 ` jv244 at cam dot ac dot uk
  2010-02-13 21:13 ` jv244 at cam dot ac dot uk
                   ` (10 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-10  8:57 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from jv244 at cam dot ac dot uk  2010-02-10 08:57 -------
the patch for 41113 fixes one of the two warnings


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2010-02-10  8:57 ` jv244 at cam dot ac dot uk
@ 2010-02-13 21:13 ` jv244 at cam dot ac dot uk
  2010-02-13 21:15 ` jv244 at cam dot ac dot uk
                   ` (9 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-13 21:13 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from jv244 at cam dot ac dot uk  2010-02-13 21:13 -------
testing Paul's patch (http://gcc.gnu.org/ml/fortran/2010-02/msg00093.html) on
CP2K it further halved the number of pack/unpacks. However, some cases still
unexpectedly resulted in a pack. A slightly modified version of the original
testcase still fails:

MODULE M1
  IMPLICIT NONE
  TYPE particle
   REAL :: r(3)
  END TYPE
CONTAINS
  SUBROUTINE S1(p)
     TYPE(particle), POINTER, DIMENSION(:) :: p
     REAL :: a(3)
     INTEGER :: i
     a=pbc(p(i)%r)
  END SUBROUTINE S1
  FUNCTION pbc(a)
     REAL :: a(3)
     REAL :: pbc(3)
     pbc=a
  END FUNCTION
END MODULE M1

here, the only difference is that 'p' has become an argument of 'S1'.


-- 

jv244 at cam dot ac dot uk changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
  GCC build triplet|                            |pault


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2010-02-13 21:13 ` jv244 at cam dot ac dot uk
@ 2010-02-13 21:15 ` jv244 at cam dot ac dot uk
  2010-02-14  9:47 ` pault at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-13 21:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from jv244 at cam dot ac dot uk  2010-02-13 21:14 -------
mv 'Build' to 'CC' , Paul, please see previous comment.


-- 

jv244 at cam dot ac dot uk changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu dot org
  GCC build triplet|pault                       |


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (4 preceding siblings ...)
  2010-02-13 21:15 ` jv244 at cam dot ac dot uk
@ 2010-02-14  9:47 ` pault at gcc dot gnu dot org
  2010-02-14 19:27 ` jv244 at cam dot ac dot uk
                   ` (7 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2010-02-14  9:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2010-02-14 09:47 -------
(In reply to comment #4)
> mv 'Build' to 'CC' , Paul, please see previous comment.
> 

Joost,

You scared the life out of me when you said that it failed!  I had to exclude
dummies but I now do not recall why.  I'll look into it.

Cheers

Paul 


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (5 preceding siblings ...)
  2010-02-14  9:47 ` pault at gcc dot gnu dot org
@ 2010-02-14 19:27 ` jv244 at cam dot ac dot uk
  2010-02-14 19:55 ` paul dot richard dot thomas at gmail dot com
                   ` (6 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-14 19:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from jv244 at cam dot ac dot uk  2010-02-14 19:27 -------
(In reply to comment #5)
> I had to exclude
> dummies but I now do not recall why.  I'll look into it.

Hi Paul,

tested your patch at http://gcc.gnu.org/ml/fortran/2010-02/msg00106.html.

However, this ICEs with:

Program received signal SIGSEGV, Segmentation fault.
0x0000000000550816 in gfc_conv_array_parameter (se=0x7fff19b82f90,
expr=0x13af600, ss=0x13b1e20, g77=1, fsym=0x0,
    proc_name=0x7f450fd48ee8 "newuob", size=0x0) at
/data03/vondele/gcc_trunk/gcc/gcc/fortran/trans-array.c:5550
5550      if (contiguous && g77 && !this_array_result
(gdb) list
5545              se->expr = gfc_conv_array_data (tmp);
5546              return;
5547            }
5548        }
5549
5550      if (contiguous && g77 && !this_array_result
5551            && expr->symtree->n.sym->as->type != AS_ASSUMED_SHAPE)
5552        {
5553          gfc_conv_expr_descriptor (se, expr, ss);
5554          if (expr->ts.type == BT_CHARACTER)
(gdb) q

on the following reduced testcase.

MODULE powell
  INTEGER, PARAMETER :: dp=8
  TYPE opt_state_type
    REAL(dp), DIMENSION(:), POINTER  :: w
  END TYPE opt_state_type
CONTAINS
  SUBROUTINE newuoa (n,x,optstate)
    TYPE(opt_state_type)                     :: optstate
    CALL newuob (optstate%w(ixb:),optstate%w(ixo:),&
         optstate%w(ivl:),optstate%w(iw:),optstate)
  END SUBROUTINE newuoa
END MODULE powell


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (6 preceding siblings ...)
  2010-02-14 19:27 ` jv244 at cam dot ac dot uk
@ 2010-02-14 19:55 ` paul dot richard dot thomas at gmail dot com
  2010-02-15  7:35 ` jv244 at cam dot ac dot uk
                   ` (5 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: paul dot richard dot thomas at gmail dot com @ 2010-02-14 19:55 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 2523 bytes --]



------- Comment #7 from paul dot richard dot thomas at gmail dot com  2010-02-14 19:54 -------
Subject: Re:  unneeded temporary (2x)

Joost,

This time I beat you to it :-)

Dominique's problems on fortran-dev are fixed by a test for the
array_spec, which also fixes this one.

As soon as somebody gives me the green light, I'll apply the patch.
The present version is attached.

Cheers

Paul

On Sun, Feb 14, 2010 at 8:27 PM, jv244 at cam dot ac dot uk
<gcc-bugzilla@gcc.gnu.org> wrote:
>
>
> ------- Comment #6 from jv244 at cam dot ac dot uk  2010-02-14 19:27 -------
> (In reply to comment #5)
>> I had to exclude
>> dummies but I now do not recall why.  I'll look into it.
>
> Hi Paul,
>
> tested your patch at http://gcc.gnu.org/ml/fortran/2010-02/msg00106.html.
>
> However, this ICEs with:
>
> Program received signal SIGSEGV, Segmentation fault.
> 0x0000000000550816 in gfc_conv_array_parameter (se=0x7fff19b82f90,
> expr=0x13af600, ss=0x13b1e20, g77=1, fsym=0x0,
>    proc_name=0x7f450fd48ee8 "newuob", size=0x0) at
> /data03/vondele/gcc_trunk/gcc/gcc/fortran/trans-array.c:5550
> 5550      if (contiguous && g77 && !this_array_result
> (gdb) list
> 5545              se->expr = gfc_conv_array_data (tmp);
> 5546              return;
> 5547            }
> 5548        }
> 5549
> 5550      if (contiguous && g77 && !this_array_result
> 5551            && expr->symtree->n.sym->as->type != AS_ASSUMED_SHAPE)
> 5552        {
> 5553          gfc_conv_expr_descriptor (se, expr, ss);
> 5554          if (expr->ts.type == BT_CHARACTER)
> (gdb) q
>
> on the following reduced testcase.
>
> MODULE powell
>  INTEGER, PARAMETER :: dp=8
>  TYPE opt_state_type
>    REAL(dp), DIMENSION(:), POINTER  :: w
>  END TYPE opt_state_type
> CONTAINS
>  SUBROUTINE newuoa (n,x,optstate)
>    TYPE(opt_state_type)                     :: optstate
>    CALL newuob (optstate%w(ixb:),optstate%w(ixo:),&
>         optstate%w(ivl:),optstate%w(iw:),optstate)
>  END SUBROUTINE newuoa
> END MODULE powell
>
>
> --
>
>
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=36932
>
> ------- You are receiving this mail because: -------
> You are on the CC list for the bug, or are watching someone who is.
>


------- Comment #8 from paul dot richard dot thomas at gmail dot com  2010-02-14 19:54 -------
Created an attachment (id=19863)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=19863&action=view)


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (7 preceding siblings ...)
  2010-02-14 19:55 ` paul dot richard dot thomas at gmail dot com
@ 2010-02-15  7:35 ` jv244 at cam dot ac dot uk
  2010-02-16  9:05 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-15  7:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from jv244 at cam dot ac dot uk  2010-02-15 07:35 -------
(In reply to comment #7)
> As soon as somebody gives me the green light, I'll apply the patch.
> The present version is attached.

the latest version works now without ICE. pack/unpack are down to about 1000
(down from 4400). I will add another PR with another (but independent) missed
case. Thanks a lot for fixing these.


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (8 preceding siblings ...)
  2010-02-15  7:35 ` jv244 at cam dot ac dot uk
@ 2010-02-16  9:05 ` pault at gcc dot gnu dot org
  2010-02-16  9:22 ` jv244 at cam dot ac dot uk
                   ` (3 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2010-02-16  9:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from pault at gcc dot gnu dot org  2010-02-16 09:04 -------
(In reply to comment #6)

Joost,

I held back from committing the patch this morning because I noticed that your
testcase below is also calling pack/unpack like it is going out of business. 

I have to confess that I looked into this because one of the maintainers
(Dominique, I think) asked me if I understood the fix to this segfault.  My
off-the-cuff response was CLASSes but I see that this cannot entirely be the
case.  In investigating, I found these extra temporaries and have eliminated
them.  However, I did not have time to regtest and get the new patch to you.

Paul
> (In reply to comment #5)
> > I had to exclude
> > dummies but I now do not recall why.  I'll look into it.
> 
> Hi Paul,
> 
> tested your patch at http://gcc.gnu.org/ml/fortran/2010-02/msg00106.html.
> 
> However, this ICEs with:
> 
> Program received signal SIGSEGV, Segmentation fault.
> 0x0000000000550816 in gfc_conv_array_parameter (se=0x7fff19b82f90,
> expr=0x13af600, ss=0x13b1e20, g77=1, fsym=0x0,
>     proc_name=0x7f450fd48ee8 "newuob", size=0x0) at
> /data03/vondele/gcc_trunk/gcc/gcc/fortran/trans-array.c:5550
> 5550      if (contiguous && g77 && !this_array_result
> (gdb) list
> 5545              se->expr = gfc_conv_array_data (tmp);
> 5546              return;
> 5547            }
> 5548        }
> 5549
> 5550      if (contiguous && g77 && !this_array_result
> 5551            && expr->symtree->n.sym->as->type != AS_ASSUMED_SHAPE)
> 5552        {
> 5553          gfc_conv_expr_descriptor (se, expr, ss);
> 5554          if (expr->ts.type == BT_CHARACTER)
> (gdb) q
> 
> on the following reduced testcase.
> 
> MODULE powell
>   INTEGER, PARAMETER :: dp=8
>   TYPE opt_state_type
>     REAL(dp), DIMENSION(:), POINTER  :: w
>   END TYPE opt_state_type
> CONTAINS
>   SUBROUTINE newuoa (n,x,optstate)
>     TYPE(opt_state_type)                     :: optstate
>     CALL newuob (optstate%w(ixb:),optstate%w(ixo:),&
>          optstate%w(ivl:),optstate%w(iw:),optstate)
>   END SUBROUTINE newuoa
> END MODULE powell
> 


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (9 preceding siblings ...)
  2010-02-16  9:05 ` pault at gcc dot gnu dot org
@ 2010-02-16  9:22 ` jv244 at cam dot ac dot uk
  2010-02-20 12:47 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-16  9:22 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from jv244 at cam dot ac dot uk  2010-02-16 09:22 -------
(In reply to comment #10)
> (In reply to comment #6)
> 
> Joost,
> 
> I held back from committing the patch this morning because I noticed that your
> testcase below is also calling pack/unpack like it is going out of business. 
> 
> I have to confess that I looked into this because one of the maintainers
> (Dominique, I think) asked me if I understood the fix to this segfault.  My
> off-the-cuff response was CLASSes but I see that this cannot entirely be the
> case.  In investigating, I found these extra temporaries and have eliminated
> them.  However, I did not have time to regtest and get the new patch to you.

Hi Paul

not sure I understand your full reply. However, for the testcase below, I guess
there have to be pack/unpacks, since newuob has an implicit interface and
optstate%w(i:) is a slice from a 'pointer array', and thus packing is needed to
guarantee things are contiguous. But I'm sure you know :-)

Having said that, there is no pressure from my side to commit patches. Just
commit whenever you think they are in good shape, ready, understood...

Joost

> > MODULE powell
> >   INTEGER, PARAMETER :: dp=8
> >   TYPE opt_state_type
> >     REAL(dp), DIMENSION(:), POINTER  :: w
> >   END TYPE opt_state_type
> > CONTAINS
> >   SUBROUTINE newuoa (n,x,optstate)
> >     TYPE(opt_state_type)                     :: optstate
> >     CALL newuob (optstate%w(ixb:),optstate%w(ixo:),&
> >          optstate%w(ivl:),optstate%w(iw:),optstate)
> >   END SUBROUTINE newuoa
> > END MODULE powell
> > 
> 


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (10 preceding siblings ...)
  2010-02-16  9:22 ` jv244 at cam dot ac dot uk
@ 2010-02-20 12:47 ` pault at gcc dot gnu dot org
  2010-02-20 21:46 ` burnus at gcc dot gnu dot org
  2010-02-21 14:12 ` jv244 at cam dot ac dot uk
  13 siblings, 0 replies; 15+ messages in thread
From: pault at gcc dot gnu dot org @ 2010-02-20 12:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from pault at gcc dot gnu dot org  2010-02-20 12:47 -------
Subject: Bug 36932

Author: pault
Date: Sat Feb 20 12:46:43 2010
New Revision: 156926

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=156926
Log:
2010-02-20  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/36932
        PR fortran/36933
        PR fortran/43072
        PR fortran/43111
        * dependency.c (gfc_check_argument_var_dependency): Use enum
        value instead of arithmetic vaue for 'elemental'.
        (check_data_pointer_types): New function.
        (gfc_check_dependency): Call check_data_pointer_types.
        * trans-array.h : Change fourth argument of
        gfc_conv_array_parameter to boolean.
        * trans-array.c (gfc_conv_array_parameter): A contiguous array
        can be a dummy but it must not be assumed shape or deferred.
        Change fourth argument to boolean. Array constructor exprs will
        always be contiguous and do not need packing and unpacking.
        * trans-expr.c (gfc_conv_procedure_call): Clean up some white
        space and change fourth argument of gfc_conv_array_parameter
        to boolean.
        (gfc_trans_arrayfunc_assign): Change fourth argument of
        gfc_conv_array_parameter to boolean.
        * trans-io.c (gfc_convert_array_to_string): The same.
        * trans-intrinsic.c (gfc_conv_intrinsic_loc): The same.

2010-02-20  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/36932
        PR fortran/36933
        * gfortran.dg/dependency_26.f90: New test.

        PR fortran/43072
        * gfortran.dg/internal_pack_7.f90: New test.

        PR fortran/43111
        * gfortran.dg/internal_pack_8.f90: New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/dependency_26.f90
    trunk/gcc/testsuite/gfortran.dg/internal_pack_7.f90
    trunk/gcc/testsuite/gfortran.dg/internal_pack_8.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/dependency.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-array.h
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-intrinsic.c
    trunk/gcc/fortran/trans-io.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (11 preceding siblings ...)
  2010-02-20 12:47 ` pault at gcc dot gnu dot org
@ 2010-02-20 21:46 ` burnus at gcc dot gnu dot org
  2010-02-21 14:12 ` jv244 at cam dot ac dot uk
  13 siblings, 0 replies; 15+ messages in thread
From: burnus at gcc dot gnu dot org @ 2010-02-20 21:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from burnus at gcc dot gnu dot org  2010-02-20 21:46 -------
Can this PR be closed? I think all items are fixed.


-- 


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


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

* [Bug fortran/36932] unneeded temporary (2x)
  2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
                   ` (12 preceding siblings ...)
  2010-02-20 21:46 ` burnus at gcc dot gnu dot org
@ 2010-02-21 14:12 ` jv244 at cam dot ac dot uk
  13 siblings, 0 replies; 15+ messages in thread
From: jv244 at cam dot ac dot uk @ 2010-02-21 14:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from jv244 at cam dot ac dot uk  2010-02-21 14:12 -------
all fixed


-- 

jv244 at cam dot ac dot uk changed:

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


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


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

end of thread, other threads:[~2010-02-21 14:12 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-07-25 10:48 [Bug fortran/36932] New: unneeded temporary (2x) jv244 at cam dot ac dot uk
2008-07-25 13:06 ` [Bug fortran/36932] " tkoenig at gcc dot gnu dot org
2008-08-17  0:06 ` pinskia at gcc dot gnu dot org
2010-02-10  8:57 ` jv244 at cam dot ac dot uk
2010-02-13 21:13 ` jv244 at cam dot ac dot uk
2010-02-13 21:15 ` jv244 at cam dot ac dot uk
2010-02-14  9:47 ` pault at gcc dot gnu dot org
2010-02-14 19:27 ` jv244 at cam dot ac dot uk
2010-02-14 19:55 ` paul dot richard dot thomas at gmail dot com
2010-02-15  7:35 ` jv244 at cam dot ac dot uk
2010-02-16  9:05 ` pault at gcc dot gnu dot org
2010-02-16  9:22 ` jv244 at cam dot ac dot uk
2010-02-20 12:47 ` pault at gcc dot gnu dot org
2010-02-20 21:46 ` burnus at gcc dot gnu dot org
2010-02-21 14:12 ` jv244 at cam dot ac dot uk

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).