[Bug fortran/47844] Pointer-valued function: Provide wrong result when dereferenced automatically after list-write

2011-02-21 Thread burnus at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47844

Tobias Burnus  changed:

   What|Removed |Added

   Keywords||wrong-code
 CC||burnus at gcc dot gnu.org
 Blocks||32834
  Known to fail||4.3.4, 4.4.0, 4.5.1, 4.6.0

--- Comment #1 from Tobias Burnus  2011-02-22 
07:13:57 UTC ---
I have not yet checked the code, but ifort, open64, pathf95 and NAG it prints
twice "1 11", with gfortran (FE: 4.3 to 4.6; libgfortran was always 4.6) I get
"1 11" and "1 3".


[Bug fortran/47845] [OOP] Polymorphic deferred function: Not matched class

2011-02-21 Thread burnus at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47845

Tobias Burnus  changed:

   What|Removed |Added

 CC||burnus at gcc dot gnu.org
Summary|Polymorphic deferred|[OOP] Polymorphic deferred
   |function: Not matched class |function: Not matched class

--- Comment #1 from Tobias Burnus  2011-02-22 
07:06:48 UTC ---
The following is in any case wrong:

  TYPE,ABSTRACT::vec
   CONTAINS
 PROCEDURE,PASS::set_vec=>set_vec_sub
with
  SUBROUTINE set_vec_sub(this,x,y)

and

  TYPE,EXTENDS(vec),PUBLIC::vec3d
   CONTAINS
 PROCEDURE,PUBLIC,PASS::set_vec=>set_vec_3d
with
  SUBROUTINE set_vec_3d(this,x,y,z)


NAG's error message is

Error: Overriding type-bound procedure SET_VEC of type VEC3D has 4 arguments,
but overridden one has 3 arguments


Which matches gfortran's

 PROCEDURE,PUBLIC,PASS::set_vec=>set_vec_3d
  1
Error: 'set_vec' at (1) must have the same number of formal arguments as the
overridden procedure

See Fortran 2008, "4.5.7.3 Type-bound procedure overriding":
"The overriding and overridden type-bound procedures shall satisfy the
following conditions. [...] They shall have the same number of dummy
arguments."
See: http://gcc.gnu.org/wiki/GFortranStandards


I have not checked the other error messages.


[Bug fortran/47845] New: Polymorphic deferred function: Not matched class

2011-02-21 Thread Kdx1999 at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47845

   Summary: Polymorphic deferred function: Not matched class
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: major
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: kdx1...@gmail.com


I'm trying to work out an Exercise in Stephen Chapman's book Fortran 95/2003
for Scientists & Engineers. Create a abstract class vec and subclass vec2d and
vec3d, override some deferred functions, then test the classes.



Here is my construction of vec:
MODULE class_vec
  !
  ! Brief Description:
  ! 1. Superclass of vec2d and vec3d 
  ! 2. Perform vector addition and subtraction
  ! 3. Perform vector dot product
  !
  ! 4. Common fields:
  !  a.x
  !  b.y
  !  
  ! Record of revisions:
  ! Date  Programmer  Description of change
  ! 02/21/2011KePuOriginal code
  !
  IMPLICIT NONE

  TYPE,ABSTRACT::vec
 ! Common fields
 REAL::x
 REAL::y

 ! Declare methods
   CONTAINS
 GENERIC::OPERATOR(+)=>add
 GENERIC::OPERATOR(-)=>subtract
 GENERIC::OPERATOR(*)=>dot
 PROCEDURE,PASS::set_vec=>set_vec_sub
 PROCEDURE(addx),PASS,DEFERRED::add
 PROCEDURE(subtractx),PASS,DEFERRED::subtract
 PROCEDURE(dotx),PASS,DEFERRED::dot

  END TYPE vec

!!
!!

  ! Interfaces to deferred procedures
  ABSTRACT INTERFACE

 FUNCTION  addx(this,other) RESULT(add_vec)
   !
   ! Purpose:
   ! Add two vector
   !
   ! Record of revisions:
   ! Date  Programmer  Description of change
   ! 02/21/2011KePuOriginal code
   !
   IMPORT vec 
   IMPLICIT NONE
   CLASS(vec),INTENT(in)::this! This object
   CLASS(vec),INTENT(in)::other   ! The other object
   CLASS(vec),POINTER::add_vec! Return value

 END FUNCTION addx

!!

 FUNCTION subtractx(this,other) RESULT(subtract_vec)
   !
   ! Purpose:
   ! Subtract two vector
   !
   ! Reord of revisions:
   ! Date  Programmer  Description of change
   ! 02/21/2011KePuOriginal code
   !
   IMPORT vec
   IMPLICIT NONE
   CLASS(vec),INTENT(in)::this! This object
   CLASS(vec),INTENT(in)::other   ! The other object
   CLASS(vec),Pointer::subtract_vec   ! Return value
 END FUNCTION subtractx

!!

 FUNCTION dotx(this,other)
   !
   ! Purpose:
   ! Dot product of two vectors
   !
   ! Record of revisions:
   ! Date  Programmer  Description of change
   ! 02/21/2011KePuOriginal code
   !
   IMPORT vec
   IMPLICIT NONE
   CLASS(vec),INTENT(in)::this! This object
   CLASS(vec),INTENT(in)::other   ! The other object
   REAL::dotx ! Return value
 END FUNCTION dotx
  END INTERFACE

!!
!!

  ! Define methods
CONTAINS

  SUBROUTINE set_vec_sub(this,x,y)
!
! Purpose:
! Set coordinate of vector
!
! Record of revisions:
! Date  Programmer  Description of change
! 02/21/2011KePuOriginal code
!
IMPLICIT NONE

! Data dictionary:
CLASS(vec),INTENT(inout)::this ! Input object
REAL,INTENT(in)::x,y   ! Coordinate 

this%x=x
this%y=y 

  END SUBROUTINE set_vec_sub
END MODULE class_vec

--
--

Subclass vec3d will override all the functions and subroutines defined above

MODULE class_vec3d
  !
  ! Brief description:
  ! 1. Subclass of vec
  ! 2. Fields
  !  a. Inherited: real::x real::y
  !  b. Extends: real::z
  ! 3. Method
  !  a. set_vec
  !  b. Addition
  !  c. Subtraction
  !  d. Dot product
  !
  ! Record of revisions:
  ! Date  Programmer  Description of change
  ! 02/22/2011KePuOriginal code
  !
  USE class_vec ! Use parent class

  IMPLICIT NONE

  ! Type definition
  TYPE,EXTENDS(vec),PUBLIC::vec3d
 ! Fields
 REAL::z

 ! Declare methods
   CONTAINS
 PROCEDURE,PUBLIC,PASS::set_vec=>set_vec_3d
 PROCEDURE,PUBLIC,PASS::add=>add_fn
 PROCED

[Bug fortran/47844] New: Pointer-valued function: Provide wrong result when dereferenced automatically after list-write

2011-02-21 Thread Kdx1999 at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47844

   Summary: Pointer-valued function: Provide wrong result when
dereferenced automatically after list-write
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: minor
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: kdx1...@gmail.com


Hello,I'm trying to compile Example 15.20 in Stephen J.Chapman's book Fortran
95/2003 for Scientists & Engineers. The purpose of the function is simple:
"Return a pointer to every fifth element in a input rank 1 array".
--
--
Code:

PROGRAM test_pointer_value
  !
  ! Purpose:
  ! Test pointer valued function
  !
  ! Record of revisions:
  ! Date  Programmer  Description of change
  ! 02/22/2011KePuOriginal code
  !
  IMPLICIT NONE

  ! Data dictionary
  INTEGER,DIMENSION(10),TARGET::array=[1,3,5,7,9,11,13,15,17,19]! Array to be
test
  INTEGER,dimension(2)::arrar_fifth
  INTEGER,POINTER,DIMENSION(:)::ptr_array=>NULL()! Pointer to array
  INTEGER,POINTER,DIMENSION(:)::ptr_array_fifth=>NULL()  ! Pointer return every
fifth element of array

  ptr_array=>array  ! Initialization

  ptr_array_fifth=>every_fifth(ptr_array)
  WRITE(*,*)ptr_array_fifth
  WRITE(*,*)every_fifth(ptr_array)
CONTAINS
  FUNCTION every_fifth(ptr_array) RESULT(ptr_fifth)
!
! Purpose:
! To produce a pointer ot every fifth element in an
! input rand 1 array.
!
! Record of revisions:
! Date  Programmer  Description of change
! 02/22/2011KePuOriginal code
!
IMPLICIT NONE

INTEGER,POINTER,DIMENSION(:)::ptr_fifth
INTEGER,POINTER,DIMENSION(:),INTENT(in)::ptr_array
INTEGER::low
INTEGER::high

low=LBOUND(ptr_array,1)
high=UBOUND(ptr_array,1)
ptr_fifth=>ptr_array(low:high:5) 
  END FUNCTION every_fifth
END PROGRAM test_pointer_value 
--
--

The book says "The function can also be used in a location where an integer
array is expected. Inthat case, the pointer returned by the function will
automatically be dereferenced,and will print out the value by the pointer
returned from the function". But after ran the program, two result prompt on
the screen are different(The first line is right answer):
1   11
13

I'm not sure if it's a bug. Any help to my problem will be appreciated. Thank
you.


[Bug rtl-optimization/46002] ICE: in update_copy_costs, at ira-color.c:319 with -fira-algorithm=priority

2011-02-21 Thread cltang at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46002

--- Comment #4 from Chung-Lin Tang  2011-02-22 
03:23:24 UTC ---
Author: cltang
Date: Tue Feb 22 03:23:21 2011
New Revision: 170388

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170388
Log:
2011-02-21  Chung-Lin Tang  

PR rtl-optimization/46002
* ira-color.c (update_copy_costs): Change class intersection
test to reg_class_contents[] test of 'hard_regno'.

Modified:
trunk/gcc/ChangeLog
trunk/gcc/ira-color.c


[Bug target/47487] ICE in rs6000_output_function_epilogue, at config/rs6000/rs6000.c:21782 building 64bit libgo

2011-02-21 Thread doko at ubuntu dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47487

--- Comment #4 from Matthias Klose  2011-02-22 03:03:28 
UTC ---
libgo has configury bits for powerpc*-linux. that was my reason to assume that
Go is supported on powerpc.


[Bug target/43999] Gcc (lib1funcs.asm) doesn't build on ARM/Thumb2

2011-02-21 Thread jingyu at google dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43999

