[Bug fortran/64508] New: [F03] interface check missing for procedure pointer component as actual argument

2015-01-06 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64508

Bug ID: 64508
   Summary: [F03] interface check missing for procedure pointer
component as actual argument
   Product: gcc
   Version: 5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: janus at gcc dot gnu.org

Inspired by the discussion at:

https://groups.google.com/forum/?fromgroups=#!topic/comp.lang.fortran/svfanCGU2vU

Example code:


module m

   TYPE :: parent
   END TYPE parent

   TYPE, EXTENDS(parent) :: extension
 INTEGER :: extension_component = 0
  procedure(extension_proc), pointer :: ppc
   END TYPE extension

contains

   SUBROUTINE parent_proc(arg)
 CLASS(parent), INTENT(IN) :: arg
 PRINT *, 'I am parent_proc'
   END SUBROUTINE parent_proc

   SUBROUTINE extension_proc(arg)
 CLASS(extension), INTENT(IN) :: arg
 PRINT *, 'I am extension_proc'
 PRINT *, arg%extension_component
   END SUBROUTINE extension_proc

   SUBROUTINE some_proc(proc)
 PROCEDURE(parent_proc) :: proc
 TYPE(Parent) :: a
 CALL proc(a)
   END SUBROUTINE some_proc

end module

program test
  use m
   CLASS(extension), ALLOCATABLE :: x
   procedure(parent_proc), pointer :: ppp
   procedure(extension_proc), pointer :: ppe

   CALL some_proc(parent_proc) ! ok
   CALL some_proc(extension_proc)  ! interface mismatch

   ppp = extension_proc   ! interface mismatch
   call some_proc(ppp)

   ppe = extension_proc
   call some_proc(ppe) ! interface mismatch

   allocate(x, source= Extension(666,extension_proc))
   CALL some_proc(x%ppc)   !  XXX: mismatch not detected
end



As the above example shows, interface checking is done for ordinary procedures
and procedure pointers as actual arguments to dummy procedures. However, it is
missing for procedure-pointer components.


[Bug c/64509] New: _Generic throws error in unselected generic association

2015-01-06 Thread maurits.de.jong at ericsson dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64509

Bug ID: 64509
   Summary: _Generic throws error in unselected generic
association
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: c
  Assignee: unassigned at gcc dot gnu.org
  Reporter: maurits.de.jong at ericsson dot com

Created attachment 34387
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34387action=edit
The offending source separately