--- Comment #9 from Jing Yu  2011-02-22 01:53:11 UTC 
---
I am on leave from 02/01/2011 to 05/30/2011. I may not reply your
email during this period.

If you have Android toolchain questions/issues/requests, please
contact Doug (dougk...@google.com) or my manager Bhaskar
(bjanakira...@google.com).

Thanks,
Jing


[Bug target/43999] Gcc (lib1funcs.asm) doesn't build on ARM/Thumb2

2011-02-21 Thread m.k.edwards at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=43999

Michael K. Edwards  changed:

   What|Removed |Added

 CC||m.k.edwards at gmail dot
   ||com

--- Comment #8 from Michael K. Edwards  
2011-02-22 01:52:41 UTC ---
Correct patch (http://patchwork.ozlabs.org/patch/72260/) was applied to
mainline.  Apply to 4.5 branch?


[Bug target/47825] SSE bitwise operations on floats work -g, fail -O3

2011-02-21 Thread cck0011 at yahoo dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47825

--- Comment #7 from cck0011 at yahoo dot com 2011-02-22 00:54:17 UTC ---
(In reply to comment #5)
> The issue is that maskarray is initialized as array of ints but then you
> load it as array of floats, the scheduler re-orders those so you see
> a load from uninitialized stack:
> 
[looks puzzled; reads info page for gcc -fstrict-aliasing for the N + 1th time;
sudden look of comprehension dawns...]

"taking a pointer and casting gives undefined result..."

 Thank you Richard. That makes sense now given the context... -)

Thanks folks!


[Bug c++/46170] [4.4/4.5 Regression] g++ wrongly rejects pointer-to-member in template arguments

2011-02-21 Thread fang at csl dot cornell.edu
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46170

--- Comment #26 from David Fang  2011-02-22 
00:16:19 UTC ---
Friendly ping?


[Bug c/47842] New: gcc forces 16-byte stack alignment on Solaris i386, when SYSV requires word alignment

2011-02-21 Thread yuri at tsoft dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47842

   Summary: gcc forces 16-byte stack alignment on Solaris i386,
when SYSV requires word alignment
   Product: gcc
   Version: 4.5.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: c
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: y...@tsoft.com


Linux made a decision to switch to 16-byte alignment, but not others.

I know for a fact that Solaris is affected, I am not sure, but FreeBSD i386
might also be affected.

Please turn this behavior back to the one prescribed by specification for
Solaris (and FreeBSD if affected):
http://www.sco.com/developers/devspecs/abi386-4.pdf
section 3-10: "The stack is word aligned. Although the architecture does not
require any alignment of the stack, software convention and the operating
system requires that the stack be aligned on a word boundary."

Or please refer to the Sun/Oracle decision to change this behavior.


[Bug middle-end/42973] [4.4 regression] IRA apparently systematically making reload too busy on 2 address instructions with 3 operands

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42973

Jeffrey A. Law  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 CC||law at redhat dot com
 Resolution||FIXED

--- Comment #19 from Jeffrey A. Law  2011-02-21 23:46:07 
UTC ---
Fixed long ago.


[Bug middle-end/47790] [4.5/4.6 Regression] optimize_bitfield_assignment_op no longer works in 4.5.x

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47790

Jeffrey A. Law  changed:

   What|Removed |Added

   Priority|P3  |P2
 Status|UNCONFIRMED |NEW
   Last reconfirmed||2011.02.21 23:31:43
 CC||law at redhat dot com
 Ever Confirmed|0   |1


[Bug middle-end/45644] [4.6 Regression] 450.soplex in SPEC CPU 2006 is miscompiled

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=45644

Jeffrey A. Law  changed:

   What|Removed |Added

 CC||mbooth at redhat dot com

--- Comment #9 from Jeffrey A. Law  2011-02-21 23:09:31 
UTC ---
*** Bug 46452 has been marked as a duplicate of this bug. ***


[Bug target/46452] Apparently invalid optimization of bitfield access (4.5 regression?)

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46452

Jeffrey A. Law  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution||DUPLICATE
   Target Milestone|--- |4.6.0

--- Comment #3 from Jeffrey A. Law  2011-02-21 23:09:31 
UTC ---
Duplicate of 45644.  Fixed by:
2010-09-15  Martin Jambor  

PR middle-end/45644
* tree-sra.c (create_access): Check for bit-fields directly.

*** This bug has been marked as a duplicate of bug 45644 ***


[Bug c++/47746] [trans-mem] invalid conversion in gimple call, ICE verify_stmts failed

2011-02-21 Thread aldyh at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47746

Aldy Hernandez  changed:

   What|Removed |Added

 Status|WAITING |RESOLVED
 Resolution||FIXED


[Bug c++/47746] [trans-mem] invalid conversion in gimple call, ICE verify_stmts failed

2011-02-21 Thread aldyh at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47746

--- Comment #2 from Aldy Hernandez  2011-02-21 
22:49:36 UTC ---
Author: aldyh
Date: Mon Feb 21 22:49:34 2011
New Revision: 170377

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170377
Log:
PR 47746
* trans-mem.c (ipa_tm_insert_gettmclone_call): Verify type
compatibility in call.


Added:
branches/transactional-memory/gcc/testsuite/g++.dg/tm/pr47746.C
Modified:
branches/transactional-memory/gcc/ChangeLog.tm
branches/transactional-memory/gcc/trans-mem.c


[Bug c++/47746] [trans-mem] invalid conversion in gimple call, ICE verify_stmts failed

2011-02-21 Thread aldyh at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47746

Aldy Hernandez  changed:

   What|Removed |Added

 Status|UNCONFIRMED |WAITING
   Last reconfirmed||2011.02.21 22:42:35
 Ever Confirmed|0   |1

--- Comment #1 from Aldy Hernandez  2011-02-21 
22:42:35 UTC ---
Waiting approval:
http://gcc.gnu.org/ml/gcc-patches/2011-02/msg01384.html


[Bug fortran/47348] wrong string length with array constructor

2011-02-21 Thread tkoenig at netcologne dot de
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47348

--- Comment #9 from tkoenig at netcologne dot de  
2011-02-21 22:40:52 UTC ---
Hi Paul,

> (In reply to comment #7)
>> Any plan to backport the fix in revision 170317?
> 
> I had not planned so to do but would respond positively to popular pressure 
> how
> far back would you want to go?

I think 4.5 would be great.  Anything further back is probably unneeded
(the bug has remained undetected for a few years now...)

Thomas


[Bug target/46452] Apparently invalid optimization of bitfield access (4.5 regression?)

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46452

--- Comment #2 from Jeffrey A. Law  2011-02-21 22:14:15 
UTC ---
Also note that the code will not compile with the current trunk of gcc as the
definition of struct lens triggers a long standing bug with anonymous members
which was fixed in the GCC 4.6 development cycle:


struct lens {
unsigned int  ref;
enum lens_tag tag;
struct info  *info;
struct regexp*ctype;  /* NULL when recursive == 1 */
struct regexp*atype;
struct regexp*ktype;
struct regexp*vtype;
struct jmt   *jmt;/* NULL when recursive == 0 */
unsigned int  value : 1;
unsigned int  key : 1;
unsigned int  recursive : 1;
unsigned int  consumes_value : 1;
/* Whether we are inside a recursive lens or outside */
unsigned int  rec_internal : 1;
unsigned int  ctype_nullable : 1;
union {
/* Primitive lenses */
struct {   /* L_DEL uses both */
struct regexp *regexp; /* L_STORE, L_KEY */
struct string *string; /* L_VALUE, L_LABEL, L_SEQ, L_COUNTER */
};
/* Combinators */
struct lens *child; /* L_SUBTREE, L_STAR, L_MAYBE */
struct {/* L_UNION, L_CONCAT */
unsigned int nchildren;
struct lens **children;
};
struct {
struct lens *body;  /* L_REC */
/* We represent a recursive lens as two instances of struct
 * lens with L_REC. One has rec_internal set to 1, the other
 * has it set to 0. The one with rec_internal is used within
 * the body, the other is what is used from the 'outside'. This
 * is necessary to break the cycles inherent in recursive
 * lenses with reference counting. The link through alias is
 * set up in lns_check_rec, and not reference counted.
 *
 * Generally, any lens used in the body of a recursive lens is
 * marked with rec_internal == 1; lenses that use the recursive
 * lens 'from the outside' are marked with rec_internal ==
 * 0. In the latter case, we can assign types right away,
 * except for the ctype, which we never have for any recursive
 * lens.
 */
struct lens *alias;
struct jmt  *jmt;
};
};
};

Note there is a "jmt" at the toplevel of the structure and also within the
anonymous sub struct.  In the past GCC was too permissive in allowing this
situation to go unnoticed, GCC 4.6 will issue an error because  reference to
jmt is ambiguous.


[Bug fortran/41359] Wrong line numbers for debugging/profiling

2011-02-21 Thread burnus at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=41359

--- Comment #9 from Tobias Burnus  2011-02-21 
21:47:59 UTC ---
I think the current gcov output is OK:
1:1:program main
-:2:   implicit none
-:3:   integer :: a = 7
1:4:   if( a == 0 ) then
#:5:  print *, "a is null"
1:6:   else if( a > 0 ) then
1:7:  print *, "a is positif"
-:8:   else
#:9:  print *, "a is negatif"
-:   10:   end if
2:   11:end program

Though the following is still partially wrong:
  [foo.f90 : 6] if ([foo.f90 : 5] a > 0)
With patch:
  [foo.f90 : 6] if ([foo.f90 : 6] a > 0)


--- a/gcc/fortran/trans-stmt.c
+++ b/gcc/fortran/trans-stmt.c
@@ -718,6 +718,7 @@ gfc_trans_if_1 (gfc_code * code)
 {
   gfc_se if_se;
   tree stmt, elsestmt;
+  locus saved_loc;
   location_t loc;

   /* Check for an unconditional ELSE clause.  */
@@ -729,7 +730,10 @@ gfc_trans_if_1 (gfc_code * code)
   gfc_start_block (&if_se.pre);

   /* Calculate the IF condition expression.  */
+  gfc_save_backend_locus (&saved_loc);
+  gfc_set_backend_locus (&code->expr1->where);
   gfc_conv_expr_val (&if_se, code->expr1);
+  gfc_restore_backend_locus (&saved_loc);

   /* Translate the THEN clause.  */
   stmt = gfc_trans_code (code->next);


[Bug rtl-optimization/46002] ICE: in update_copy_costs, at ira-color.c:319 with -fira-algorithm=priority

2011-02-21 Thread hjl.tools at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46002

--- Comment #3 from H.J. Lu  2011-02-21 21:45:47 
UTC ---
Still fail on Linux/x86-64 as of revision 170371:

[hjl@gnu-34 gcc]$ /export/gnu/import/svn/gcc-test-intel64corei7/bld/gcc/xgcc
-B/export/gnu/import/svn/gcc-test-intel64corei7/bld/gcc/ -Os
-fira-algorithm=priority -c -o pr46002.o
/export/gnu/import/svn/gcc-test-intel64corei7/src-trunk/gcc/testsuite/gcc.c-torture/compile/pr46002.c
-march=corei7
/export/gnu/import/svn/gcc-test-intel64corei7/src-trunk/gcc/testsuite/gcc.c-torture/compile/pr46002.c:
In function \u2018foo\u2019:
/export/gnu/import/svn/gcc-test-intel64corei7/src-trunk/gcc/testsuite/gcc.c-torture/compile/pr46002.c:10:1:
internal compiler error: in update_copy_costs, at ira-color.c:318
Please submit a full bug report,
with preprocessed source if appropriate.
See  for instructions.
[hjl@gnu-34 gcc]$


[Bug target/47822] [4.6 Regression] Multiple test suite failures due to revision 170321

2011-02-21 Thread mrs at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47822

--- Comment #21 from mrs at gcc dot gnu.org  2011-02-21 
21:38:23 UTC ---
Author: mrs
Date: Mon Feb 21 21:38:21 2011
New Revision: 170376

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170376
Log:
PR target/47822
* config/darwin-protos.h (darwin_init_cfstring_builtins): Return a
tree so we can get save the type.
* config/i386/darwin.h (SUBTARGET_INIT_BUILTINS): Reserve builtin slot
for CFString instead of trying to use past the end of the builtins.
* config/i386/i386.c (IX86_BUILTIN_CFSTRING): Likewise.
* config/rs6000/rs6000-builtin.def (RS6000_BUILTIN_CFSTRING): Likewise.
* config/rs6000/darwin.h (SUBTARGET_INIT_BUILTINS): Likewise.
* config/darwin.c (DARWIN_BUILTIN_CFSTRINGMAKECONSTANTSTRING):
Rename to darwin_builtin_cfstring.
(darwin_init_cfstring_builtins): Return the built type.

Modified:
trunk/gcc/ChangeLog
trunk/gcc/config/darwin-protos.h
trunk/gcc/config/darwin.c
trunk/gcc/config/i386/darwin.h
trunk/gcc/config/i386/i386.c
trunk/gcc/config/rs6000/darwin.h
trunk/gcc/config/rs6000/rs6000-builtin.def


[Bug target/46452] Apparently invalid optimization of bitfield access (4.5 regression?)

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46452

Jeffrey A. Law  changed:

   What|Removed |Added

 CC||law at redhat dot com

--- Comment #1 from Jeffrey A. Law  2011-02-21 21:33:57 
UTC ---
You'll also need:

  readline-devel.i386
  libselinux-devel.i686

I did manage to get it to segfault.  But I haven't started reducing the scope
of the testcase yet.


[Bug target/47822] [4.6 Regression] Multiple test suite failures due to revision 170321

2011-02-21 Thread mikestump at comcast dot net
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47822

--- Comment #20 from Mike Stump  2011-02-21 
21:02:16 UTC ---
Ah, never mind, we have another thread going where the problem was pointed out.
 Sorry for missing it.


[Bug target/47822] [4.6 Regression] Multiple test suite failures due to revision 170321

2011-02-21 Thread mikestump at comcast dot net
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47822

--- Comment #19 from Mike Stump  2011-02-21 
20:58:35 UTC ---
?  The patch does touch rs6000 is the same way as we touch i386.  I think there
is an additional issue on ppc.  My previous patch is necessary, but not
sufficient.  So, if someone has a rs6000, I'll fix it, if you point out the
line that dies or the data structure that it was playing with.


[Bug target/47840] [4.4/4.5/4.6 Regression] incorrect _mm256_insert_epi{32,64} implementations

2011-02-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47840

Uros Bizjak  changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution||FIXED

--- Comment #5 from Uros Bizjak  2011-02-21 20:06:03 
UTC ---
Fixed.


[Bug target/47840] [4.4/4.5/4.6 Regression] incorrect _mm256_insert_epi{32,64} implementations

2011-02-21 Thread uros at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47840

--- Comment #4 from uros at gcc dot gnu.org 2011-02-21 20:05:02 UTC ---
Author: uros
Date: Mon Feb 21 20:04:57 2011
New Revision: 170373

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170373
Log:
PR target/47840
* config/i386/avxintrin.h (_mm256_insert_epi32): Use _mm_insert_epi32.
(_mm256_insert_epi64): Use _mm_insert_epi64.


Modified:
branches/gcc-4_4-branch/gcc/ChangeLog
branches/gcc-4_4-branch/gcc/config/i386/avxintrin.h


[Bug target/47840] [4.4/4.5/4.6 Regression] incorrect _mm256_insert_epi{32,64} implementations

2011-02-21 Thread uros at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47840

--- Comment #3 from uros at gcc dot gnu.org 2011-02-21 20:02:08 UTC ---
Author: uros
Date: Mon Feb 21 20:02:02 2011
New Revision: 170372

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170372
Log:
PR target/47840
* config/i386/avxintrin.h (_mm256_insert_epi32): Use _mm_insert_epi32.
(_mm256_insert_epi64): Use _mm_insert_epi64.


Modified:
branches/gcc-4_5-branch/gcc/ChangeLog
branches/gcc-4_5-branch/gcc/config/i386/avxintrin.h


[Bug target/47840] [4.4/4.5/4.6 Regression] incorrect _mm256_insert_epi{32,64} implementations

2011-02-21 Thread uros at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47840

--- Comment #2 from uros at gcc dot gnu.org 2011-02-21 19:59:55 UTC ---
Author: uros
Date: Mon Feb 21 19:59:52 2011
New Revision: 170371

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170371
Log:
PR target/47840
* config/i386/avxintrin.h (_mm256_insert_epi32): Use _mm_insert_epi32.
(_mm256_insert_epi64): Use _mm_insert_epi64.


Modified:
trunk/gcc/ChangeLog
trunk/gcc/config/i386/avxintrin.h


[Bug bootstrap/47230] [4.6 Regression] gcc fails to bootstrap on alpha in stage2 with "relocation truncated to fit: GPREL16 against ..."

2011-02-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47230

Uros Bizjak  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution||FIXED

--- Comment #2 from Uros Bizjak  2011-02-21 19:47:01 
UTC ---
Apparently fixed [1].

[1] http://gcc.gnu.org/ml/gcc-testresults/2011-02/msg02323.html


[Bug target/47840] [4.4/4.5/4.6 Regression] incorrect _mm256_insert_epi{32,64} implementations

2011-02-21 Thread ubizjak at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47840

Uros Bizjak  changed:

   What|Removed |Added

 Status|UNCONFIRMED |ASSIGNED
   Last reconfirmed||2011.02.21 19:45:17
 AssignedTo|unassigned at gcc dot   |ubizjak at gmail dot com
   |gnu.org |
   Target Milestone|--- |4.4.6
Summary|incorrect   |[4.4/4.5/4.6 Regression]
   |_mm256_insert_epi{32,64}|incorrect
   |implementations |_mm256_insert_epi{32,64}
   ||implementations
 Ever Confirmed|0   |1

--- Comment #1 from Uros Bizjak  2011-02-21 19:45:17 
UTC ---
A typo, following patch should fix it:

Index: avxintrin.h
===
--- avxintrin.h(revision 170367)
+++ avxintrin.h(working copy)
@@ -737,7 +737,7 @@
 _mm256_insert_epi32 (__m256i __X, int __D, int const __N)
 {
   __m128i __Y = _mm256_extractf128_si256 (__X, __N >> 2);
-  __Y = _mm_insert_epi16 (__Y, __D, __N % 4);
+  __Y = _mm_insert_epi32 (__Y, __D, __N % 4);
   return _mm256_insertf128_si256 (__X, __Y, __N >> 2);
 }

@@ -762,7 +762,7 @@
 _mm256_insert_epi64 (__m256i __X, int __D, int const __N)
 {
   __m128i __Y = _mm256_extractf128_si256 (__X, __N >> 1);
-  __Y = _mm_insert_epi16 (__Y, __D, __N % 2);
+  __Y = _mm_insert_epi64 (__Y, __D, __N % 2);
   return _mm256_insertf128_si256 (__X, __Y, __N >> 1);
 }
 #endif


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread dave at hiauly1 dot hia.nrc.ca
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

--- Comment #12 from dave at hiauly1 dot hia.nrc.ca 2011-02-21 19:38:33 UTC ---
On Mon, 21 Feb 2011, jakub at gcc dot gnu.org wrote:

> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802
> 
> --- Comment #11 from Jakub Jelinek  2011-02-21 
> 18:58:27 UTC ---
> In libgfortran it is not the user, but libgfortran implementation, so it makes
> sure it always passes buffer of at least 26 bytes.  If there are OSes where we
> can't trust ctime_r, we could either blacklist them (or whitelist the known
> good ones), or on some of them try to supply larger buffer (is there any
> implementation that would overflow say 256 or 1024 bytes)?

The gnulib thread that led to the autoconf recommendation suggests using
strftime.  localtime_r is thread safe.

Besides the buffer overflow issues, asctime_r and ctime_r do not honor
i18n, and incorrect values are produced for some input values.  For example,
some Solaris versions silently generate incorrect values for timestamps
before 1900.

See:
http://www.mail-archive.com/bug-gnulib@gnu.org/msg02248.html

Dave


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #15 from Jakub Jelinek  2011-02-21 
19:23:36 UTC ---
Created attachment 23431
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23431
variant 3

This is code-wide like variant 1, but configury is actually checking for the
bug (slightly adapted EH-compatible --gc-section support test can be used for
this).

So, any preferences among these?  Perhaps another alternative would be to use
.gcc_except_table.startup.main and similar, though not sure how hard would that
be.


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #14 from Jakub Jelinek  2011-02-21 
19:21:49 UTC ---
Created attachment 23430
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23430
variant 2

This one will just disable .gcc_except_table.foo for the buggy linkers (in
addition to the even more buggy (and older) ones).


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

Jakub Jelinek  changed:

   What|Removed |Added

  Attachment #23428|0   |1
is obsolete||

--- Comment #13 from Jakub Jelinek  2011-02-21 
19:20:32 UTC ---
Created attachment 23429
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23429
variant 1

So, a few untested or only very lightly tested alternatives.

This one is basically the above configury check plus varasm change to avoid
using .text.startup.*, .text.exit.* etc. with broken linkers.


[Bug regression/47836] Some Cross Compiler can't build target-libiberty or target-zlib

2011-02-21 Thread pinskia at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47836

--- Comment #1 from Andrew Pinski  2011-02-21 
19:20:20 UTC ---
Why does these libraries fail?


[Bug bootstrap/47806] Failure to build cross-combiner to powerpc-ibm-aix6.0

2011-02-21 Thread steven at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47806

Steven Bosscher  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution||INVALID

--- Comment #6 from Steven Bosscher  2011-02-21 
19:09:57 UTC ---
.


[Bug lto/47841] [4.6 Regression] New guality test failures

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47841

Jakub Jelinek  changed:

   What|Removed |Added

 CC||jakub at gcc dot gnu.org

--- Comment #2 from Jakub Jelinek  2011-02-21 
19:02:10 UTC ---
Saying these are regressions is weird, -flto has pretty much broken -g support
and lots of guality tests don't FAIL just because of being flagged as
UNSUPPORTED (as the tests conservatively assume some of the errors might be gdb
bugs).


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

--- Comment #11 from Jakub Jelinek  2011-02-21 
18:58:27 UTC ---
In libgfortran it is not the user, but libgfortran implementation, so it makes
sure it always passes buffer of at least 26 bytes.  If there are OSes where we
can't trust ctime_r, we could either blacklist them (or whitelist the known
good ones), or on some of them try to supply larger buffer (is there any
implementation that would overflow say 256 or 1024 bytes)?


[Bug lto/47841] [4.6 Regression] New guality test failures

2011-02-21 Thread hjl.tools at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47841

H.J. Lu  changed:

   What|Removed |Added

 CC||rguenth at gcc dot gnu.org

--- Comment #1 from H.J. Lu  2011-02-21 18:53:15 
UTC ---
It may be caused by revision 170359:

http://gcc.gnu.org/ml/gcc-cvs/2011-02/msg00904.html


[Bug lto/47841] New: [4.6 Regression] New guality test failures

2011-02-21 Thread hjl.tools at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47841

   Summary: [4.6 Regression] New guality test failures
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: lto
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: hjl.to...@gmail.com


On Linux/ia32, revision 170359 gave

FAIL: gcc.dg/guality/sra-1.c  -O2 -flto  line 43 a.j == 14
FAIL: gcc.dg/guality/sra-1.c  -O2 -flto -flto-partition=none  line 43 a.j == 14
FAIL: gcc.dg/guality/vla-1.c  -O2 -flto  line 17 sizeof (a) == 6
FAIL: gcc.dg/guality/vla-1.c  -O2 -flto -flto-partition=none  line 17 sizeof
(a) == 6

Revision 170354 is OK.


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

--- Comment #10 from Jeffrey A. Law  2011-02-21 18:51:09 
UTC ---
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 02/21/11 11:09, burnus at gcc dot gnu.org wrote:
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802
> 
> --- Comment #8 from Tobias Burnus  2011-02-21 
> 18:08:13 UTC ---
> (In reply to comment #6)
>> Certain implementations pass in a buffer size
>> parameter to deal with that problem, others (glibc) presumably do some
>> checking before dumping results into the user supplied buffer to make
>> sure they don't exceed the 26 bytes or whatever the minimum size of hte
>> buffer is supposed to be.
> 
> Baring implementation bugs I would claim that all two-argument ctime_r
> implementations should work with 26 byte arguments as POSIX has been defined 
> as
> such:
> 
> "The ctime_r() function shall convert the calendar time pointed to by clock to
> local time in exactly the same form as ctime() and put the string into the
> array pointed to by buf (which shall be at least 26 bytes in size) and return
> buf.
> Unlike ctime(), the thread-safe version ctime_r() is not required to set
> tzname."
> http://pubs.opengroup.org/onlinepubs/009695399/functions/ctime.html
The problem is some vendors mucked up their implementations and don't
stay within the 26 byte limit for bogus input values.  And just because
their implementations are correct *today* doesn't mean that they're
correct on the systems which might be running this code.  There's people
still running very old systems out there.

Furthermore, no implementation I'm aware of can catch teh case where the
user supplied buffer is less than 26 bytes.

Jeff
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Fedora - http://enigmail.mozdev.org/

iQEcBAEBAgAGBQJNYrQNAAoJEBRtltQi2kC7f28IAJdrRtgUiAewCofhz6jWNcZN
DRBjZLybLfNx0sHX6czLql/1q1MNmJdtc0Vwmp6VnGHkoZtepY+HRwyu/6Y/5nAi
cLaNHSkeOAKwR+JElzOqczRKxli/YBzYtgcTAJFD2nNTB0gK5h53hhR/Pup2JLmC
PSddl3cDUdYdl9KRydRJpU0Z8hOC03fd70MMIxO//H12HTzpHXDsjCA8PrZTcY0l
hEwyKRgw81zwB0+LHt0E14v9XhMm9t3U81FCngo1W/EKtEqAsGFHaMiZXl+ums0H
9LSIE53e10Tq5R6V4LpJhOa3Tpk7G/hbGraojdbq6w6unt/7nfVoZB4G4+yq9J8=
=cpqO
-END PGP SIGNATURE-


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

--- Comment #9 from Jeffrey A. Law  2011-02-21 18:49:02 
UTC ---
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 02/21/11 10:41, jakub at gcc dot gnu.org wrote:
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802
> 
> Jakub Jelinek  changed:
> 
>What|Removed |Added
> 
>  CC||jakub at gcc dot gnu.org
> 
> --- Comment #7 from Jakub Jelinek  2011-02-21 
> 17:41:20 UTC ---
> Well, we don't want to use ctime because it is not thread-safe.
Right.

> glibc ctime_r implementation should be safe if the passed buffer is at least 
> 26
> bytes long, it calls internally asctime, which is:
I'm aware that glibc's variant is safe from bogus input causing a buffer
overrun.  The problem is not every vendor's implementation is safe with
regards to buffer overruns due to bogus input.

Furthermore, I don't think any of the implementations are safe if the
user supplied buffer is less than 26 bytes.  So if an idiot programmer
called ctime_r with too small a buffer, then we've got a buffer overrun
and a vector for a security attack.

jeff
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Fedora - http://enigmail.mozdev.org/

iQEcBAEBAgAGBQJNYrOUAAoJEBRtltQi2kC7KPMH/25knyvBbLrN5lHbuBHJ9sh3
eGFMuym9/5yXRn/oAesxoPA/PqakfULGUgecF7168H+N+ECoHhn53D/clY5ea7Ti
6yuLb0a2rFMtZpn+BxB4JFzW3hdDXKjj8nIZiT5PuZX7yjLfIYlQZiVBpVG0IpfU
wGGFXHUnGM1j4YDB0tStZnzU+4/rkXml2pmjBzApjGGDrMRXarrrCD4cEffBGZOc
xnVLfcarKQ/wnltrEs3PCogG8zwpu4Gp6jJLnZDYNF4Rk8K4RhsvmeRzFND0n0ZM
3w9dBEQXF3AqmrWVBX08krgXornXN1n7zwj3bZdM6o6jH6iW5NY4vsyx4SRtZ7Q=
=JcEq
-END PGP SIGNATURE-


[Bug target/47840] New: incorrect _mm256_insert_epi{32,64} implementations

2011-02-21 Thread kretz at kde dot org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47840

   Summary: incorrect _mm256_insert_epi{32,64} implementations
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: target
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: kr...@kde.org


see avxintrin.h:
_mm256_insert_epi32 and _mm256_insert_epi64 use _mm_insert_epi16 internally

if __OPTIMIZE__ is not defined they use _mm_insert_epi32/64 internally - as I
would have expected.

I also checked 4.5 and 4.4, and it seems the bug was not noticed in any branch
yet.


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread burnus at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

--- Comment #8 from Tobias Burnus  2011-02-21 
18:08:13 UTC ---
(In reply to comment #6)
> Certain implementations pass in a buffer size
> parameter to deal with that problem, others (glibc) presumably do some
> checking before dumping results into the user supplied buffer to make
> sure they don't exceed the 26 bytes or whatever the minimum size of hte
> buffer is supposed to be.

Baring implementation bugs I would claim that all two-argument ctime_r
implementations should work with 26 byte arguments as POSIX has been defined as
such:

"The ctime_r() function shall convert the calendar time pointed to by clock to
local time in exactly the same form as ctime() and put the string into the
array pointed to by buf (which shall be at least 26 bytes in size) and return
buf.
Unlike ctime(), the thread-safe version ctime_r() is not required to set
tzname."
http://pubs.opengroup.org/onlinepubs/009695399/functions/ctime.html

The definition goes back to POSIX (SUSv2) of February 1997 - and IEEE Std
1003.1c-1995. One should assume that within the last 15 years they vendors
managed to get the 26-byte buffer issue correct ...

(How to deal with a three-argument version is a separate question; different
vendors have probably different arguments, though buflen could be a more common
choice.)


> I guess the question we need to ask is how important are these routines

>From he non-normative part of POSIX:

"The ctime_r() function is thread-safe and shall return values in a
user-supplied buffer instead of possibly using a static data area that may be
overwritten by each call."


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #12 from Jakub Jelinek  2011-02-21 
17:51:00 UTC ---
HAVE_GAS_HIDDEN and HAVE_COMDAT_GROUP checks use ld --version date too.


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread steven at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #11 from Steven Bosscher  2011-02-21 
17:47:14 UTC ---
(In reply to comment #7)

Interesting, I didn't know that :-)
Do you have an example?


[Bug rtl-optimization/46178] gcc.target/i386/(u)divmod-[58].c FAIL: ICE: in dec_register_pressure, at ira-lives.c:215 with -fira-algorithm=priority

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46178

Jeffrey A. Law  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 CC||law at redhat dot com
 Resolution||FIXED
   Target Milestone|--- |4.6.0
  Known to fail|4.6.0   |

--- Comment #3 from Jeffrey A. Law  2011-02-21 17:44:27 
UTC ---
Fixed.


[Bug rtl-optimization/46002] ICE: in update_copy_costs, at ira-color.c:319 with -fira-algorithm=priority

2011-02-21 Thread law at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46002

--- Comment #2 from Jeffrey A. Law  2011-02-21 17:43:18 
UTC ---
Author: law
Date: Mon Feb 21 17:43:15 2011
New Revision: 170370

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170370
Log:

PR rtl-optimization/46178
* gcc.target/i386/pr46178.c: New test.

PR rtl-optimization/46002
* gcc.c-torture/compile/pr46002.c: New test.

Added:
trunk/gcc/testsuite/gcc.c-torture/compile/pr46002.c
trunk/gcc/testsuite/gcc.target/i386/pr46178.c
Modified:
trunk/gcc/testsuite/ChangeLog


[Bug rtl-optimization/46178] gcc.target/i386/(u)divmod-[58].c FAIL: ICE: in dec_register_pressure, at ira-lives.c:215 with -fira-algorithm=priority

2011-02-21 Thread law at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46178

--- Comment #2 from Jeffrey A. Law  2011-02-21 17:43:18 
UTC ---
Author: law
Date: Mon Feb 21 17:43:15 2011
New Revision: 170370

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170370
Log:

PR rtl-optimization/46178
* gcc.target/i386/pr46178.c: New test.

PR rtl-optimization/46002
* gcc.c-torture/compile/pr46002.c: New test.

Added:
trunk/gcc/testsuite/gcc.c-torture/compile/pr46002.c
trunk/gcc/testsuite/gcc.target/i386/pr46178.c
Modified:
trunk/gcc/testsuite/ChangeLog


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

Jakub Jelinek  changed:

   What|Removed |Added

 CC||jakub at gcc dot gnu.org

--- Comment #7 from Jakub Jelinek  2011-02-21 
17:41:20 UTC ---
Well, we don't want to use ctime because it is not thread-safe.
glibc ctime_r implementation should be safe if the passed buffer is at least 26
bytes long, it calls internally asctime, which is:
/* Like asctime, but write result to the user supplied buffer.  The
   buffer is only guaranteed to be 26 bytes in length.  */
char *
__asctime_r (const struct tm *tp, char *buf)
{
  return asctime_internal (tp, buf, 26);
}
and asctime_internal uses the passed buflen as second argument to snprintf.


[Bug c++/47833] ICE during GC in gt_ggc_mx_pending_template

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47833

--- Comment #2 from Jakub Jelinek  2011-02-21 
17:32:22 UTC ---
Different testcase at https://bugzilla.redhat.com/attachment.cgi?id=479920


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread hubicka at ucw dot cz
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #10 from Jan Hubicka  2011-02-21 17:30:00 
UTC ---
Testing datestamp seems resonable to me. I can do the changes needed to avoid
.text subsections then
(basically the elf implementation should then return NULL)

Honza


[Bug c++/44118] ICE: in instantiate_decl, at cp/pt.c:16657

2011-02-21 Thread paolo.carlini at oracle dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=44118

Paolo Carlini  changed:

   What|Removed |Added

 CC||rearnsha at gcc dot gnu.org

--- Comment #8 from Paolo Carlini  2011-02-21 
17:24:32 UTC ---
*** Bug 44737 has been marked as a duplicate of this bug. ***


[Bug c++/44737] ICE in instantiate_decl

2011-02-21 Thread paolo.carlini at oracle dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=44737

Paolo Carlini  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution||DUPLICATE
  Known to fail||

--- Comment #5 from Paolo Carlini  2011-02-21 
17:24:32 UTC ---
Fixed.

*** This bug has been marked as a duplicate of bug 44118 ***


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #9 from Jakub Jelinek  2011-02-21 
17:23:02 UTC ---
Created attachment 23428
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23428
gcc46-pr46790-configury.patch

Completely untested draft of a configury patch (still no code changes to
actually revert Honza's changes ifdef HAVE_GLD_GC_BUG).  I think writing a
testcase that wouldn't use date strings would be quite entertaining (it would
need to be written in assembler, but in a way that it assembles and does the
right thing on all targets).


[Bug c++/46831] [4.6 Regression][C++0x] Crash when it tries to do an invalid ICS with a conversion function template

2011-02-21 Thread paolo.carlini at oracle dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46831

Paolo Carlini  changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution||FIXED

--- Comment #9 from Paolo Carlini  2011-02-21 
17:20:53 UTC ---
Fixed.


[Bug middle-end/46790] [4.6 regression] EH failures in libstdc++ testsuite with --gc-sections and GNU ld 2.18

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46790

--- Comment #8 from Jakub Jelinek  2011-02-21 
17:14:10 UTC ---
So, I've tried a few linkers from various RHEL/Fedora distros, and narrowed it
down to the fact that 20071102 ld still fails, while 20080208 ld already works.
There have been pretty big --gc-sections changes in between, starting with:
http://sources.redhat.com/ml/binutils/2007-12/msg0.html
series and then its follow-ups BZ#5526 and BZ#5604.


[Bug c++/47207] [4.6 Regression] [C++0x] ICE: in decl_constant_var_p, at cp/decl2.c:3563 on invalid code

2011-02-21 Thread paolo.carlini at oracle dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47207

Paolo Carlini  changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution||FIXED

--- Comment #4 from Paolo Carlini  2011-02-21 
17:07:37 UTC ---
Fixed.


[Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification

2011-02-21 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

Richard Guenther  changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Last reconfirmed||2011.02.21 17:04:46
 Ever Confirmed|0   |1

--- Comment #2 from Richard Guenther  2011-02-21 
17:04:46 UTC ---
We merge the decls during symtab merging.  The prevailing one looks for example
like

(gdb) call debug_tree (prevailing->decl)
 
unit size 
align 32 symtab 0 alias set -1 canonical type 0x77ee3498 precision
32 min  max 
pointer_to_this >
used public static SI file mod.f90 line 2 col 0 size  unit size 
align 32 context >

while the non-prevailing one is

 
unit size 
align 32 symtab 0 alias set -1 canonical type 0x77ee3498 precision
32 min  max 
pointer_to_this >
used public ignored external SI file t.f90 line 4 col 0 size  unit size 
align 32>

note that it is public and external and has a NULL DECL_CONTEXT.

The C frontend for a local extern declaration has

 
unit size 
align 32 symtab 0 alias set -1 canonical type 0x77ee6498 precision
32 min  max 
pointer_to_this >
used public external common SI defer-output file t.c line 8 col 15 size
 unit size 
align 32 context >

thus puts it into function context.  This decl is solely used for the BLOCK
tree, in the function a public external global var is used (which is
then merged with the static one from the other TU).

void foo (void)
{
  extern int i;
  i = 0;
}

---

int i;



Simplified Fortran testcase:

MODULE globalvar_mod
integer:: xstop
CONTAINS
END MODULE globalvar_mod

---

MODULE PEC_mod
CONTAINS
SUBROUTINE PECapply(Ex)
USE globalvar_mod, ONLY : xstop
real(kind=8), dimension(1:xstop), intent(inout) :: Ex
END SUBROUTINE PECapply
END MODULE PEC_mod

it's important that PECapply is inside a module.

The decl is built by gfc_get_symbol_decl and put into the function via
gfc_add_decl_to_function - which is I think in general bogus for
imported decls.  Its context is later cleared in pushdecl, but the
variable isn't removed from BLOCK_VARS.

I think we want to avoid gfc_add_decl_to_function in the first place.


[Bug tree-optimization/47838] FAIL: gcc.dg/tree-ssa/foldconst-2.c scan-tree-dump-not optimized "fundamentals..0"

2011-02-21 Thread mikpe at it dot uu.se
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47838

Mikael Pettersson  changed:

   What|Removed |Added

 CC||mikpe at it dot uu.se

--- Comment #2 from Mikael Pettersson  2011-02-21 
17:03:34 UTC ---
I see the foldconst-2 failure also on powerpc64-linux, ever since the 20100904
trunk snapshot.


[Bug libfortran/47802] [4.6 Regression] libgfortran/intrinsics/ctime.c:75:3: error: too few arguments to function 'ctime_r'

2011-02-21 Thread law at redhat dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802

--- Comment #6 from Jeffrey A. Law  2011-02-21 16:56:18 
UTC ---
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 02/18/11 13:56, dave at hiauly1 dot hia.nrc.ca wrote:
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47802
> 
> --- Comment #2 from dave at hiauly1 dot hia.nrc.ca 2011-02-18 20:56:54 UTC ---
>> Is there no way to get a posix compliant ctime?  Alternatively, we'll need
>> autoconf magic to detect the extra arg.  I know at one time it was relatively
>> common, so autoconf magic might be around somewhere.  Assuming it is you just
>> have to do something like
>>
>>
>> #if defined (oddballctime)
>>   *date = ctime_r (&now, cbuf, CSZ);
>> #else
>>   *date = ctime_r (&now, cbuf);
>> #endif
> 
> Using ctime_r is a bit of a can of worms.  The GNU autoconf manual recommends
> not using ctime_r unless the inputs are known to be within certain limits.
Correct.  The problem is some implementations can trigger buffer
overflows for bad input.  Certain implementations pass in a buffer size
parameter to deal with that problem, others (glibc) presumably do some
checking before dumping results into the user supplied buffer to make
sure they don't exceed the 26 bytes or whatever the minimum size of hte
buffer is supposed to be.

Even for checking versions like glibc, if the wrong sized buffer is
passed in, then it'll probably break.

I guess the question we need to ask is how important are these routines
and should we be issuing warnings when they are used, much like is done
with gets.  If we don't need them, I'd much prefer to see them go away
as they're a rats nest of security issues.

Just a quick glance at the code in libgfortran/ctime.c and I'm pretty
sure it's vulnerable to a buffer overflow attack.


Jeff
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.11 (GNU/Linux)
Comment: Using GnuPG with Fedora - http://enigmail.mozdev.org/

iQEcBAEBAgAGBQJNYpkoAAoJEBRtltQi2kC7HwcH/3IEgG2sh265kwu9kKQQ87gf
um1qKykJo4/Ph3W4UF7q1G26mw5luemVE6ga4+4nEzpivH0hzgsxWADDPXjQzq26
tqUXwh0nKi5665O1rcW88EZpej5J0MDLtUBTQXv1DipQWDBa/YjDqrmO4IRkw+MK
QlkgPvCqosS1wvlbVJ9xKpTn2XY8tVTPdLlAMI3iBbbtDcsWMdKxaG5mpnhh8P4i
HkVepfpRr5RtpuVN3SJ6AWhqR0PQgS1e2PB2WbbY8bvNy5ev1GggJZj/3j101jza
/QseJ16lj3CqOMHCppHOhXGL8bxMFW17AWv/hL74+gTn9rZCH/JUjOQ+YzRgs0A=
=SpA9
-END PGP SIGNATURE-


[Bug c/47772] warnings from -Wmissing-field-initializers contradict documentation

2011-02-21 Thread webmas...@sky-siteweb.com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47772

Jonathan 'Sky' Squirawski  changed:

   What|Removed |Added

 CC||webmas...@sky-siteweb.com

--- Comment #2 from Jonathan 'Sky' Squirawski  
2011-02-21 16:55:39 UTC ---
I've the same problem with gcc 4.5.2.

Here another test case:

/*==*/
typedef struct bar_t {
int a;
int b;
} bar_t;

typedef struct foo_ok_t {
int   bar;
bar_t foo;
} foo_ok_t;

typedef struct foo_nok_t {
bar_t bar;
bar_t foo;
} foo_nok_t;

int main(void) {
foo_ok_t foo_ok;
foo_nok_t foo_nok;

foo_ok = (foo_ok_t){
.bar = 32,
};

foo_nok = (foo_nok_t){
.bar = (bar_t){ .a = 32, .b = 42 },
};

return 0;
}
/*==*/


The first assignment doesn't trigger any warning, but the second one gives:
test.c:29:5: warning: missing initializer
test.c:29:5: warning: (near initialization for ‘(anonymous).foo’)


[Bug fortran/47839] ICE in dwarf2out.c:add_AT_specification

2011-02-21 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

--- Comment #1 from Richard Guenther  2011-02-21 
16:19:20 UTC ---
--- a.f90

MODULE globalvar_mod
integer:: xstart, ystart, zstart, xstop, ystop, zstop
CONTAINS
END MODULE globalvar_mod

--- b.f90

MODULE PEC_mod
CONTAINS
SUBROUTINE PECapply(Ex,Ey,Ez)
USE globalvar_mod, ONLY : xstart, ystart, zstart, xstop, ystop, zstop
real(kind=8), dimension(xstart:xstop+1,ystart:ystop+1,zstart:zstop+1),  &
intent(inout) :: Ex, Ey, Ez
END SUBROUTINE PECapply
END MODULE PEC_mod


> gfortran a.f90 b.f90 -flto -flto-partition=none -r -nostdlib -g
lto1: internal compiler error: in add_AT_specification, at dwarf2out.c:7558
Please submit a full bug report,
with preprocessed source if appropriate.
See  for instructions.


[Bug fortran/47839] New: ICE in dwarf2out.c:add_AT_specification

2011-02-21 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47839

   Summary: ICE in dwarf2out.c:add_AT_specification
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Keywords: lto
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: rgue...@gcc.gnu.org


Building 459.GemsFDTD (and 416.gamess) with -O3 -ffast-math -flto -g ICEs
because the Fortran frontend seemingly puts imported variables in the
BLOCK tree of the imported function and does not mark them external.

The variable in question is huy_param from huygens_mod, imported from
nft_store

SUBROUTINE NFT_Store(Ex,Ey,Ez,Hx,Hy,Hz,t,ts)

USE excite_mod,  ONLY : excitation
USE huygens_mod, ONLY : Huy_param, HuyPulseType

and

MODULE Huygens_mod
...
real(kind=rfp), dimension(excite_max_no_param), PUBLIC :: Huy_param


I tried to create a small testcase but failed sofar.  It doesn't ICE
with -flto-partition=none but it does with -flto-partition=1to1.

With partially linking 459.GemsFDTD I get the ICE with

/abuild/rguenther/install-trunk/usr/local/bin/gfortran globalvar.f90 PEC.f90 -o
GemsFDTD -flto -flto-partition=none -r -nostdlib -O -g

which is then obviously related to a different variable.  Trying to
reduce the sources now.


[Bug rtl-optimization/47477] [4.6 regression] Sub-optimal mov at end of method

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47477

Jakub Jelinek  changed:

   What|Removed |Added

   Target Milestone|4.6.0   |4.7.0


[Bug debug/47106] -fcompare-debug failure (length) with -fpartial-inlining -flto -fconserve-stack

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47106

--- Comment #17 from Jakub Jelinek  2011-02-21 
15:53:54 UTC ---
Author: jakub
Date: Mon Feb 21 15:53:49 2011
New Revision: 170366

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170366
Log:
PR debug/47106
* g++.dg/debug/pr47106.C: Require effective target lto.

Modified:
trunk/gcc/testsuite/ChangeLog
trunk/gcc/testsuite/g++.dg/debug/pr47106.C


[Bug middle-end/38219] gcc.dg/tree-ssa/vrp47.c fails on powerpc

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38219

--- Comment #11 from John David Anglin  2011-02-21 
15:51:59 UTC ---
Still fails on hppa1.1-hp-hpux10.20 with 4.6.0 revision 170207.


[Bug c++/47207] [4.6 Regression] [C++0x] ICE: in decl_constant_var_p, at cp/decl2.c:3563 on invalid code

2011-02-21 Thread jason at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47207

--- Comment #3 from Jason Merrill  2011-02-21 
15:35:52 UTC ---
Author: jason
Date: Mon Feb 21 15:35:44 2011
New Revision: 170365

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170365
Log:
PR c++/47207
* decl2.c (decl_constant_var_p): A constexpr var needs an
initializer to be constant.
* semantics.c (cxx_eval_constant_expression): Complain about
constexpr var used in its own initializer.
* call.c (set_up_extended_ref_temp): Set
DECL_INITIALIZED_BY_CONSTANT_EXPRESSION_P too.

Added:
trunk/gcc/testsuite/g++.dg/cpp0x/constexpr-diag2.C
Modified:
trunk/gcc/cp/ChangeLog
trunk/gcc/cp/call.c
trunk/gcc/cp/decl2.c
trunk/gcc/cp/semantics.c
trunk/gcc/testsuite/ChangeLog


[Bug tree-optimization/47835] FAIL: gcc.dg/pr46909.c scan-tree-dump ifcombine "optimizing two comparisons to x_[0-9]+\(D\) != 4"

2011-02-21 Thread mikpe at it dot uu.se
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47835

Mikael Pettersson  changed:

   What|Removed |Added

 CC||mikpe at it dot uu.se

--- Comment #2 from Mikael Pettersson  2011-02-21 
15:14:06 UTC ---
I see the same pr46909 failure on powerpc64-linux too, with every weekly trunk
snapshot since 2010-12-18.


[Bug tree-optimization/47838] FAIL: gcc.dg/tree-ssa/foldconst-2.c scan-tree-dump-not optimized "fundamentals..0"

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47838

--- Comment #1 from John David Anglin  2011-02-21 
15:12:18 UTC ---
Created attachment 23427
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23427
Tree dump.


[Bug tree-optimization/47838] New: FAIL: gcc.dg/tree-ssa/foldconst-2.c scan-tree-dump-not optimized "fundamentals..0"

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47838

   Summary: FAIL: gcc.dg/tree-ssa/foldconst-2.c scan-tree-dump-not
optimized "fundamentals..0"
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: tree-optimization
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: dang...@gcc.gnu.org
  Host: hppa1.1-hp-hpux10.20
Target: hppa1.1-hp-hpux10.20
 Build: hppa1.1-hp-hpux10.20


Executing on host: /xxx/gnu/gcc/objdir/gcc/xgcc -B/xxx/gnu/gcc/objdir/gcc/
/xxx/
gnu/gcc/gcc/gcc/testsuite/gcc.dg/tree-ssa/foldconst-2.c   -O2
-fdump-tree-optimi
zed -S  -o foldconst-2.s(timeout = 300)
PASS: gcc.dg/tree-ssa/foldconst-2.c (test for excess errors)
FAIL: gcc.dg/tree-ssa/foldconst-2.c scan-tree-dump-not optimized
"fundamentals.0
"


[Bug c++/47207] [4.6 Regression] [C++0x] ICE: in decl_constant_var_p, at cp/decl2.c:3563 on invalid code

2011-02-21 Thread jason at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47207

Jason Merrill  changed:

   What|Removed |Added

 Status|NEW |ASSIGNED
 CC||jason at gcc dot gnu.org

--- Comment #2 from Jason Merrill  2011-02-21 
15:11:14 UTC ---
Mine.


[Bug fortran/46321] [OOP] Polymorphic deallocation

2011-02-21 Thread janus at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=46321

--- Comment #2 from janus at gcc dot gnu.org 2011-02-21 15:06:10 UTC ---
(In reply to comment #1)
> Note: There are four cases where a polymorphic deallocate is needed - though
> some might end up in the same code path:
> 
> - explicit DEALLOCATE (cf. comment 0)
> - implicit deallocate at the end of the scope
> - implicit deallocate via INTENT(OUT) (cf. PR 47637)
> - implicit deallocate when doing polymorphic reallocate on assignment (PR
> 43366)

Some more things we need to consider:
* explicit deallocation with STAT or ERRMSG
* deallocation of allocatable components (explicit/implicit)


[Bug target/47487] ICE in rs6000_output_function_epilogue, at config/rs6000/rs6000.c:21782 building 64bit libgo

2011-02-21 Thread bergner at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47487

--- Comment #3 from Peter Bergner  2011-02-21 
15:02:40 UTC ---
I don't recall anyone adding GO support for powerpc{,64}-linux, so I'm guessing
such a patch should be added when that is submitted?


[Bug c/47837] New: FAIL: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 26)

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47837

   Summary: FAIL: gcc.dg/uninit-pred-7_a.c bogus warning (test for
bogus messages, line 26)
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: c
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: dang...@gcc.gnu.org
  Host: hppa1.1-hp-hpux10.20
Target: hppa1.1-hp-hpux10.20
 Build: hppa1.1-hp-hpux10.20


Executing on host: /xxx/gnu/gcc/objdir/gcc/xgcc -B/xxx/gnu/gcc/objdir/gcc/
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c   -Wuninitialized -O2
-S  -o 
uninit-pred-7_a.s(timeout = 300)
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c: In function
'foo':/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c:26:11: warning:
'v' may 
be used uninitialized in this function [-Wuninitialized]
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c: In function 'foo_2':
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c:48:12: warning: 'v' may
be used uninitialized in this function [-Wuninitialized]
output is:
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c: In function
'foo':/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c:26:11: warning:
'v' may 
be used uninitialized in this function [-Wuninitialized]
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c: In function 'foo_2':
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/uninit-pred-7_a.c:48:12: warning: 'v' may 
be used uninitialized in this function [-Wuninitialized]

PASS: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 20)
PASS: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 23)
FAIL: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 26)
PASS: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 42)
PASS: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 45)
PASS: gcc.dg/uninit-pred-7_a.c warning (test for warnings, line 48)
PASS: gcc.dg/uninit-pred-7_a.c bogus warning (test for bogus messages, line 51)
PASS: gcc.dg/uninit-pred-7_a.c (test for excess errors)


[Bug regression/47836] New: Some Cross Compiler can't build target-libiberty or target-zlib

2011-02-21 Thread th.r.klein at web dot de
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47836

   Summary: Some Cross Compiler can't build target-libiberty or
target-zlib
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: regression
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: th.r.kl...@web.de


With upcoming 4.6 building of target-libiberty and target-zlib is enabled (at
most platforms) per default.
It should be possible to disable this behavior e.g. with switches like:
--without-target-libiberty
--without-target-zlib

Previous versions did not try to build these libraries for cross compilers.


Index: configure.ac
===
--- configure.ac(revision 170359)
+++ configure.ac(working copy)
@@ -262,6 +262,16 @@ skipdirs=
 # Noconfigdirs are removed loudly.
 noconfigdirs=""

+# Make sure we don't let target-libiberty be added if we didn't want it.
+if test x$with_target_libiberty = xno ; then
+  noconfigdirs="$noconfigdirs target-libiberty"
+fi
+
+# Make sure we don't let target-zlib be added if we didn't want it.
+if test x$with_target_zlib = xno ; then
+  noconfigdirs="$noconfigdirs target-zlib"
+fi
+
 use_gnu_ld=
 # Make sure we don't let GNU ld be added if we didn't want it.
 if test x$with_gnu_ld = xno ; then