I would have expected this to work (basically insert a conversion function
call if the type doesn't match):


-
typedef struct {
int x;
} mystruct;

extern int __f(int);
extern int __stoi(mystruct);

void call(void)
{
mystruct S = {1};

double z = _Generic((S), mystruct: __f(__stoi(S)), default: __f(S));
}
-

but the typechecker is not happy about __f(S), which is in an association 
not relevant for the controlling expression:

The standard says:

  None of the expressions from any other generic association of the generic
  selection is evaluated.

Of course, evaluation is different from typechecking, but since the construct
is intended to conditionalise based on types, wouldn't it make sense to only
typecheck the selected association?




bash$ ./bin/gcc -std=c11 -v generic.c
Using built-in specs.
COLLECT_GCC=./bin/gcc
COLLECT_LTO_WRAPPER=/space/radmmj/gcc492/gcc-4.9.2/libexec/gcc/x86_64-unknown-linux-gnu/4.9.2/lto-wrapper
Target: x86_64-unknown-linux-gnu
Configured with: ../configure --prefix=/space/radmmj/gcc492/gcc-4.9.2 :
(reconfigured) ../configure --prefix=/space/radmmj/gcc492/gcc-4.9.2
--enable-languages=c
Thread model: posix
gcc version 4.9.2 (GCC) 
COLLECT_GCC_OPTIONS='-std=c11' '-v' '-mtune=generic' '-march=x86-64'
 /space/radmmj/gcc492/gcc-4.9.2/libexec/gcc/x86_64-unknown-linux-gnu/4.9.2/cc1
-quiet -v -imultiarch x86_64-linux-gnu generic.c -quiet -dumpbase generic.c
-mtune=generic -march=x86-64 -auxbase generic -std=c11 -version -o
/tmp/ccEshK6s.s
GNU C (GCC) version 4.9.2 (x86_64-unknown-linux-gnu)
compiled by GNU C version 4.9.2, GMP version 4.3.2, MPFR version 2.4.2,
MPC version 0.8.1
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
ignoring nonexistent directory /usr/local/include/x86_64-linux-gnu
ignoring nonexistent directory
/space/radmmj/gcc492/gcc-4.9.2/lib/gcc/x86_64-unknown-linux-gnu/4.9.2/../../../../x86_64-unknown-linux-gnu/include
#include ... search starts here:
#include ... search starts here:
 /space/radmmj/gcc492/gcc-4.9.2/lib/gcc/x86_64-unknown-linux-gnu/4.9.2/include
 /usr/local/include
 /space/radmmj/gcc492/gcc-4.9.2/include

/space/radmmj/gcc492/gcc-4.9.2/lib/gcc/x86_64-unknown-linux-gnu/4.9.2/include-fixed
 /usr/include/x86_64-linux-gnu
 /usr/include
End of search list.
GNU C (GCC) version 4.9.2 (x86_64-unknown-linux-gnu)
compiled by GNU C version 4.9.2, GMP version 4.3.2, MPFR version 2.4.2,
MPC version 0.8.1
GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
Compiler executable checksum: 1bfa4fb39c457521c17e15d89fa44581
generic.c: In function ‘call’:
generic.c:12:69: error: incompatible type for argument 1 of ‘__f’
 double z = _Generic((S), mystruct: __f(__stoi(S)), default: __f(S));
 ^
generic.c:5:12: note: expected ‘int’ but argument is of type ‘mystruct’
 extern int __f(int);
^

[Bug target/64507] New: SH inlined builtin strncmp doesn't return 0 for 0 length

2015-01-06 Thread chrbr at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64507

Bug ID: 64507
   Summary: SH inlined builtin strncmp doesn't return 0 for 0
length
   Product: gcc
   Version: unknown
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: target
  Assignee: unassigned at gcc dot gnu.org
  Reporter: chrbr at gcc dot gnu.org

Created attachment 34386
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34386action=edit
test case

Thought the check was emitted from the builtin generic prologue like for the
constant lengths. which was not :-(


[Bug c++/64497] std::scalbln does not round correctly for long doubles

2015-01-06 Thread jakub at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64497

Jakub Jelinek jakub at gcc dot gnu.org changed:

   What|Removed |Added

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

--- Comment #6 from Jakub Jelinek jakub at gcc dot gnu.org ---
Closing as this is definitely not a GCC issue.
Please file it against glibc instead.  Note, on x86_64, scalbnl is implemented
in assembly, while scalblnl is not.


[Bug rtl-optimization/64287] [5 Regression] Disable -fuse-caller-save when -pg is active

2015-01-06 Thread vries at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64287

vries at gcc dot gnu.org changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

--- Comment #4 from vries at gcc dot gnu.org ---
Patch and test-case committed. Marking as resolved, fixed.


[Bug target/63949] Aarch64 instruction combiner does not optimize subsi_sxth function as expected (gcc.target/aarch64/extend.c fails)

2015-01-06 Thread vekumar at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63949

--- Comment #8 from vekumar at gcc dot gnu.org ---
This is complete patch for the first approach that I took (comment 6). This
patch fixes issues I faced while testing. But I have added extra patterns to
cater the sign extended operands with left shifts. This might impact other
targets as well :( 

Now I am also exploring other possibilities instead of writing extra patterns. 


diff --git a/gcc/combine.c b/gcc/combine.c
index ee7b3f9..80b345d 100644
--- a/gcc/combine.c
+++ b/gcc/combine.c
@@ -7896,7 +7896,7 @@ make_compound_operation (rtx x, enum rtx_code in_code)
   INTVAL (rhs)  HOST_BITS_PER_WIDE_INT
   INTVAL (rhs)  mode_width
   (new_rtx = extract_left_shift (lhs, INTVAL (rhs))) != 0)
-   new_rtx = make_extraction (mode, make_compound_operation (new_rtx,
next_
+   new_rtx = make_extraction (mode, new_rtx,
   0, NULL_RTX, mode_width - INTVAL (rhs),
   code == LSHIFTRT, 0, in_code == COMPARE);

diff --git a/gcc/config/aarch64/aarch64.md b/gcc/config/aarch64/aarch64.md
index 97d7009..f0b9240 100644
--- a/gcc/config/aarch64/aarch64.md
+++ b/gcc/config/aarch64/aarch64.md
@@ -1570,26 +1570,62 @@
   [(set_attr type alus_ext)]
 )

-(define_insn *adds_optabmode_multp2
+(define_insn *adds_optabmode_extend_ashift
   [(set (reg:CC_NZ CC_REGNUM)
(compare:CC_NZ
-(plus:GPI (ANY_EXTRACT:GPI
-   (mult:GPI (match_operand:GPI 1 register_operand r)
- (match_operand 2 aarch64_pwr_imm3 Up3))
-   (match_operand 3 const_int_operand n)
-   (const_int 0))
-  (match_operand:GPI 4 register_operand r))
+(plus:GPI (match_operand:GPI 1 register_operand r)
+  (ashift:GPI (ANY_EXTEND:GPI
+(match_operand:ALLX 2 register_operand r))
+   (match_operand 3 aarch64_imm3 Ui3)))
(const_int 0)))
(set (match_operand:GPI 0 register_operand =r)
-   (plus:GPI (ANY_EXTRACT:GPI (mult:GPI (match_dup 1) (match_dup 2))
-  (match_dup 3)
-  (const_int 0))
- (match_dup 4)))]
+   (plus:GPI  (match_dup 1) 
+   (ashift:GPI (ANY_EXTEND:GPI (match_dup 2))
+   (match_dup 3]
+  
+  adds\\t%w0, %w1, %w2, suxt %3
+  [(set_attr type alus_ext)]
+)
+
+(define_insn *subs_optabmode_extend_ashift
+  [(set (reg:CC_NZ CC_REGNUM)
+(compare:CC_NZ
+ (minus:GPI (match_operand:GPI 1 register_operand r)
+(ashift:GPI (ANY_EXTEND:GPI
+  (match_operand:ALLX 2 register_operand
r)
+ (match_operand 3 aarch64_imm3 Ui3)))
+(const_int 0)))
+   (set (match_operand:GPI 0 register_operand =r)
+(minus:GPI (match_dup 1)
+   (ashift:GPI (ANY_EXTEND:GPI (match_dup 2))
+(match_dup 3]
+  
+  subs\\t%w0, %w1, %w2, suxt %3
+  [(set_attr type alus_ext)]
+)
+
+
+(define_insn *adds_optabmode_multp2
+  [(set (reg:CC_NZ CC_REGNUM)
+(compare:CC_NZ
+ (plus:GPI (ANY_EXTRACT:GPI
+(mult:GPI (match_operand:GPI 1 register_operand r)
+  (match_operand 2 aarch64_pwr_imm3 Up3))
+(match_operand 3 const_int_operand n)
+(const_int 0))
+   (match_operand:GPI 4 register_operand r))
+(const_int 0)))
+   (set (match_operand:GPI 0 register_operand =r)
+(plus:GPI (ANY_EXTRACT:GPI (mult:GPI (match_dup 1) (match_dup 2))
+   (match_dup 3)
+   (const_int 0))
+  (match_dup 4)))]
   aarch64_is_extend_from_extract (MODEmode, operands[2], operands[3])
   adds\\t%w0, %w4, %w1, suxt%e3 %p2
   [(set_attr type alus_ext)]
 )

+
 (define_insn *subs_optabmode_multp2
   [(set (reg:CC_NZ CC_REGNUM)
(compare:CC_NZ


[Bug target/64479] [4.8 Regression][SH] wrong optimization delayed-branch

2015-01-06 Thread olegendo at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64479

Oleg Endo olegendo at gcc dot gnu.org changed:

   What|Removed |Added

 Target|sh3 |sh*-*-*
 Status|UNCONFIRMED |NEW
   Last reconfirmed||2015-01-06
 CC||kkojima at gcc dot gnu.org,
   ||olegendo at gcc dot gnu.org
Summary|wrong optimization  |[4.8 Regression][SH] wrong
   |delayed-branch  for SH  |optimization delayed-branch
 Ever confirmed|0   |1

--- Comment #1 from Oleg Endo olegendo at gcc dot gnu.org ---
Thanks for pinpointing and reporting this.

trunk (GCC 5): OK
4.9 branch: OK
4.8 branch: NG

This is a problem of the flaky cbranch optimization in 4.8 in the *cbranch_t
splitter code. 

For some reason, modified_between_p seems to ignore the fact that the T_REG is
clobbered in call insns.  Thus it thinks that it's OK to extend the T_REG
lifetime across a call insn.


[Bug web/64469] Broken link on main page

2015-01-06 Thread redi at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64469

Jonathan Wakely redi at gcc dot gnu.org changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #3 from Jonathan Wakely redi at gcc dot gnu.org ---
Jakub corrected the link.


[Bug libstdc++/64504] Invalid free() with _GLIBCXX_DEBUG and -fwhole-program

2015-01-06 Thread redi at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64504

--- Comment #1 from Jonathan Wakely redi at gcc dot gnu.org ---
(In reply to Andrey Vihrov from comment #0)
 -fwhole-program is that it can be used with one source file that includes
 standard library headers and links with the standard library. If this is
 wrong, then I'm sorry for filing a bogus bug report.

I don't know if it's supposed to work (I would expect not), but using
-fwhole-program with _GLIBCXX_DEBUG seems silly to me. The Debug Mode macro can
slow things down by an order of magnitude, so the advantages of -fwhole-program
will be minimal anyway.

Is there a reason you can't use -flto instead?


[Bug ipa/64503] [5 Regression] gcc.dg/ipa/iinline-4.c:210:1: internal compiler error: Floating point exception

2015-01-06 Thread marxin at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64503

Martin Liška marxin at gcc dot gnu.org changed:

   What|Removed |Added

 CC||marxin at gcc dot gnu.org

--- Comment #3 from Martin Liška marxin at gcc dot gnu.org ---
Hello.

I've been testing fix where I replaced exp2 with scalbln, as Jakub suggested.
On the other hand, -inf looks a bit suspicious and is created here:

ipa-inline.c:946, where

if (growth = 0) {
  badness = (sreal) (-SREAL_MIN_SIG + growth)  (SREAL_MAX_EXP / 256);

as one can see, it's (-1073741824+growth)  (536870911/256) which is
practically always -inf?

I am curious if it's desired calculation Honza?

Thanks,
Martin

[Bug rtl-optimization/63259] Detecting byteswap sequence

2015-01-06 Thread thopre01 at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63259

--- Comment #21 from thopre01 at gcc dot gnu.org ---
Author: thopre01
Date: Tue Jan  6 11:51:16 2015
New Revision: 219256

URL: https://gcc.gnu.org/viewcvs?rev=219256root=gccview=rev
Log:
2015-01-06  Thomas Preud'homme  thomas.preudho...@arm.com

gcc/
PR tree-optimization/63259
* tree-ssa-math-opts.c (pass_optimize_bswap::execute): Stop checking
if optab exists for 16bit byteswap.

Modified:
trunk/gcc/ChangeLog
trunk/gcc/tree-ssa-math-opts.c


[Bug target/64507] SH inlined builtin strncmp doesn't return 0 for 0 length

2015-01-06 Thread chrbr at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64507

--- Comment #1 from chrbr at gcc dot gnu.org ---
Author: chrbr
Date: Tue Jan  6 11:59:09 2015
New Revision: 219257

URL: https://gcc.gnu.org/viewcvs?rev=219257root=gccview=rev
Log:
PR target/64507
* config/sh/sh-mem.cc (sh_expand_cmpnstr): Check 0 length.


Added:
trunk/gcc/testsuite/gcc.target/sh/pr64507.c
Modified:
trunk/gcc/ChangeLog
trunk/gcc/config/sh/sh-mem.cc
trunk/gcc/testsuite/ChangeLog


[Bug target/64507] SH inlined builtin strncmp doesn't return 0 for 0 length

2015-01-06 Thread chrbr at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64507

--- Comment #2 from chrbr at gcc dot gnu.org ---
Author: chrbr
Date: Tue Jan  6 12:22:51 2015
New Revision: 219258

URL: https://gcc.gnu.org/viewcvs?rev=219258root=gccview=rev
Log:
PR target/64507
* config/sh/sh-mem.cc (sh_expand_cmpnstr): Check 0 length.


Added:
branches/gcc-4_9-branch/gcc/testsuite/gcc.target/sh/pr64507.c
Modified:
branches/gcc-4_9-branch/gcc/ChangeLog
branches/gcc-4_9-branch/gcc/config/sh/sh-mem.cc
branches/gcc-4_9-branch/gcc/testsuite/ChangeLog


[Bug fortran/64508] [F03] interface check missing for procedure pointer component as actual argument

2015-01-06 Thread janus at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64508

janus at gcc dot gnu.org changed:

   What|Removed |Added

 Status|UNCONFIRMED |ASSIGNED
   Last reconfirmed||2015-01-06
   Assignee|unassigned at gcc dot gnu.org  |janus at gcc dot gnu.org
 Ever confirmed|0   |1

--- Comment #1 from janus at gcc dot gnu.org ---
Draft patch (regtest cleanly):


Index: gcc/fortran/interface.c
===
--- gcc/fortran/interface.c(Revision 219257)
+++ gcc/fortran/interface.c(Arbeitskopie)
@@ -1922,6 +1922,8 @@ compare_parameter (gfc_symbol *formal, gfc_expr *a
 {
   gfc_ref *ref;
   bool rank_check, is_pointer;
+  char err[200];
+  gfc_component *ppc;

   /* If the formal arg has type BT_VOID, it's to one of the iso_c_binding
  procs c_f_pointer or c_f_procpointer, and we need to accept most
@@ -1942,7 +1944,6 @@ compare_parameter (gfc_symbol *formal, gfc_expr *a

   if (actual-ts.type == BT_PROCEDURE)
 {
-  char err[200];
   gfc_symbol *act_sym = actual-symtree-n.sym;

   if (formal-attr.flavor != FL_PROCEDURE)
@@ -1976,6 +1977,19 @@ compare_parameter (gfc_symbol *formal, gfc_expr *a
   return 1;
 }

+  ppc = gfc_get_proc_ptr_comp (actual);
+  if (ppc)
+{
+  if (!gfc_compare_interfaces (formal, ppc-ts.interface, ppc-name, 0, 1,
+   err, sizeof(err), NULL, NULL))
+{
+  if (where)
+gfc_error (Interface mismatch in dummy procedure %qs at %L: %s,
+   formal-name, actual-where, err);
+  return 0;
+}
+}
+
   /* F2008, C1241.  */
   if (formal-attr.pointer  formal-attr.contiguous
!gfc_is_simply_contiguous (actual, true))


[Bug c++/56126] -fno-exceptions should activate -fcheck-new or issue diagnostic for all new operators without throw()

2015-01-06 Thread bruck.michael at googlemail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56126

--- Comment #9 from Michael Bruck bruck.michael at googlemail dot com ---
 Jonathan: Using -fno-exceptions says I do not want ISO C++ so quoting the 
 standard isn't very relevant.
 Olaf: No, as you could (should?) abort/terminate instead of returning NULL.

I quoted it to illustrate that returning NULL is the intuitive option here,
while abort() is a completely new approach. Returning NULL is what I would
expect to be the case when -fno-exceptions is active and it is what happens in
the libc++ implementation AFAIK.

 Why would you want an operator new that can't throw but is declared to 
 potentially throw?

Because -fno-exceptions suggests to the user that they can produce safe code
without using any exception-specific C++ syntax. 

https://gcc.gnu.org/onlinedocs/libstdc++/manual/using_exceptions.html
The last language feature needing to be transformed by -fno-exceptions is
treatment of exception specifications on member functions. Fortunately, the
compiler deals with this by ignoring exception specifications and so no
alternate source markup is needed.

If the authors of the libstdc++ docs get this wrong, how is the average
compiler user expected to know this?

Likewise GCC's documentation also pretends this case doesn't exist:

https://gcc.gnu.org/onlinedocs/gcc-4.9.0/gcc/C_002b_002b-Dialect-Options.html
-fcheck-new
Check that the pointer returned by operator new is non-null before attempting
to modify the storage allocated. This check is normally unnecessary because the
C++ standard specifies that operator new only returns 0 if it is declared
‘throw()’, in which case the compiler always checks the return value even
without this option. In all other cases, when operator new has a non-empty
exception specification, memory exhaustion is signalled by throwing
std::bad_alloc. See also ‘new (nothrow)’. 

 The exception specification is defined by the language to inform the compiler 
 whether to check the result or not, so use that.
 If declaring it like that really isn't possible, then you should use 
 -fcheck-new, but it seems OK to not enable that automatically and rely on 
 correct exception specifications.

As you pointed out we are outside the standard with -fno-exceptions. There is
certainly no rule that prevents the compiler from issuing a warning when it
generates code that is highly unlikely to be safe.

[Bug go/61265] gccgo: ICE in verify_gimple_in_seq [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61265

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #4 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug libstdc++/64504] Invalid free() with _GLIBCXX_DEBUG and -fwhole-program

2015-01-06 Thread andrey.vihrov at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64504

--- Comment #2 from Andrey Vihrov andrey.vihrov at gmail dot com ---
Thanks for a fast reply!

My use case for these two (amongst several others) options together is
competitive programming, in which a contestant is required a write a
one-source-file solution, test it locally and submit it to a grading server.
Debug Mode helps detect mistakes, and -fwhole-program helps find variables or
functions that I defined and intended to use, but forgot to. For example, for
this source:

int unused;

int main()
{

}

g++ -Wall -fwhole-program x.cpp gives

x.cpp:1:5: warning: 'unused' defined but not used [-Wunused-variable]

, and there is no warning without -fwhole-program. Of course, I can get the
same effect by making everything static, but this depends on me remembering
to do it, so this option is better in this regard. -flto doesn't have the same
effect.

If -fwhole-program isn't supported in this case, then it's fair enough. But
then it would be great if the documentation on -fwhole-program was updated to
clarify when the option can be used and when not.


[Bug go/61253] gccgo: spurious error: expected '-' or '=' [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61253

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug target/64507] SH inlined builtin strncmp doesn't return 0 for 0 length

2015-01-06 Thread chrbr at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64507

chrbr at gcc dot gnu.org changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

--- Comment #3 from chrbr at gcc dot gnu.org ---
fixed in 4.9 qnd trunk


[Bug go/61273] gccgo: ICE in Unsafe_type_conversion_expression::do_get_backend [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61273

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 CC||cmang at google dot com
 Resolution|--- |FIXED

--- Comment #2 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61258] gccgo: assertion failure go-map-delete.c:37 [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61258

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61264] gccgo: ICE in __normal_iterator [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61264

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #3 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61255] gccgo: spurious error: argument 2 has incompatible type [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61255

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61254] gccgo: spurious error: slice end must be integer [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61254

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61248] gccgo: spurious error: too many arguments [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61248

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61244] gccgo: ICE in write_specific_type_functions [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61244

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #5 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/61246] gccgo: ICE in do_determine_types [GoSmith]

2015-01-06 Thread cmang at google dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=61246

Chris Manghane cmang at google dot com changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #4 from Chris Manghane cmang at google dot com ---
Fixed and test added to Go testsuite.


[Bug go/64510] New: FAIL: go.test/test/nilptr2.go execution on non-split-stack targets

2015-01-06 Thread ubizjak at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64510

Bug ID: 64510
   Summary: FAIL: go.test/test/nilptr2.go execution on
non-split-stack targets
   Product: gcc
   Version: 5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: go
  Assignee: ian at airs dot com
  Reporter: ubizjak at gmail dot com
CC: cmang at google dot com

The testcase go.test/test/nilptr2.go fails execution on non-split-stack
targets:

Program received signal SIGSEGV, Segmentation fault.
0x00402965 in main.$nested32 () at
/home/uros/gcc-svn/trunk/gcc/testsuite/go.test/test/nilptr2.go:76
76  {*bigstructp, func() { use(*bigstructp) }},

The test wants to pass ~128MB structure on the stack, resulting in
(x86_64-linux-gnu, CentOS 5.11):

(gdb) disass
Dump of assembler code for function main.$nested32:
   0x00402910 +0: sub$0x858,%rsp
   0x00402917 +7: mov0x204fa2(%rip),%rsi# 0x6078c0
main.bigstructp
   0x0040291e +14:test   %rsi,%rsi
   0x00402921 +17:je 0x402960 main.$nested32+80
   0x00402923 +19:lea0x10(%rsp),%rdi
   0x00402928 +24:mov$0x838,%edx
   0x0040292d +29:callq  0x401bc8 memcpy@plt
   0x00402932 +34:mov$0x838,%esi
   0x00402937 +39:mov$0x404680,%edi
   0x0040293c +44:callq  0x401b28 __go_new@plt
   0x00402941 +49:lea0x10(%rsp),%rsi
   0x00402946 +54:mov$0x838,%edx
   0x0040294b +59:mov%rax,%rdi
   0x0040294e +62:callq  0x401bc8 memcpy@plt
   0x00402953 +67:add$0x858,%rsp
   0x0040295a +74:retq   
   0x0040295b +75:nopl   0x0(%rax,%rax,1)
   0x00402960 +80:mov$0x6,%edi
= 0x00402965 +85:mov%rsi,0x8(%rsp)

Please see the stack adjustment at the top:

sub$0x858,%rsp

The testcase also fails for -m32, fails on alpha [1] (with the same failure),
sparc [2], powerpc [3], powerpc64le [4] and probably other non-split-stack
targets.

[1] https://gcc.gnu.org/ml/gcc-testresults/2015-01/msg00400.html
[2] https://gcc.gnu.org/ml/gcc-testresults/2015-01/msg00354.html
[3] https://gcc.gnu.org/ml/gcc-testresults/2015-01/msg00477.html
[4] https://gcc.gnu.org/ml/gcc-testresults/2015-01/msg00480.html


[Bug c/64509] _Generic throws error in unselected generic association

2015-01-06 Thread mpolacek at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64509

Marek Polacek mpolacek at gcc dot gnu.org changed:

   What|Removed |Added

 CC||mpolacek at gcc dot gnu.org

--- Comment #1 from Marek Polacek mpolacek at gcc dot gnu.org ---
I think it's fine to reject that testcase.  The type checking is performed when
parsing while building the association expression...


[Bug c/64440] -Wdiv-by-zero false negative on const variables

2015-01-06 Thread mpolacek at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64440

Marek Polacek mpolacek at gcc dot gnu.org changed:

   What|Removed |Added

 CC||mpolacek at gcc dot gnu.org

--- Comment #4 from Marek Polacek mpolacek at gcc dot gnu.org ---
(In reply to Manuel López-Ibáñez from comment #3)
 (In reply to Chengnian Sun from comment #2)
  Thanks for your reply. It seems GCC sometimes does consider const int for
  other types of warnings (but not for -Wdiv-by-zero). See the following, with
  -O3, GCC warns that the left shift count is negative.  
  
 
 I wonder how this happens? The warning is still given by the FE!

By using decl_constant_value_for_optimization.

[Bug tree-optimization/64494] [5 Regression] ICE at -Os and above on x86_64-linux-gnu in duplicate_ssa_name_range_info, at tree-ssanames.c:499

2015-01-06 Thread jakub at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64494

Jakub Jelinek jakub at gcc dot gnu.org changed:

   What|Removed |Added

 Status|ASSIGNED|RESOLVED
 Resolution|--- |FIXED

--- Comment #4 from Jakub Jelinek jakub at gcc dot gnu.org ---
Fixed.


[Bug target/64513] New: [4.8/4.9/5 Regression] ICE: in maybe_record_trace_start, at dwarf2cfi.c:2231 with -mstack-arg-probe

2015-01-06 Thread zsojka at seznam dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64513

Bug ID: 64513
   Summary: [4.8/4.9/5 Regression] ICE: in
maybe_record_trace_start, at dwarf2cfi.c:2231 with
-mstack-arg-probe
   Product: gcc
   Version: 5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: target
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zsojka at seznam dot cz

Created attachment 34389
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34389action=edit
reduced testcase

Compiler output:
$ gcc -O2 -mstack-arg-probe testcase.c 
testcase.c: In function 'bar':
testcase.c:19:1: internal compiler error: in maybe_record_trace_start, at
dwarf2cfi.c:2302
 }
 ^
0x879e5c maybe_record_trace_start
/mnt/svn/gcc-trunk/gcc/dwarf2cfi.c:2302
0x87aa53 scan_trace
/mnt/svn/gcc-trunk/gcc/dwarf2cfi.c:2480
0x87c20a create_cfi_notes
/mnt/svn/gcc-trunk/gcc/dwarf2cfi.c:2634
0x87c20a execute_dwarf2_frame
/mnt/svn/gcc-trunk/gcc/dwarf2cfi.c:2990
0x87c20a execute
/mnt/svn/gcc-trunk/gcc/dwarf2cfi.c:3470
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.

Tested revisions:
r219255 - ICE
4_9 r219040 - ICE
4_8 r219093 - ICE
4_7 r211571 - ICE
4_6 r197894 - OK


[Bug c++/64514] New: Error in template instantiation in GCC 4.9, works fine in GCC 4.8

2015-01-06 Thread freddie_chopin at op dot pl
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64514

Bug ID: 64514
   Summary: Error in template instantiation in GCC 4.9, works fine
in GCC 4.8
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: c++
  Assignee: unassigned at gcc dot gnu.org
  Reporter: freddie_chopin at op dot pl

The test code below works perfectly fine with GCC 4.8 (and 4.7):

--- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 ---

#include type_traits

templatetypename T, T object, typename... Args
struct Functor
{
templatefloat (T::*function)(Args...), Args... args
struct Inner
{
float operator()() const
{
return (object.*function)(args...);
}
};
};

class Object
{
public:

float someFunction()
{
return {};
}

float someFunctionWithArgument(int)
{
return {};
}
};

Object object;

FunctorObject, object::InnerObject::someFunction functor1;
FunctorObject, object, int::InnerObject::someFunctionWithArgument, 1
functor2;

int main()
{

}

--- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 ---

However with GCC 4.9 it fails with a rather unhelpful message at the point of
instantiation of functor1:

--- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 ---

$ g++ -std=c++11 test.cpp 
test.cpp: In instantiation of ‘struct FunctorObject, (*  object)’:
test.cpp:33:24:   required from here
test.cpp:7:9: error: wrong number of template arguments (2, should be 1)
  struct Inner
 ^
test.cpp:7:9: error: provided for ‘templateclass T, T object, class ... Args
templatefloat (T::* function)(Args ...), Args ...args struct FunctorT,
object, Args::Inner’
test.cpp:7:9: error: wrong number of template arguments (2, should be 1)
test.cpp:7:9: error: provided for ‘templateclass T, T object, class ... Args
templatefloat (T::* function)(Args ...), Args ...args struct FunctorT,
object, Args::Inner’
test.cpp:33:26: error: ‘Inner’ in ‘struct FunctorObject, (*  object)’ does
not name a template type
 FunctorObject, object::InnerObject::someFunction functor1;
  ^

--- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 --- 8 ---

If I comment the line with functor1 instantiation, everything else (functor2)
works fine.

At the stackoverflow question I asked (
http://stackoverflow.com/questions/27802404/error-in-template-instantiation-in-gcc-4-9-works-fine-in-gcc-4-8?noredirect=1#comment44015634_27802404
) it was reported that clang 3.5 and Visual Studio 2015 Preview accept this
code, while intel 14 errors out (with an unreported message) and solaris studio
12.4 crashes.

Is there something wrong with this code (which was working for me for over 2
years with older versions) or maybe this is a regression?

[Bug target/64505] Powerpc compiler generates insn not found for -m32 -mpowerpc64

2015-01-06 Thread meissner at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64505

--- Comment #1 from Michael Meissner meissner at gcc dot gnu.org ---
Author: meissner
Date: Tue Jan  6 20:29:54 2015
New Revision: 219264

URL: https://gcc.gnu.org/viewcvs?rev=219264root=gccview=rev
Log:
[gcc]
2015-01-06  Michael Meissner  meiss...@linux.vnet.ibm.com

PR target/64505
* config/rs6000/rs6000.c (rs6000_secondary_reload): Return the
correct reload handler if -m32 -mpowerpc64 is used.

[gcc/testsuite]
2015-01-06  Michael Meissner  meiss...@linux.vnet.ibm.com

PR target/64505
* gcc.target/powerpc/pr64505.c: New file to test -m32 -mpowerpc64
fix is correct.


Added:
trunk/gcc/testsuite/gcc.target/powerpc/pr64505.c
Modified:
trunk/gcc/ChangeLog
trunk/gcc/config/rs6000/rs6000.c
trunk/gcc/testsuite/ChangeLog


[Bug c++/64455] A constexpr variable template can't be used with enable_if

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64455

--- Comment #3 from Jason Merrill jason at gcc dot gnu.org ---
Author: jason
Date: Tue Jan  6 20:44:51 2015
New Revision: 219268

URL: https://gcc.gnu.org/viewcvs?rev=219268root=gccview=rev
Log:
PR c++/64455
* pt.c (type_dependent_expression_p): Handle variable templates.
* constexpr.c (potential_constant_expression_1): Use it.

Added:
trunk/gcc/testsuite/g++.dg/cpp1y/var-templ21.C
Modified:
trunk/gcc/cp/ChangeLog
trunk/gcc/cp/constexpr.c
trunk/gcc/cp/pt.c


[Bug c++/64487] [4.8/4.9/5 Regression] internal compiler error: in fold_offsetof_1, at c-family/c-common.c:9857

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64487

--- Comment #3 from Jason Merrill jason at gcc dot gnu.org ---
Author: jason
Date: Tue Jan  6 20:44:46 2015
New Revision: 219267

URL: https://gcc.gnu.org/viewcvs?rev=219267root=gccview=rev
Log:
PR c++/64487
* semantics.c (finish_offsetof): Handle templates here.
* parser.c (cp_parser_builtin_offsetof): Not here.

Added:
trunk/gcc/testsuite/g++.dg/template/offsetof3.C
Modified:
trunk/gcc/cp/ChangeLog
trunk/gcc/cp/parser.c
trunk/gcc/cp/semantics.c


[Bug c++/64496] [4.8/4.9/5 Regression] ICE with NSDMI and lambda

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64496

--- Comment #1 from Jason Merrill jason at gcc dot gnu.org ---
Author: jason
Date: Tue Jan  6 20:44:39 2015
New Revision: 219266

URL: https://gcc.gnu.org/viewcvs?rev=219266root=gccview=rev
Log:
PR c++/64496
* semantics.c (process_outer_var_ref): Diagnose lambda in local
class NSDMI.

Added:
trunk/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-nsdmi7.C
Modified:
trunk/gcc/cp/ChangeLog
trunk/gcc/cp/semantics.c


[Bug c++/64489] A simple struct wrapping a const int is not trivially copyable

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64489

--- Comment #2 from Jason Merrill jason at gcc dot gnu.org ---
Author: jason
Date: Tue Jan  6 20:44:32 2015
New Revision: 219265

URL: https://gcc.gnu.org/viewcvs?rev=219265root=gccview=rev
Log:
PR c++/64489
* class.c (check_field_decls): Make copy assignment operators
complex only in c++98 mode.

Modified:
trunk/gcc/cp/ChangeLog
trunk/gcc/cp/class.c
trunk/gcc/testsuite/g++.dg/ext/is_trivially_constructible1.C


[Bug c/64515] Segmentation fault during linker operation in gcc for arm-none-eabi

2015-01-06 Thread karolas801 at student dot polsl.pl
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64515

--- Comment #1 from Karol karolas801 at student dot polsl.pl ---
Problem doesn't occurs in gcc 4.9 version


[Bug c++/64489] A simple struct wrapping a const int is not trivially copyable

2015-01-06 Thread ville.voutilainen at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64489

Ville Voutilainen ville.voutilainen at gmail dot com changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

--- Comment #3 from Ville Voutilainen ville.voutilainen at gmail dot com ---
Fixed, then.



[Bug preprocessor/47857] Pragma once warning when compiling PCH

2015-01-06 Thread p_hampson at wargaming dot net
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=47857

Paul TBBle Hampson p_hampson at wargaming dot net changed:

   What|Removed |Added

 CC||p_hampson at wargaming dot net

--- Comment #6 from Paul TBBle Hampson p_hampson at wargaming dot net ---
This looks like a specific instance or duplicate of the much older bug 9471.


[Bug c++/56126] -fno-exceptions should activate -fcheck-new or issue diagnostic for all new operators without throw()

2015-01-06 Thread olafvdspek at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56126

--- Comment #10 from Olaf van der Spek olafvdspek at gmail dot com ---
On Tue, Jan 6, 2015 at 2:22 PM, bruck.michael at googlemail dot com
gcc-bugzi...@gcc.gnu.org wrote:
 https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56126

 --- Comment #9 from Michael Bruck bruck.michael at googlemail dot com ---
 Jonathan: Using -fno-exceptions says I do not want ISO C++ so quoting the 
 standard isn't very relevant.
 Olaf: No, as you could (should?) abort/terminate instead of returning NULL.

 I quoted it to illustrate that returning NULL is the intuitive option here,
 while abort() is a completely new approach. Returning NULL is what I would
 expect to be the case when -fno-exceptions is active and it is what happens in
 the libc++ implementation AFAIK.

-fno-exceptions transforms throws into aborts in the STL.
Unfortunately it doesn't do that for other code but I've filed a
feature request for to fix that.

Given this transformation aborting would be the natural consequence.
What does the GCC STL do?

 Why would you want an operator new that can't throw but is declared to 
 potentially throw?

 Because -fno-exceptions suggests to the user that they can produce safe code
 without using any exception-specific C++ syntax.

I think we disagree on that part.

BTW, what's your use case? Do you really want to check NULL on every
call to new?

Olaf


[Bug libstdc++/64467] [5 Regression] 28_regex/traits/char/isctype.cc and wchar_t/isctype.cc

2015-01-06 Thread hp at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64467

--- Comment #5 from Hans-Peter Nilsson hp at gcc dot gnu.org ---
(In reply to Jonathan Wakely from comment #3)
 Almost certainly r217066.
 
 Is this a newlib target? I would expect to see the same failure for all
 newlib targets,

I verified that this is the case for mmix-knuth-mmixware and arm-eabi too, just
to eliminate my initial suspicion that this was a target bug.

 as I defined std::ctype_base::blank to be equal to
 std::ctype_base::space for newlib (and any libc where I couldn't determine
 the right bitmask for the [:blank:] character class) and the [:space:] class
 includes newline.

Uh, src/newlib/libc/include/ctype.h:

#define _B  0200
...
#define isblank(__c) \
  __extension__ ({ __typeof__ (__c) __x = (__c);\
(__ctype_lookup(__x)_B) || (int) (__x) == '\t';})

(while isspace has it's own bit, #define _S  010)
HTH. :)

But that might not be very helpful, I'm just not sure how to help.


[Bug target/64479] [4.8 Regression][SH] wrong optimization delayed-branch

2015-01-06 Thread olegendo at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64479

--- Comment #2 from Oleg Endo olegendo at gcc dot gnu.org ---
The *cbranch_t splitter is done like 4 times, because there are 4 split passes.
 The last split pass is split5, which is done right after the delayed-branch
pass.  Before delayed-branch handling the call insn looks like:

(call_insn 13 79 14 2 (parallel [
(call (mem:SI (reg/f:SI 1 r1 [167]) [0 bar S4 A32])
(const_int 0 [0]))
(use (reg:PSI 151 ))
(clobber (reg:SI 146 pr))
]) sh_tmp.cpp:453 304 {calli}
 (expr_list:REG_DEAD (reg:PSI 151 )
(expr_list:REG_DEAD (reg:SI 4 r4)
(expr_list:REG_DEAD (reg/f:SI 1 r1 [167])
(nil
(expr_list:REG_UNUSED (use (reg:SI 4 r4))
(nil)))

And modified_between_p returns true.

After delayed-branch pass the call insn looks like:

(insn 122 60 14 (sequence [
(call_insn 13 60 12 (parallel [
(call (mem:SI (reg/f:SI 1 r1 [167]) [0 bar S4 A32])
(const_int 0 [0]))
(use (reg:PSI 151 ))
(clobber (reg:SI 146 pr))
]) sh_tmp.cpp:453 304 {calli}
 (expr_list:REG_DEAD (reg:PSI 151 )
(expr_list:REG_DEAD (reg:SI 4 r4)
(expr_list:REG_DEAD (reg/f:SI 1 r1 [167])
(nil
(expr_list:REG_UNUSED (use (reg:SI 4 r4))
(nil)))
(insn 12 13 14 (set (reg:SI 4 r4)
(reg/f:SI 15 r15)) 247 {movsi_ie}
 (nil))
]) sh_tmp.cpp:453 -1
 (nil))

And modified_between_p returns false, because the function reg_set_p doesn't
handle sequence rtx codes.

This could be a fix:

Index: gcc/rtlanal.c
===
--- gcc/rtlanal.c(revision 218544)
+++ gcc/rtlanal.c(working copy)
@@ -875,17 +875,24 @@
 {
   /* We can be passed an insn or part of one.  If we are passed an insn,
  check if a side-effect of the insn clobbers REG.  */
-  if (INSN_P (insn)
-   (FIND_REG_INC_NOTE (insn, reg)
-  || (CALL_P (insn)
-   ((REG_P (reg)
-REGNO (reg)  FIRST_PSEUDO_REGISTER
-overlaps_hard_reg_set_p (regs_invalidated_by_call,
-   GET_MODE (reg), REGNO (reg)))
-  || MEM_P (reg)
-  || find_reg_fusage (insn, CLOBBER, reg)
-return 1;
+  if (INSN_P (insn)  FIND_REG_INC_NOTE (insn, reg))
+return true;

+  /* After delay slot handling, call and branch insns might be in a
+ sequence.  Check all the elements there.  */
+  if (INSN_P (insn)  GET_CODE (PATTERN (insn)) == SEQUENCE)
+for (int i = 0; i  XVECLEN (PATTERN (insn), 0); ++i)
+  if (reg_set_p (reg, XVECEXP (PATTERN (insn), 0, i)))
+return true;
+
+  if (CALL_P (insn)
+   ((REG_P (reg)  REGNO (reg)  FIRST_PSEUDO_REGISTER
+overlaps_hard_reg_set_p (regs_invalidated_by_call,
+   GET_MODE (reg), REGNO (reg)))
+  || MEM_P (reg)
+  || find_reg_fusage (insn, CLOBBER, reg)))
+return true;
+
   return set_of (reg, insn) != NULL_RTX;
 }


I haven't checked it, but maybe this also helps PR 56451 in some way.


Alternatively, we can just disable the *cbranch_t splitter after the
delay-branch pass:

Index: gcc/config/sh/sh.md
===
--- gcc/config/sh/sh.md(revision 218544)
+++ gcc/config/sh/sh.md(working copy)
@@ -8361,7 +8361,7 @@
 {
   return output_branch (sh_eval_treg_value (operands[1]), insn, operands);
 }
-   1
+   !crtl-dbr_scheduled_p
   [(set (pc) (if_then_else (eq (reg:SI T_REG) (match_dup 2))
(label_ref (match_dup 0))
(pc)))]


Both patches fix the problem here, but I haven't tested them further.  My
feeling is that the function reg_set_p should be fixed.


[Bug c++/64496] [4.8/4.9/5 Regression] ICE with NSDMI and lambda

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64496

Jason Merrill jason at gcc dot gnu.org changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED
   Assignee|unassigned at gcc dot gnu.org  |jason at gcc dot gnu.org
   Target Milestone|4.8.5   |5.0

--- Comment #2 from Jason Merrill jason at gcc dot gnu.org ---
Fixed for GCC 5.


[Bug debug/64511] [5 Regression] ICE at -O3 with -g enabled on x86_64-linux-gnu

2015-01-06 Thread glisse at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64511

Marc Glisse glisse at gcc dot gnu.org changed:

   What|Removed |Added

  Component|c   |debug

--- Comment #2 from Marc Glisse glisse at gcc dot gnu.org ---
The explosion seems to be in var tracking.


[Bug c/64511] [5 Regression] ICE at -O3 with -g enabled on x86_64-linux-gnu

2015-01-06 Thread hjl.tools at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64511

H.J. Lu hjl.tools at gmail dot com changed:

   What|Removed |Added

 Status|UNCONFIRMED |NEW
   Last reconfirmed||2015-01-06
 CC||rguenther at suse dot de
   Target Milestone|--- |5.0
Summary|ICE at -O3 with -g enabled  |[5 Regression] ICE at -O3
   |on x86_64-linux-gnu |with -g enabled on
   ||x86_64-linux-gnu
 Ever confirmed|0   |1

--- Comment #1 from H.J. Lu hjl.tools at gmail dot com ---
It was caused by r216728.


[Bug c/64515] New: Segmentation fault during linker operation in gcc for arm-none-eabi

2015-01-06 Thread karolas801 at student dot polsl.pl
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64515

Bug ID: 64515
   Summary: Segmentation fault during linker operation in gcc for
arm-none-eabi
   Product: gcc
   Version: 4.8.4
Status: UNCONFIRMED
  Severity: major
  Priority: P3
 Component: c
  Assignee: unassigned at gcc dot gnu.org
  Reporter: karolas801 at student dot polsl.pl

Created attachment 34390
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34390action=edit
full log from compilation

I was wondering the new ChibiOS RTOS version, so I clone it
(https://github.com/ChibiOS/ChibiOS branch master), go to:
testhal/STM32/STM32F1xx/USB_CDC
and type make. After compilation I saw linker error:

Linking build/ch.elf
../../../../test/rt/test.c: In function 'TestThread':
../../../../test/rt/test.c:314:7: internal compiler error: Segmentation fault
 msg_t TestThread(void *p) {
   ^
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html for instructions.
lto-wrapper: arm-none-eabi-gcc returned 1 exit status
/home/cruz/Embedded_systems/toolchain/bin/../lib/gcc/arm-none-eabi/4.8.4/../../../../arm-none-eabi/bin/ld:
lto-wrapper failed
collect2: error: ld returned 1 exit status
make: *** [build/ch.elf] Błąd 1

So I submit to you full bug report :)

My system:

lsb_release -a
No LSB modules are available.
Distributor ID:LinuxMint
Description:Linux Mint 16 Petra
Release:16
Codename:petra


kernel:
Linux cruz-laptop 3.11.0-12-generic #19-Ubuntu SMP Wed Oct 9 16:20:46 UTC 2013
x86_64 x86_64 x86_64 GNU/Linux

In attachement full log from compilation.

[Bug c++/64487] [4.8/4.9 Regression] internal compiler error: in fold_offsetof_1, at c-family/c-common.c:9857

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64487

Jason Merrill jason at gcc dot gnu.org changed:

   What|Removed |Added

   Keywords||ice-on-valid-code
 Status|NEW |ASSIGNED
   Assignee|unassigned at gcc dot gnu.org  |jason at gcc dot gnu.org
Summary|[4.8/4.9/5 Regression]  |[4.8/4.9 Regression]
   |internal compiler error: in |internal compiler error: in
   |fold_offsetof_1, at |fold_offsetof_1, at
   |c-family/c-common.c:9857|c-family/c-common.c:9857

--- Comment #4 from Jason Merrill jason at gcc dot gnu.org ---
Fixed on trunk so far.


[Bug c/64511] New: ICE at -O3 with -g enabled on x86_64-linux-gnu

2015-01-06 Thread su at cs dot ucdavis.edu
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64511

Bug ID: 64511
   Summary: ICE at -O3 with -g enabled on x86_64-linux-gnu
   Product: gcc
   Version: 5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: c
  Assignee: unassigned at gcc dot gnu.org
  Reporter: su at cs dot ucdavis.edu

The following code causes an ICE (after a very very long pause) when compiled
with the current gcc trunk at -O3 with -g enabled on x86_64-linux-gnu in 64-bit
mode (but not in 32-bit mode). 

It is a regression from 4.9.x.

$ gcc-trunk -v
Using built-in specs.
COLLECT_GCC=gcc-trunk
COLLECT_LTO_WRAPPER=/usr/local/gcc-trunk/libexec/gcc/x86_64-unknown-linux-gnu/5.0.0/lto-wrapper
Target: x86_64-unknown-linux-gnu
Configured with: ../gcc-trunk/configure --prefix=/usr/local/gcc-trunk
--enable-languages=c,c++ --disable-werror --enable-multilib
Thread model: posix
gcc version 5.0.0 20150106 (experimental) [trunk revision 219217] (GCC) 

$ 
$ gcc-trunk -O3 -c small.c
$ gcc-4.9 -O3 -g -c small.c
$ 
$ time gcc-trunk -O3 -g -c small.c
gcc-trunk: internal compiler error: Segmentation fault (program cc1)
0x40c1de execute
../../gcc-trunk/gcc/gcc.c:2912
0x40c4e9 do_spec_1
../../gcc-trunk/gcc/gcc.c:4845
0x40eaf7 process_brace_body
../../gcc-trunk/gcc/gcc.c:6128
0x40eaf7 handle_braces
../../gcc-trunk/gcc/gcc.c:6042
0x40d4e7 do_spec_1
../../gcc-trunk/gcc/gcc.c:5499
0x40eaf7 process_brace_body
../../gcc-trunk/gcc/gcc.c:6128
0x40eaf7 handle_braces
../../gcc-trunk/gcc/gcc.c:6042
0x40d4e7 do_spec_1
../../gcc-trunk/gcc/gcc.c:5499
0x40c873 do_spec_1
../../gcc-trunk/gcc/gcc.c:5614
0x40eaf7 process_brace_body
../../gcc-trunk/gcc/gcc.c:6128
0x40eaf7 handle_braces
../../gcc-trunk/gcc/gcc.c:6042
0x40d4e7 do_spec_1
../../gcc-trunk/gcc/gcc.c:5499
0x40eaf7 process_brace_body
../../gcc-trunk/gcc/gcc.c:6128
0x40eaf7 handle_braces
../../gcc-trunk/gcc/gcc.c:6042
0x40d4e7 do_spec_1
../../gcc-trunk/gcc/gcc.c:5499
0x40eaf7 process_brace_body
../../gcc-trunk/gcc/gcc.c:6128
0x40eaf7 handle_braces
../../gcc-trunk/gcc/gcc.c:6042
0x40d4e7 do_spec_1
../../gcc-trunk/gcc/gcc.c:5499
0x40eaf7 process_brace_body
../../gcc-trunk/gcc/gcc.c:6128
0x40eaf7 handle_braces
../../gcc-trunk/gcc/gcc.c:6042
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.
Command exited with non-zero status 4
50.56user 1.04system 2:06.99elapsed 40%CPU (0avgtext+0avgdata
5923360maxresident)k
56inputs+0outputs (4major+371046minor)pagefaults 0swaps
$ 


--


char a;
unsigned short b;
int c;
unsigned long d;

void fn1 ()
{
  for (;;)
;
}

void fn2 (unsigned char p1)
{
  unsigned char *e = p1;
  c = 27;
  for (; c  37; c++)
b *= (a %= ((*e %= *e) ^ 0));
  p1 /= d = a;
  fn1 (p1);
}


[Bug target/64512] New: ICE: in sched_analyze_reg, at sched-deps.c:2360 with -O2 -mmemcpy-strategy=vector_loop:-1:align -mno-push-args

2015-01-06 Thread zsojka at seznam dot cz
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64512

Bug ID: 64512
   Summary: ICE: in sched_analyze_reg, at sched-deps.c:2360 with
-O2 -mmemcpy-strategy=vector_loop:-1:align
-mno-push-args
   Product: gcc
   Version: 5.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: target
  Assignee: unassigned at gcc dot gnu.org
  Reporter: zsojka at seznam dot cz

Created attachment 34388
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34388action=edit
reduced testcase

Compiler output:
$ gcc -O2 -mmemcpy-strategy=vector_loop:-1:align -mno-push-args testcase.c 
testcase.c: In function 'foo':
testcase.c:20:1: internal compiler error: in sched_analyze_reg, at
sched-deps.c:2360
 }
 ^
0x17210af sched_analyze_reg
/mnt/svn/gcc-trunk/gcc/sched-deps.c:2360
0x1722513 sched_analyze_2
/mnt/svn/gcc-trunk/gcc/sched-deps.c:2625
0x1722249 sched_analyze_2
/mnt/svn/gcc-trunk/gcc/sched-deps.c:2731
0x17223c0 sched_analyze_2
/mnt/svn/gcc-trunk/gcc/sched-deps.c:2843
0x1724600 sched_analyze_insn
/mnt/svn/gcc-trunk/gcc/sched-deps.c:2993
0x1725f0b deps_analyze_insn(deps_desc*, rtx_insn*)
/mnt/svn/gcc-trunk/gcc/sched-deps.c:3731
0x17268a9 sched_analyze(deps_desc*, rtx_insn*, rtx_insn*)
/mnt/svn/gcc-trunk/gcc/sched-deps.c:3826
0xbf702e compute_block_dependences
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:2748
0xbf702e sched_rgn_compute_dependencies(int)
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:3272
0xbf9e20 schedule_region
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:3028
0xbf9e20 schedule_insns()
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:3431
0xbfa67d schedule_insns()
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:3416
0xbfa67d rest_of_handle_sched2
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:3655
0xbfa67d execute
/mnt/svn/gcc-trunk/gcc/sched-rgn.c:3791
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See http://gcc.gnu.org/bugs.html for instructions.

Tested revisions:
r219255 - ICE


[Bug fortran/55901] [OOP] type is (character(len=*)) misinterpreted as array

2015-01-06 Thread anlauf at gmx dot de
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=55901

--- Comment #10 from Harald Anlauf anlauf at gmx dot de ---
(In reply to paul.richard.tho...@gmail.com from comment #9)
 By the way, the patch of comment 8 bootstraps and regtests OK
 
 Paul

Hi Paul,

any news on that patch?

Harald


[Bug c++/64455] A constexpr variable template can't be used with enable_if

2015-01-06 Thread jason at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64455

Jason Merrill jason at gcc dot gnu.org changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 CC||jason at gcc dot gnu.org
 Resolution|--- |FIXED
   Assignee|unassigned at gcc dot gnu.org  |jason at gcc dot gnu.org

--- Comment #4 from Jason Merrill jason at gcc dot gnu.org ---
Fixed.


[Bug other/57928] Doesn't compile with ISL 0.12

2015-01-06 Thread egall at gwmail dot gwu.edu
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=57928

Eric Gallager egall at gwmail dot gwu.edu changed:

   What|Removed |Added

 CC||egall at gwmail dot gwu.edu

--- Comment #1 from Eric Gallager egall at gwmail dot gwu.edu ---
The prerequisites page now says it works with isl 0.14 or 0.12.2:
https://gcc.gnu.org/install/prerequisites.html


[Bug target/64516] New: arm: wrong unaligned load generated

2015-01-06 Thread markus at oberhumer dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64516

Bug ID: 64516
   Summary: arm: wrong unaligned load generated
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: target
  Assignee: unassigned at gcc dot gnu.org
  Reporter: markus at oberhumer dot com

Created attachment 34391
  -- https://gcc.gnu.org/bugzilla/attachment.cgi?id=34391action=edit
unaligned_load_bug.c to reproduce the problem.

arm: bad code generated = run time crash

- gcc 4.9.2 seems to forget the attribute(packed) in some cases.

- please see the disassembly for get16_unaligned().

- put16_unaligned() is correct !

- FWIW, gcc 4.3.5 and clang 3.5 work

~Markus


$ cat unaligned_load_bug.c
typedef struct { char a[2]; } __attribute__((__packed__)) TU2;

// OK: correct (but poor) code generated for the store
void put16_unaligned(void *p, unsigned short v) {
if (sizeof(TU2) == sizeof(v)  __alignof__(TU2) == 1) {
*(TU2 *)p = *(const TU2 *)(const void *)(v);
}
}

// BUG: incorrect transformation into an aligned load = run time crash !!
unsigned short get16_unaligned(const void *p) {
unsigned short v;
if (sizeof(TU2) == sizeof(v)  __alignof__(TU2) == 1) {
*(TU2 *)(void *)(v) = *(const TU2 *)p;
}
return v;
}

// aligned versions - just for comparison
void put16_aligned(void *p, unsigned short v) {
*(unsigned short *)p = *(v);
}
unsigned short get16_aligned(const void *p) {
unsigned short v;
*(v) = *(const unsigned short *)p;
return v;
}

// EOF

$ arm-linux-gnueabi-gcc-4.9 -v
gcc version 4.9.2 (Ubuntu/Linaro 4.9.2-7ubuntu3)

$ arm-linux-gnueabi-gcc-4.9 -march=armv4 -marm -O2 -Wall -W -Wcast-align -c
unaligned_load_bug.c

$ arm-linux-gnueabi-objdump -d unaligned_load_bug.o

unaligned_load_bug.o: file format elf32-littlearm

Disassembly of section .text:

 put16_unaligned:
   0:   e52de004push{lr}; (str lr, [sp, #-4]!)
   4:   e24dd00csub sp, sp, #12
   8:   e28d3008add r3, sp, #8
   c:   e16310b2strhr1, [r3, #-2]!
  10:   e3a02002mov r2, #2
  14:   e1a01003mov r1, r3
  18:   ebfebl  0 memcpy
  1c:   e28dd00cadd sp, sp, #12
  20:   e49de004pop {lr}; (ldr lr, [sp], #4)
  24:   e12fff1ebx  lr

0028 get16_unaligned:
  28:   e1d000b0ldrhr0, [r0]
  2c:   e12fff1ebx  lr

0030 put16_aligned:
  30:   e1c010b0strhr1, [r0]
  34:   e12fff1ebx  lr

0038 get16_aligned:
  38:   e1d000b0ldrhr0, [r0]
  3c:   e12fff1ebx  lr


[Bug testsuite/62250] FAIL: gfortran.dg/coarray/alloc_comp_1.f90 -fcoarray=lib -O2 -lcaf_single

2015-01-06 Thread hp at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=62250

--- Comment #5 from Hans-Peter Nilsson hp at gcc dot gnu.org ---
(In reply to Hans-Peter Nilsson from comment #4)
 Also, the patch should have used
 atomic-dg.exp instead of manually adding the search paths.

Easier said than done, unfortunately.  Doing a simpler fix.


[Bug testsuite/62250] FAIL: gfortran.dg/coarray/alloc_comp_1.f90 -fcoarray=lib -O2 -lcaf_single

2015-01-06 Thread dave.anglin at bell dot net
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=62250

--- Comment #7 from dave.anglin at bell dot net ---
On 2015-01-06, at 10:10 PM, hp at gcc dot gnu.org wrote:

 Easier said than done, unfortunately.  Doing a simpler fix.

Thanks

--
John David Anglindave.ang...@bell.net


[Bug fortran/64517] New: Inconsistent behavior when mixing -E and -M

2015-01-06 Thread thfanning at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64517

Bug ID: 64517
   Summary: Inconsistent behavior when mixing -E and -M
   Product: gcc
   Version: 4.9.2
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: thfanning at gmail dot com

According to documentation, Passing -M to the driver implies -E. However an
explicit `-E` produces different behavior.

  touch test.F90
  gfortran -M test.F90

produces:

  test.o: test.F90

However,

  gfortran -E -M test.F90

produces

  # 1 test.F90
  # 1 built-in
  # 1 command-line
  # 1 test.F90

  test.o: test.F90

As a result, preprocessor output is mixed with dependency output. A kludge is
to add `-o /dev/null`, but that is ugly.

The description for `-E` states: The output is in the form of preprocessed
source code, which is sent to the standard output. But shouldn't `-M` change
*what* is sent to stdout?


[Bug testsuite/62250] FAIL: gfortran.dg/coarray/alloc_comp_1.f90 -fcoarray=lib -O2 -lcaf_single

2015-01-06 Thread dave.anglin at bell dot net
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=62250

--- Comment #6 from dave.anglin at bell dot net ---
On 2015-01-06, at 9:06 PM, hp at gcc dot gnu.org wrote:

 But instead causing these tests to fail for all targets that don't have
 -latomic.
 I.e. -latomic should only be added when there is one, otherwise assume that
 support is built-in as before the patch.  Also, the patch should have used
 atomic-dg.exp instead of manually adding the search paths.

That is clearly a better approach.

What about the gfortran.dg/coarray_lib_comm_1.f90 test?  Do you see a better
alternative than adding load_lib atomic-dg.exp to gfortran.dg/dg.exp?

--
John David Anglindave.ang...@bell.net


[Bug libstdc++/64239] regex_iterator::operator= should copy match_results::position

2015-01-06 Thread kariya_mitsuru at hotmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64239

--- Comment #7 from Mitsuru Kariya kariya_mitsuru at hotmail dot com ---
When I used the match_results::swap on r218710, I got a compilation error.

== sample code
==
#include regex

int main()
{
  std::cmatch mm1, mm2;

  mm1.swap(mm2);
}
=

== g++ output
===
In file included from /usr/local/gcc-218710/include/c++/5.0.0/regex:59:0,
 from swap.cpp:1:
/usr/local/gcc-218710/include/c++/5.0.0/bits/regex.h: In instantiation of 'void
std::match_results template-parameter-1-1, template-parameter-1-2
::swap(std::match_results template-parameter-1-1, template-parameter-1-2
) [with _Bi_iter = const char*; _Alloc = std::allocatorstd::sub_matchconst
char* ]':
swap.cpp:7:15:   required from here
/usr/local/gcc-218710/include/c++/5.0.0/bits/regex.h:1864:6: error: no matching
function for call to 'std::match_resultsconst char*::swap(const char*, const
char*)'
  swap(_M_begin, __that._M_begin);
  ^
/usr/local/gcc-218710/include/c++/5.0.0/bits/regex.h:1861:7: note: candidate:
void std::match_results template-parameter-1-1, template-parameter-1-2
::swap(std::match_results template-parameter-1-1, template-parameter-1-2
) [with _Bi_iter = const char*; _Alloc = std::allocatorstd::sub_matchconst
char* ]
   swap(match_results __that)
   ^
/usr/local/gcc-218710/include/c++/5.0.0/bits/regex.h:1861:7: note:   candidate
expects 1 argument, 2 provided
=

 g++ -v
=
Using built-in specs.
COLLECT_GCC=/usr/local/gcc-218710/bin/g++
COLLECT_LTO_WRAPPER=/usr/local/gcc-218710/libexec/gcc/x86_64-unknown-linux-gnu/5.0.0/lto-wrapper
Target: x86_64-unknown-linux-gnu
Configured with: ../gcc.218710/configure --prefix=/usr/local/gcc-218710
--enable-checking=yes --disable-nls --enable-languages=c,c++,lto
Thread model: posix
gcc version 5.0.0 20141213 (experimental) (GCC)
=

Note that the sample code above was compiled successfully on r218555.

I think that the match_results::swap needs use std::swap; for swapping
_M_begin.


[Bug testsuite/62250] FAIL: gfortran.dg/coarray/alloc_comp_1.f90 -fcoarray=lib -O2 -lcaf_single

2015-01-06 Thread hp at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=62250

Hans-Peter Nilsson hp at gcc dot gnu.org changed:

   What|Removed |Added

 CC||hp at gcc dot gnu.org

--- Comment #4 from Hans-Peter Nilsson hp at gcc dot gnu.org ---
(In reply to John David Anglin from comment #3)
 Fixed.

But instead causing these tests to fail for all targets that don't have
-latomic.
I.e. -latomic should only be added when there is one, otherwise assume that
support is built-in as before the patch.  Also, the patch should have used
atomic-dg.exp instead of manually adding the search paths.


[Bug fortran/64517] Inconsistent behavior when mixing -E and -M

2015-01-06 Thread thfanning at gmail dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64517

--- Comment #1 from Thomas Fanning thfanning at gmail dot com ---
There is a bigger problem that I didn't immediately recognize with the empty
file: Using `-M` results in gfortran trying to compile the source. I.e., it
does *not* stop after preprocessing, which it should if `-E` is implied.


[Bug c/64509] _Generic throws error in unselected generic association

2015-01-06 Thread maurits.de.jong at ericsson dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64509

--- Comment #2 from Martien de Jong maurits.de.jong at ericsson dot com ---
That's just rephrasing my bugreport. The question is, should it type check
while parsing an expression that may not be realized? The entire idea of
switching on a type is to prevent and fix type errors, no?


[Bug target/64149] -mno-lra bitrots, suggest to remove for GCC 5

2015-01-06 Thread mshawcroft at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64149

mshawcroft at gcc dot gnu.org changed:

   What|Removed |Added

 CC||mshawcroft at gcc dot gnu.org
   Assignee|unassigned at gcc dot gnu.org  |mshawcroft at gcc dot 
gnu.org

--- Comment #3 from mshawcroft at gcc dot gnu.org ---
Mine.


[Bug c/64440] -Wdiv-by-zero false negative on const variables

2015-01-06 Thread mpolacek at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64440

Marek Polacek mpolacek at gcc dot gnu.org changed:

   What|Removed |Added

 Status|UNCONFIRMED |ASSIGNED
   Last reconfirmed||2015-01-06
   Assignee|unassigned at gcc dot gnu.org  |mpolacek at gcc dot 
gnu.org
   Target Milestone|--- |5.0
 Ever confirmed|0   |1

--- Comment #5 from Marek Polacek mpolacek at gcc dot gnu.org ---
C++ FE warns for the div-by-zero testcase, and C FE can easily too, I think. 
Ditto for %.  Mine.


[Bug target/63596] Saving of GPR/FPRs for stdarg even though the variable argument is not used

2015-01-06 Thread jiwang at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=63596

Jiong Wang jiwang at gcc dot gnu.org changed:

   What|Removed |Added

 Status|NEW |ASSIGNED


[Bug target/56025] ARM NEON polynomial types have broken overload resolution

2015-01-06 Thread belagod at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56025

Tejas Belagod belagod at gcc dot gnu.org changed:

   What|Removed |Added

 Status|RESOLVED|REOPENED
 Resolution|FIXED   |---

--- Comment #3 from Tejas Belagod belagod at gcc dot gnu.org ---
(In reply to Tejas Belagod from comment #2)
 (In reply to Tim Northover from comment #0)
  While investigating bug #56024, we discovered this problem in the same area.
  Essentially, GCC has semi-special builtin types to cover poly8_t and
  poly16_t defined in arm_neon.h.
  
  These types are used by G++ when calculating the overload resolution. The
  following two functions can both be defined with no issues in the front-end:
  
  #include arm_neon.h
  void foo(short s) {}
  void foo(__builtin_neon_poly16 s) {}
  
  However, in the resulting assembly they are both mangled as _Z3foos, which
  causes a conflict.
  
  This mangling area is likely to be affected by any change fixing 56024, so a
  sensible combined solution might be a good idea.
 
 This should now be fixed. Now mangled as _Z3foos and _Z3foo10__Poly16_t
 respectively.
 
   .cpu generic+fp+simd
   .file   gpp.cpp
   .text
   .align  2
   .p2align 3,,7
   .global _Z3foos
   .type   _Z3foos, %function
 _Z3foos:
 .LFB3026:
   .cfi_startproc
   ret
   .cfi_endproc
 .LFE3026:
   .size   _Z3foos, .-_Z3foos
   .align  2
   .p2align 3,,7
   .global _Z3foo10__Poly16_t
   .type   _Z3foo10__Poly16_t, %function
 _Z3foo10__Poly16_t:
 .LFB3027:
   .cfi_startproc
   ret
   .cfi_endproc
 .LFE3027:
   .size   _Z3foo10__Poly16_t, .-_Z3foo10__Poly16_t
   .ident  GCC: (unknown) 5.0.0 20141229 (experimental)

Sorry, wrong target. Still doesn't seem to be fixed for aarch32.

[Bug rtl-optimization/64304] AArch64 miscompilation with -mgeneral-regs-only

2015-01-06 Thread jiwang at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64304

Jiong Wang jiwang at gcc dot gnu.org changed:

   What|Removed |Added

 Status|UNCONFIRMED |ASSIGNED
   Last reconfirmed||2015-01-06
 Ever confirmed|0   |1

--- Comment #2 from Jiong Wang jiwang at gcc dot gnu.org ---
a quick looks shows it's related with SHIFT_COUNT_TRUNCATED.

looks like generic code, especially combine pass, is with wrong usage of
SHIFT_COUNT_TRUNCATED in some situations.


[Bug target/56025] ARM NEON polynomial types have broken overload resolution

2015-01-06 Thread belagod at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56025

Tejas Belagod belagod at gcc dot gnu.org changed:

   What|Removed |Added

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

--- Comment #2 from Tejas Belagod belagod at gcc dot gnu.org ---
(In reply to Tim Northover from comment #0)
 While investigating bug #56024, we discovered this problem in the same area.
 Essentially, GCC has semi-special builtin types to cover poly8_t and
 poly16_t defined in arm_neon.h.
 
 These types are used by G++ when calculating the overload resolution. The
 following two functions can both be defined with no issues in the front-end:
 
 #include arm_neon.h
 void foo(short s) {}
 void foo(__builtin_neon_poly16 s) {}
 
 However, in the resulting assembly they are both mangled as _Z3foos, which
 causes a conflict.
 
 This mangling area is likely to be affected by any change fixing 56024, so a
 sensible combined solution might be a good idea.

This should now be fixed. Now mangled as _Z3foos and _Z3foo10__Poly16_t
respectively.

.cpu generic+fp+simd
.filegpp.cpp
.text
.align2
.p2align 3,,7
.global_Z3foos
.type_Z3foos, %function
_Z3foos:
.LFB3026:
.cfi_startproc
ret
.cfi_endproc
.LFE3026:
.size_Z3foos, .-_Z3foos
.align2
.p2align 3,,7
.global_Z3foo10__Poly16_t
.type_Z3foo10__Poly16_t, %function
_Z3foo10__Poly16_t:
.LFB3027:
.cfi_startproc
ret
.cfi_endproc
.LFE3027:
.size_Z3foo10__Poly16_t, .-_Z3foo10__Poly16_t
.identGCC: (unknown) 5.0.0 20141229 (experimental)


[Bug target/56025] ARM NEON polynomial types have broken overload resolution

2015-01-06 Thread belagod at gcc dot gnu.org
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=56025

--- Comment #4 from Tejas Belagod belagod at gcc dot gnu.org ---
The ABI does not define an internal type name for scalar poly types -
http://infocenter.arm.com/help/topic/com.arm.doc.ihi0042e/IHI0042E_aapcs.pdf.
This will need an ABI update.


[Bug c/64509] _Generic throws error in unselected generic association

2015-01-06 Thread joseph at codesourcery dot com
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64509

--- Comment #3 from joseph at codesourcery dot com joseph at codesourcery dot 
com ---
_Generic is intended for cases like tgmath.h, where calls to all 
functions are still valid for all argument types.  This is a case where 
the expression __f(S) violates a constraint, and that constraint applies 
to all function calls, not just evaluated ones - this is just the same as 
a constraint violation inside if (0), or if 
(expression_that_evaluates_to_0_at_runtime).  (It's also required that 
functions called in unevaluated generic associations are defined somewhere 
in the program; only sizeof and _Alignof have exemptions from that.)