Index: configure
===
--- configure   (revision 170359)
+++ configure   (working copy)
@@ -2801,6 +2801,16 @@ skipdirs=
 # Noconfigdirs are removed loudly.
 noconfigdirs=""

+# Make sure we don't let target-libiberty be added if we didn't want it.
+if test x$with_target_libiberty = xno ; then
+  noconfigdirs="$noconfigdirs target-libiberty"
+fi
+
+# Make sure we don't let target-zlib be added if we didn't want it.
+if test x$with_target_zlib = xno ; then
+  noconfigdirs="$noconfigdirs target-zlib"
+fi
+
 use_gnu_ld=
 # Make sure we don't let GNU ld be added if we didn't want it.
 if test x$with_gnu_ld = xno ; then


[Bug tree-optimization/47835] FAIL: gcc.dg/pr46909.c scan-tree-dump ifcombine "optimizing two comparisons to x_[0-9]+\(D\) != 4"

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47835

--- Comment #1 from John David Anglin  2011-02-21 
14:37:14 UTC ---
Created attachment 23426
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=23426
Tree dump.


[Bug fortran/47778] reading two arrays of structures from namelist fails

2011-02-21 Thread jvdelisle at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47778

--- Comment #4 from Jerry DeLisle  2011-02-21 
14:35:20 UTC ---
Status update. I have more or less isolated the problem in list-read.c.  I do
not have an exact solution yet, but I am able to get the test case to work. I
just need now to find the right place to make the tweak.


[Bug tree-optimization/42108] [4.4/4.5/4.6 Regression] 50% performance regression

2011-02-21 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=42108

Richard Guenther  changed:

   What|Removed |Added

   Last reconfirmed|2009-11-19 16:49:51 |2011-02-21 16:49:51

--- Comment #51 from Richard Guenther  2011-02-21 
14:33:16 UTC ---
Re-confirmed.  The PR42131 "fix" didn't improve the situation.


[Bug objc/47832] [4.6 Regression] ObjC errors on structures with flexible data members

2011-02-21 Thread nicola at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47832

--- Comment #4 from Nicola Pero  2011-02-21 14:33:14 
UTC ---

> for ObjC I guess it depends if in @interface there are variables (then
> variables with flexible array members in theory could be treated there like 
> ISO
> C99 treats variables), or they are treated as struct fields, in which cases
> fields with flex array members should be rejected

I see your point.  They are struct fields.

Thanks


[Bug libfortran/47567] Wrong output for small absolute values with F editing

2011-02-21 Thread jvdelisle at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47567

--- Comment #22 from Jerry DeLisle  2011-02-21 
14:32:14 UTC ---
On my system I get with:
print *, "--"
print "(F0.0)", -0.0   ! => -0.
print "(F3.0)", -0.0   ! => -0.
print "(F2.0)", -0.0   ! => **
print "(F1.0)", -0.0   ! => *
print *, "--"
print "(F0.1)", -0.0   ! => -.0
print "(F3.1)", -0.0   ! => -.0
print "(F2.1)", -0.0   ! => **
print "(F1.1)", -0.0   ! => *

This. The difference being my signature zero.
 --
-0.
-0.
**
0
 --
-.0
-.0
**
0

I confess, it does not look consistent. Next time slice, I will update it.  ;)


[Bug tree-optimization/47835] New: FAIL: gcc.dg/pr46909.c scan-tree-dump ifcombine "optimizing two comparisons to x_[0-9]+\(D\) != 4"

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47835

   Summary: FAIL: gcc.dg/pr46909.c scan-tree-dump ifcombine
"optimizing two comparisons to x_[0-9]+\(D\) != 4"
   Product: gcc
   Version: 4.6.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: tree-optimization
AssignedTo: unassig...@gcc.gnu.org
ReportedBy: dang...@gcc.gnu.org
  Host: hppa1.1-hp-hpux10.20
Target: hppa1.1-hp-hpux10.20
 Build: hppa1.1-hp-hpux10.20


Executing on host: /xxx/gnu/gcc/objdir/gcc/xgcc -B/xxx/gnu/gcc/objdir/gcc/
/xxx/gnu/gcc/gcc/gcc/testsuite/gcc.dg/pr46909.c   -O2 -fdump-tree-ifcombine -S 
-o pr46909.s(timeout = 300)
PASS: gcc.dg/pr46909.c (test for excess errors)
FAIL: gcc.dg/pr46909.c scan-tree-dump ifcombine "optimizing two comparisons to
x_[0-9]+\(D\) != 4"

See `!= 6' in tree dump.


[Bug c++/47199] [4.6 Regression] [C++0x] ICE: expected class 'type', have 'declaration' (function_decl) in same_type_ignoring_top_level_qualifiers_p, at cp/typeck.c:1407 with -fno-elide-constructors

2011-02-21 Thread jason at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47199

Jason Merrill  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 CC||jason at gcc dot gnu.org
 Resolution||FIXED

--- Comment #3 from Jason Merrill  2011-02-21 
14:26:06 UTC ---
Fixed.


[Bug libfortran/47567] Wrong output for small absolute values with F editing

2011-02-21 Thread jvdelisle at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47567

--- Comment #21 from Jerry DeLisle  2011-02-21 
14:22:51 UTC ---
OK, can you tell I am time slicing this one.  ;)


[Bug target/47825] SSE bitwise operations on floats work -g, fail -O3

2011-02-21 Thread hjl.tools at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47825

H.J. Lu  changed:

   What|Removed |Added

 CC|hjl at gcc dot gnu.org  |hjl.tools at gmail dot com,
   ||ubizjak at gmail dot com

--- Comment #6 from H.J. Lu  2011-02-21 13:53:02 
UTC ---
(In reply to comment #5)

> /* Load four SPFP values from P.  The address must be 16-byte aligned.  */
> extern __inline __m128 __attribute__((__gnu_inline__, __always_inline__,
> __artificial__))
> _mm_load_ps (float const *__P)
> {
>   return (__m128) *(__v4sf *)__P;
> }
> 
> 
> re-opening to investigate that.  HJ, are the SSE1 intrinsics not
> aliasing in the Intel API?  The above snippets are from trunk.

It is a bug and should be fixed.


[Bug debug/47106] -fcompare-debug failure (length) with -fpartial-inlining -flto -fconserve-stack

2011-02-21 Thread danglin at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47106

John David Anglin  changed:

   What|Removed |Added

 CC||danglin at gcc dot gnu.org

--- Comment #16 from John David Anglin  2011-02-21 
13:44:58 UTC ---
Executing on host: /test/gnu/gcc/objdir/gcc/testsuite/g++/../../g++
-B/test/gnu/
gcc/objdir/gcc/testsuite/g++/../../
/test/gnu/gcc/gcc/gcc/testsuite/g++.dg/debug
/pr47106.C  -nostdinc++
-I/test/gnu/gcc/objdir/hppa2.0w-hp-hpux11.11/libstdc++-v
3/include/hppa2.0w-hp-hpux11.11
-I/test/gnu/gcc/objdir/hppa2.0w-hp-hpux11.11/lib
stdc++-v3/include -I/test/gnu/gcc/gcc/libstdc++-v3/libsupc++
-I/test/gnu/gcc/gcc
/libstdc++-v3/include/backward -I/test/gnu/gcc/gcc/libstdc++-v3/testsuite/util
-
fmessage-length=0 -gstabs1 -O -fpartial-inlining -flto -fconserve-stack
-fcompar
e-debug  -S  -o pr47106.s(timeout = 300)
cc1plus: error: LTO support has not been enabled in this configuration
compiler exited with status 1
output is:
cc1plus: error: LTO support has not been enabled in this configuration

FAIL: g++.dg/debug/pr47106.C -gstabs1 (test for excess errors)
Excess errors:
cc1plus: error: LTO support has not been enabled in this configuration


[Bug bootstrap/47820] [4.6 Regression] LTO bootstrap failed with bootstrap-profiled

2011-02-21 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47820

Richard Guenther  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution||FIXED

--- Comment #4 from Richard Guenther  2011-02-21 
13:42:36 UTC ---
Fixed.


[Bug bootstrap/47820] [4.6 Regression] LTO bootstrap failed with bootstrap-profiled

2011-02-21 Thread rguenth at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47820

--- Comment #3 from Richard Guenther  2011-02-21 
13:38:54 UTC ---
Author: rguenth
Date: Mon Feb 21 13:38:48 2011
New Revision: 170359

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=170359
Log:
2011-02-21  Richard Guenther  

PR lto/47820
* lto-streamer-in.c (lto_input_ts_decl_common_tree_pointers):
Do not stream DECL_INITIAL for TRANSLATION_UNIT_DECLs.
(lto_input_ts_block_tree_pointers): Hook a BLOCK into the
TUs context.
* lto-streamer-out.c (lto_output_ts_decl_common_tree_pointers): 
Do not stream DECL_INITIAL for TRANSLATION_UNIT_DECLs.

Modified:
trunk/gcc/ChangeLog
trunk/gcc/lto-streamer-in.c
trunk/gcc/lto-streamer-out.c


[Bug libfortran/47567] Wrong output for small absolute values with F editing

2011-02-21 Thread thenlich at users dot sourceforge.net
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47567

Thomas Henlich  changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |

--- Comment #20 from Thomas Henlich  
2011-02-21 13:22:59 UTC ---
print "(F3.0)", -0.0   ! => -0.
print "(F2.0)", -0.0   ! => **
print "(F1.0)", -0.0   ! => 0

print "(F3.1)", -0.0   ! => -.0
print "(F2.1)", -0.0   ! => **
print "(F1.1)", -0.0   ! => 0

I think it's still wrong: It is not possible for any value to fit into a field
of width w, but not into w+1.

Either

1) For the special case of a zero, we consider the minus sign and the decimal
symbol optional (which I think does not conform to the standard), then the
result should be:

print "(F3.0)", -0.0   ! => -0.
print "(F2.0)", -0.0   ! => -0 (or 0. or 0)
print "(F1.0)", -0.0   ! => 0

print "(F3.1)", -0.0   ! => -.0
print "(F2.1)", -0.0   ! => -0 (or .0 or 0)
print "(F1.1)", -0.0   ! => 0

or

2) We never consider the minus sign nor the decimal symbol optional (which I
think is required by the standard), then the result should be:

print "(F0.0)", -0.0   ! => -0.
print "(F3.0)", -0.0   ! => -0.
print "(F2.0)", -0.0   ! => **
print "(F1.0)", -0.0   ! => *

print "(F0.1)", -0.0   ! => -.0
print "(F3.1)", -0.0   ! => -.0
print "(F2.1)", -0.0   ! => **
print "(F1.1)", -0.0   ! => *


[Bug other/47824] Option to enable all warning (-Wall-real?)

2011-02-21 Thread olafvdspek at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47824

--- Comment #11 from Olaf van der Spek  2011-02-21 
13:11:04 UTC ---
> Dup.

No kidding?


[Bug objc/47832] [4.6 Regression] ObjC errors on structures with flexible data members

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47832

Jakub Jelinek  changed:

   What|Removed |Added

   Priority|P2  |P4


[Bug c/47796] The code to write to a bit_field data strucuture will be removed unexpectedly with gcc 4.5.1 -O2 option

2011-02-21 Thread qihua.dai at intel dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47796

--- Comment #7 from qihua.dai at intel dot com 2011-02-21 13:02:41 UTC ---
Hi,

I used -Wall -O2. But no warning for this situation.

gcc will print strict-aliasing related warning.

  struct tmp1_s tmp;

  tmp.a = 0xc; // this code line is removed unexpected after -O2 optimization

  tmp.d = 0x1; // this code line is removed unexpected after -O2 optimization

  data = *((unsigned int *)pTmp);



But, below code can fix above this warning. But this code might be removed by
gcc �CO2 in the situation of this bug.

  struct tmp1_s tmp;

  unsigned int *pData;

  tmp.a = 0xc; // this code line is removed unexpected after -O2 optimization

  tmp.d = 0x1; // this code line is removed unexpected after -O2 optimization

  pData = (unsigned int *)pTmp;

  data = *pData;


In addition, if cannot access bit field structure using an unsigned int, how to
share different bit field structure? For example,
void func(unsigned int data)
data can be bit field structure tmp1_s, or tmp2_s according to bit[31] (0 is
tmp1_s, 1 is tmp2_s)



struct tmp1_s {

unsigned int a : 12;

unsigned int b : 12;

unsigned int c : 7;

unsigned int d : 1;

}



struct tmp2_s {

unsigned int a : 1;

unsigned int b : 12;

unsigned int c : 12;

unsigned int d : 6;

unsigned int e : 1;

}





- Qihua

-Original Message-
From: jakub at gcc dot gnu.org [mailto:gcc-bugzi...@gcc.gnu.org]
Sent: 2011年2月21日 16:29
To: Dai, Qihua
Subject: [Bug c/47796] The code to write to a bit_field data strucuture will be
removed unexpectedly with gcc 4.5.1 -O2 option



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



Jakub Jelinek  changed:



   What|Removed |Added



 Status|UNCONFIRMED |RESOLVED

 CC||jakub at gcc dot gnu.org

 Resolution||INVALID



--- Comment #6 from Jakub Jelinek  2011-02-21
08:29:03 UTC ---

Undefined behavior means anything can happen, so wondering why undefined

behavior doesn't always behave the same doesn't make any sense.  And, both gcc

4.4.5 and 4.5.2 do warn about this with -Wstrict-aliasing=1 -O2:

pr47796.c:25: warning: dereferencing type-punned pointer might break

strict-aliasing rules

pr47796.c:31: warning: dereferencing type-punned pointer might break

strict-aliasing rules

Please stop reopening this.



--

Configure bugmail: http://gcc.gnu.org/bugzilla/userprefs.cgi?tab=email

--- You are receiving this mail because: ---

You reported the bug.


[Bug fortran/40850] double free in nested types with allocatable components

2011-02-21 Thread mikael at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40850

--- Comment #13 from Mikael Morin  2011-02-21 
13:01:23 UTC ---
Comment 5 is not affected by the double free as the allocatable components are
never allocated during the program, only the containing entity is.


[Bug fortran/40850] double free in nested types with allocatable components

2011-02-21 Thread mikael at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40850

Mikael Morin  changed:

   What|Removed |Added

 CC||mikael at gcc dot gnu.org

--- Comment #12 from Mikael Morin  2011-02-21 
12:57:31 UTC ---
(In reply to comment #11)
> I don't know whether it fixes comment 0 or comment 4
>
Sorry, I forgot to precise. 
It fixes neither. 
More precisely for comments 0 and 4, it does fix a read of freed memory:

==82785== Invalid read of size 8
==82785==at 0x400F21: __mod_all_MOD_add (in
/usr/home/mik/gfortran/pr40850/comment_0)
==82785==by 0x4023D9: MAIN__ (in /usr/home/mik/gfortran/pr40850/comment_0)
==82785==by 0x402703: main (in /usr/home/mik/gfortran/pr40850/comment_0)
==82785==  Address 0x14be678 is 8 bytes inside a block of size 112 free'd

but doesn't fix a double free affecting comments 0, 4 and 8:

==82785== Invalid free() / delete / delete[]
==82785==at 0x25A37E: free (in
/usr/local/lib/valgrind/vgpreload_memcheck-amd64-freebsd.so)
==82785==by 0x402609: MAIN__ (in /usr/home/mik/gfortran/pr40850/comment_0)
==82785==by 0x402703: main (in /usr/home/mik/gfortran/pr40850/comment_0)
==82785==  Address 0x14be3d0 is 0 bytes inside a block of size 8 free'd



Comment 8 is not affected by the invalid read as the containing entity is not
allocatable, hence not explicitly freed at the end. Thus, components release
can't happen before containing entity's release. 

For the remaining double free, the temporary for the array constructor is
filled using simple copies, and thus has components pointing to the original
array. Those components are freed by the temporary array cleanup, and again
during the final release of all allocatables. 
One could fix it by not freeing the temporary's components (no deep/nested
free), but I have the feeling (haven't completely made my mind about it) that
the proper fix, in the general case, is to create nested temporaries and do
deep copies. And yes, that would be horribly expensive :-(.


[Bug c++/31573] -Wall-all to enable all warnings

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=31573

--- Comment #5 from Jakub Jelinek  2011-02-21 
12:55:51 UTC ---
*** Bug 47824 has been marked as a duplicate of this bug. ***


[Bug other/47824] Option to enable all warning (-Wall-real?)

2011-02-21 Thread jakub at gcc dot gnu.org
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47824

Jakub Jelinek  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 CC||jakub at gcc dot gnu.org
 Resolution||DUPLICATE

--- Comment #10 from Jakub Jelinek  2011-02-21 
12:55:51 UTC ---
Dup.

*** This bug has been marked as a duplicate of bug 31573 ***


[Bug target/38306] [4.4/4.5/4.6 Regression] 15% slowdown w.r.t. 4.3 of computational kernel on some architectures

2011-02-21 Thread Joost.VandeVondele at pci dot uzh.ch
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=38306

--- Comment #23 from Joost VandeVondele  
2011-02-21 12:53:30 UTC ---
(In reply to comment #22)
> What is the performance with 4.3 -O2?  

4.3:
> gfortran -O2 -march=native -funroll-loops -ffast-math test.f90 ; ./a.out
Time for evaluation [s]:4.373

4.6:
>  gfortran -O2 -march=native -funroll-loops -ffast-math test.f90 ; ./a.out
Time for evaluation [s]:4.347

so, same performance. 

Given that vectorization only happens at -O3, it is an important optimization
level for numerical codes. Nevertheless, I would propose to remove the
regression tag, and instead refocus the bug on the what current trunk does at
-O3 vs -O2 -ftree-vectorize as noted in comment #21

> gfortran -O2 -march=native -funroll-loops  -ffast-math  -ftree-vectorize 
> test.f90 ; ./a.out
Time for evaluation [s]:2.694

> gfortran -O3 -march=native -funroll-loops  -ffast-math  -ftree-vectorize 
> test.f90 ; ./a.out
Time for evaluation [s]:4.536


[Bug other/47824] Option to enable all warning (-Wall-real?)

2011-02-21 Thread olafvdspek at gmail dot com
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47824

--- Comment #9 from Olaf van der Spek  2011-02-21 
12:47:24 UTC ---
> > So "The list in the manual already." is false.
> 
> The information is in the manual, even if not as an explicit list.

That's true, but not what was said.

> I expect adding an explicit list would soon get out of date as it just
> increases the burden on contributors when adding new options.

Adding options that can't be easily enabled / found doesn't seem very useful.

> The fact you don't agree doesn't change the fact this is a duplicate of that
> report, marking it as such helps keep the discussion in one place. Please 
> don't
> reopen this report.  

How do I reopen the other report?

> If you want a new one for the documentation issue please
> open a new PR.

Why? Seems easier to use this one for it.


  1   2   >