Re: [Patch, Fortran] Extend (lib)coarray API/ABI documentation

2015-03-24 Thread Tobias Burnus

Dear Iain,

Iain Sandoe wrote:
a couple of minor nits that Dominique and I spotted while discussing 
this :


Thanks for the suggestion. I've committed it as Rev. 221615.

Tobias

Index: gcc/fortran/ChangeLog
===
--- gcc/fortran/ChangeLog	(Revision 221614)
+++ gcc/fortran/ChangeLog	(Arbeitskopie)
@@ -1,3 +1,8 @@
+2015-03-24  Iain Sandoe  
+	Tobias Burnus  
+
+	* gfortran.texi (_gfortran_caf_sync_memory): Improve wording.
+
 2015-03-23  Paul Thomas  
 	Mikael Morin  
 
Index: gcc/fortran/gfortran.texi
===
--- gcc/fortran/gfortran.texi	(Revision 221614)
+++ gcc/fortran/gfortran.texi	(Arbeitskopie)
@@ -3860,8 +3860,8 @@
 @item @var{errmsg_len} @tab the buffer size of errmsg.
 @end multitable
 
-@item @emph{NOTE} A simple implementation could be a simple
-@code{__asm__ __volatile__ ("":::"memory)} to prevent code movements.
+@item @emph{NOTE} A simple implementation could be
+@code{__asm__ __volatile__ ("":::"memory")} to prevent code movements.
 @end table
 
 


Re: [Patch, Fortran] Reject unsupported coarray communication

2015-03-24 Thread Tobias Burnus

Dear Dominique,

Dominique Dhumieres wrote:

The test gfortran.dg/coarray/coindexed_3.f90 compiles without error,
see https://gcc.gnu.org/ml/gcc-testresults/2015-03/msg02446.html.


Ups, I somehow missed that files under coarray/ are run with both 
-fcoarray=single and =lib; the error (rightly!) only is shown with =lib.

I have now moved the test case and added an explicit -fcoarray=lib.

Thanks for the report! (Committed as Rev. 221618.)

Tobias
Index: gcc/testsuite/ChangeLog
===
--- gcc/testsuite/ChangeLog	(Revision 221614)
+++ gcc/testsuite/ChangeLog	(Arbeitskopie)
@@ -1,3 +1,8 @@
+2015-03-24  Tobias Burnus  
+
+	* gfortran.dg/coindexed_1.f90: Moved from
+	gfortran.dg/coarray/coindexed_3.f90; added dg-options.
+
 2015-03-23  Jakub Jelinek  
 
 	PR testsuite/65506
Index: gcc/testsuite/gfortran.dg/coarray/coindexed_3.f90
===
--- gcc/testsuite/gfortran.dg/coarray/coindexed_3.f90	(Revision 221614)
+++ gcc/testsuite/gfortran.dg/coarray/coindexed_3.f90	(Arbeitskopie)
@@ -1,71 +0,0 @@
-! { dg-do compile }
-!
-! Contributed by Reinhold Bader
-!
-
-program pmup
-  implicit none
-  type t
-integer :: b, a
-  end type t
-
-  CLASS(*), allocatable :: a(:)[:]
-  integer :: ii
-
-  !! --- ONE --- 
-  allocate(real :: a(3)[*])
-  IF (this_image() == num_images()) THEN
-SELECT TYPE (a)
-  TYPE IS (real)
-  a(:)[1] = 2.0
-END SELECT
-  END IF
-  SYNC ALL
-
-  IF (this_image() == 1) THEN
-SELECT TYPE (a)
-  TYPE IS (real)
-IF (ALL(A(:)[1] == 2.0)) THEN
-  !WRITE(*,*) 'OK'
-ELSE
-  WRITE(*,*) 'FAIL'
-  call abort()
-END IF
-  TYPE IS (t)
-ii = a(1)[1]%a
-call abort()
-  CLASS IS (t)
-ii = a(1)[1]%a
-call abort()
-END SELECT
-  END IF
-
-  !! --- TWO --- 
-  deallocate(a)
-  allocate(t :: a(3)[*])
-  IF (this_image() == num_images()) THEN
-SELECT TYPE (a)
-  TYPE IS (t) ! FIXME: When implemented, turn into "do-do run"
-  a(:)[1]%a = 4.0 ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
-END SELECT
-  END IF
-  SYNC ALL
-
-  IF (this_image() == 1) THEN
-SELECT TYPE (a)
-   TYPE IS (real)
-  ii = a(1)[1]
-  call abort()
-TYPE IS (t)   ! FIXME: When implemented, turn into "do-do run"
-  IF (ALL(A(:)[1]%a == 4.0)) THEN ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
-!WRITE(*,*) 'OK'
-  ELSE
-WRITE(*,*) 'FAIL'
-call abort()
-  END IF
-CLASS IS (t)
-  ii = a(1)[1]%a
-  call abort()
-END SELECT
-  END IF
-end program
Index: gcc/testsuite/gfortran.dg/coindexed_1.f90
===
--- gcc/testsuite/gfortran.dg/coindexed_1.f90	(Revision 0)
+++ gcc/testsuite/gfortran.dg/coindexed_1.f90	(Arbeitskopie)
@@ -0,0 +1,72 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib" }
+!
+! Contributed by Reinhold Bader
+!
+
+program pmup
+  implicit none
+  type t
+integer :: b, a
+  end type t
+
+  CLASS(*), allocatable :: a(:)[:]
+  integer :: ii
+
+  !! --- ONE --- 
+  allocate(real :: a(3)[*])
+  IF (this_image() == num_images()) THEN
+SELECT TYPE (a)
+  TYPE IS (real)
+  a(:)[1] = 2.0
+END SELECT
+  END IF
+  SYNC ALL
+
+  IF (this_image() == 1) THEN
+SELECT TYPE (a)
+  TYPE IS (real)
+IF (ALL(A(:)[1] == 2.0)) THEN
+  !WRITE(*,*) 'OK'
+ELSE
+  WRITE(*,*) 'FAIL'
+  call abort()
+END IF
+  TYPE IS (t)
+ii = a(1)[1]%a
+call abort()
+  CLASS IS (t)
+ii = a(1)[1]%a
+call abort()
+END SELECT
+  END IF
+
+  !! --- TWO --- 
+  deallocate(a)
+  allocate(t :: a(3)[*])
+  IF (this_image() == num_images()) THEN
+SELECT TYPE (a)
+  TYPE IS (t) ! FIXME: When implemented, turn into "do-do run"
+  a(:)[1]%a = 4.0 ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
+END SELECT
+  END IF
+  SYNC ALL
+
+  IF (this_image() == 1) THEN
+SELECT TYPE (a)
+   TYPE IS (real)
+  ii = a(1)[1]
+  call abort()
+TYPE IS (t)   ! FIXME: When implemented, turn into "do-do run"
+  IF (ALL(A(:)[1]%a == 4.0)) THEN ! { dg-error "Sorry, coindexed access at \\(1\\) to a scalar component with an array partref is not yet supported" }
+!WRITE(*,*) 'OK'
+  ELSE
+WRITE(*,*) 'FAIL'
+call abort()
+  END IF
+CLASS IS (t)
+  ii = a(1)[1]%a
+  call abort()
+END SELECT
+  END IF
+end program


Re: [PATCH] pr 63354 - gcc -pg -mprofile-kernel creates unused stack frames on leaf functions on ppc64le

2015-03-24 Thread Iain Sandoe
Hi Martin,

On 24 Mar 2015, at 02:50, Martin Sebor wrote:

> On 03/21/2015 01:48 PM, Iain Sandoe wrote:

> 2015-03-13  Anton Blanchard  
> 
>   PR target/63354
>   * gcc/config/rs6000/linux64.h (ARGET_KEEP_LEAF_WHEN_PROFILED): Define.
^ typo
> 
> It's fixed in version 2 of the patch posted here:
> https://gcc.gnu.org/ml/gcc-patches/2015-03/msg00793.html

Well, I think I have the new version applied, but slip-ups are possible...

>> This ^ will cause a bootstrap fail for every rs6000 target that doesn't 
>> include linux64.h.
>> (because rs6000_keep_leaf_when_profiled will be "defined but unused").
>> 
>> Since ISTM you intend this to apply to all rs6000 sub-targets, you might as 
>> well move it to rs6000.h?
> 
> The powerpc-darwin9 and powerpc64-darwin9 targets both built
> successfully with this patch.

I'm assuming that you mean a cross-compile (which is a stage1 without -werror). 
 If you look in the build output (I just repeated this on x86_64-darwin12 X 
powerpc-darwin9) you'll see:

/GCC/gcc-trunk/gcc/config/rs6000/rs6000.c:24404:1: warning: ‘bool 
rs6000_keep_leaf_when_profiled()’ defined but not used [-Wunused-function]
 rs6000_keep_leaf_when_profiled (void)
 ^

this becomes a bootstrap error at stage#2.  If you don't see that, then I have 
don't have the same patch applied as you :).

> I also tried powerpc64-freebsd,
> which succeeded as well (though I had to work around pr65535).
> What target do you suggest I try to reproduce the failure?
> (I don't mind moving the macro definition as you suggest,
> but I'd like to understand how to trigger the problem so
> that I can reproduce it and verify that I've fixed it.)

Any target that doesn't include linux64.h would be a reproducer (AIX, 
powerpc-linux-gnu).
cheers,
Iain



Re: [CHKP, PATCH] Fix instrumented indirect calls with propagated pointers

2015-03-24 Thread Jakub Jelinek
On Thu, Mar 19, 2015 at 11:29:44AM +0300, Ilya Enkovich wrote:
> +  /* We might propagate instrumented function pointer into
> + not instrumented function and vice versa.  In such a
> + case we need to either fix function declaration or
> + remove bounds from call statement.  */
> +  if (callee)
> +skip_bounds = chkp_redirect_edge (e);

I just want to say that I'm not really excited about all this compile time
cost that is added everywhere unconditionally for chkp.
I think much better would be to guard most of it with proper option check
first and only do the more expensive part if the option has been used.

In particular, the above call isn't inlined,

> +bool
> +chkp_redirect_edge (cgraph_edge *e)
> +{
> +  bool instrumented = false;
> +  tree decl = e->callee->decl;
> +
> +  if (e->callee->instrumentation_clone
> +  || chkp_function_instrumented_p (decl))
> +instrumented = true;

Calls here for non-instrumented code another function that calls
lookup_attribute (cheap if DECL_ATTRIBUTES is NULL, not really cheap
otherwise).

> +  if (instrumented
> +  && !gimple_call_with_bounds_p (e->call_stmt))
> +e->redirect_callee (cgraph_node::get_create (e->callee->orig_decl));
> +  else if (!instrumented
> +&& !chkp_gimple_call_builtin_p (e->call_stmt, BUILT_IN_CHKP_BNDCL)
> +&& !chkp_gimple_call_builtin_p (e->call_stmt, BUILT_IN_CHKP_BNDCU)
> +&& !chkp_gimple_call_builtin_p (e->call_stmt, BUILT_IN_CHKP_BNDSTX)
> +&& gimple_call_with_bounds_p (e->call_stmt))

Plus the ordering of the conditions above is bad, you first check
for 3 out of a few thousands builtin and only then call the predicate,
which should be probably done right after the !instrumented case.

So, for the very likely case of -fcheck-pointer-bounds not being used at
all, you've added at least 7-8 non-inlinable calls here.

There are dozens of similar calls inserted just about everywhere.

Jakub


Re: [PATCH 3/3] Fix dbr_schedule for -freorder-blocks-and-partition

2015-03-24 Thread Steven Bosscher
On Tue, Jan 27, 2015 at 12:52 AM, Kaz Kojima wrote:
> This patch is to fix 2 issues found in dbr_schedule when trying to
> fix PR target/64761.  The first is relax_delay_slots removes
> the jump insn in the insns like below:
>
> (jump_insn/j 74 58 59 (set (pc) (label_ref:SI 29)) ...)
> (barrier 59 74 105)
> (note 105 59 29 NOTE_INSN_SWITCH_TEXT_SECTIONS)
> (code_label 29 105 30 31 "" [5 uses])
> (insn 31 30 32 (set (reg ...
>
> i.e. relax_delay_slot tries to delete the jump insn pointing to
> the next active insn of that jump insn as a trivial jump even when
> there is a NOTE_INSN_SWITCH_TEXT_SECTIONS note between that jump
> and its next active insn.
> The second issue is that relax_delay_slots does a variant of
> follow jump optimization without checking targetm.can_follow_jump.
>
> --
> PR target/64761
> * reorg.c (switch_text_sections_between_p): New function.
> (relax_delay_slots): Call it when testing if the jump insn
> is removable.  Use targetm.can_follow_jump when testing if
> the conditional branch can follow an unconditional jump.


This patch merely papers over another issue, probably a missing
CROSSING_JUMP_P test.

Ciao!
Steven





> diff --git a/reorg.c b/reorg.c
> index 326fa53..2387910 100644
> --- a/reorg.c
> +++ b/reorg.c
> @@ -3211,6 +3211,19 @@ label_before_next_insn (rtx x, rtx scan_limit)
>return insn;
>  }
>
> +/* Return TRUE if there is a NOTE_INSN_SWITCH_TEXT_SECTIONS note in between
> +   BEG and END.  */
> +
> +static bool
> +switch_text_sections_between_p (const rtx_insn *beg, const rtx_insn *end)
> +{
> +  const rtx_insn *p;
> +  for (p = beg; p != end; p = NEXT_INSN (p))
> +if (NOTE_P (p) && NOTE_KIND (p) == NOTE_INSN_SWITCH_TEXT_SECTIONS)
> +  return true;
> +  return false;
> +}
> +
>
>  /* Once we have tried two ways to fill a delay slot, make a pass over the
> code to try to improve the results and to do such things as more jump
> @@ -3247,7 +3260,8 @@ relax_delay_slots (rtx_insn *first)
> target_label = find_end_label (target_label);
>
>   if (target_label && next_active_insn (target_label) == next
> - && ! condjump_in_parallel_p (insn))
> + && ! condjump_in_parallel_p (insn)
> + && ! (next && switch_text_sections_between_p (insn, next)))
> {
>   delete_jump (insn);
>   continue;
> @@ -3262,12 +3276,13 @@ relax_delay_slots (rtx_insn *first)
>
>   /* See if this jump conditionally branches around an unconditional
>  jump.  If so, invert this jump and point it to the target of the
> -second jump.  */
> +second jump.  Check if it's possible on the target.  */
>   if (next && simplejump_or_return_p (next)
>   && any_condjump_p (insn)
>   && target_label
>   && next_active_insn (target_label) == next_active_insn (next)
> - && no_labels_between_p (insn, next))
> + && no_labels_between_p (insn, next)
> + && targetm.can_follow_jump (insn, next))
> {
>   rtx label = JUMP_LABEL (next);
>


Re: [CHKP, PATCH] Fix instrumented indirect calls with propagated pointers

2015-03-24 Thread Ilya Enkovich
2015-03-24 11:33 GMT+03:00 Jakub Jelinek :
> On Thu, Mar 19, 2015 at 11:29:44AM +0300, Ilya Enkovich wrote:
>> +  /* We might propagate instrumented function pointer into
>> + not instrumented function and vice versa.  In such a
>> + case we need to either fix function declaration or
>> + remove bounds from call statement.  */
>> +  if (callee)
>> +skip_bounds = chkp_redirect_edge (e);
>
> I just want to say that I'm not really excited about all this compile time
> cost that is added everywhere unconditionally for chkp.
> I think much better would be to guard most of it with proper option check
> first and only do the more expensive part if the option has been used.

Agree, overhead for not instrumented code should be minimized.
Unfortunately there is no option check I can use to guard chkp codes
due to LTO. Currently it is allowed to pass -fcheck-pointer-bounds for
IL generation and don't pass it for final code generation. I suppose I
may set this (or some new) flag if see instrumented node when read
cgraph and then use it to guard chkp related codes. Would it be
acceptable?

>
> In particular, the above call isn't inlined,
>
>> +bool
>> +chkp_redirect_edge (cgraph_edge *e)
>> +{
>> +  bool instrumented = false;
>> +  tree decl = e->callee->decl;
>> +
>> +  if (e->callee->instrumentation_clone
>> +  || chkp_function_instrumented_p (decl))
>> +instrumented = true;
>
> Calls here for non-instrumented code another function that calls
> lookup_attribute (cheap if DECL_ATTRIBUTES is NULL, not really cheap
> otherwise).

Maybe replace attribute usage with a new flag in tree_decl_with_vis structure?

>
>> +  if (instrumented
>> +  && !gimple_call_with_bounds_p (e->call_stmt))
>> +e->redirect_callee (cgraph_node::get_create (e->callee->orig_decl));
>> +  else if (!instrumented
>> +&& !chkp_gimple_call_builtin_p (e->call_stmt, BUILT_IN_CHKP_BNDCL)
>> +&& !chkp_gimple_call_builtin_p (e->call_stmt, BUILT_IN_CHKP_BNDCU)
>> +&& !chkp_gimple_call_builtin_p (e->call_stmt, BUILT_IN_CHKP_BNDSTX)
>> +&& gimple_call_with_bounds_p (e->call_stmt))
>
> Plus the ordering of the conditions above is bad, you first check
> for 3 out of a few thousands builtin and only then call the predicate,
> which should be probably done right after the !instrumented case.

Will fix it.

>
> So, for the very likely case of -fcheck-pointer-bounds not being used at
> all, you've added at least 7-8 non-inlinable calls here.
>
> There are dozens of similar calls inserted just about everywhere.

The most popular guard call should be chkp_function_instrumented_p.
Replacing attribute with a flag should help.

Thanks for review!

Ilya

>
> Jakub


[PATCH] Fix PR65517

2015-03-24 Thread Richard Biener

The following fixes PR65517 - we need to mark loops for fixup if we
remove a path inside a loop.

Bootstrapped and tested on x86_64-unknown-linux-gnu, applied to trunk.

Richard.

2015-03-23  Richard Biener  

PR middle-end/65517
* tree-cfg.c (remove_edge_and_dominated_blocks): Mark loops
for fixup if necessary.

* gcc.dg/torture/pr65517.c: New testcase.

Index: gcc/testsuite/gcc.dg/torture/pr65517.c
===
--- gcc/testsuite/gcc.dg/torture/pr65517.c  (revision 0)
+++ gcc/testsuite/gcc.dg/torture/pr65517.c  (working copy)
@@ -0,0 +1,17 @@
+/* { dg-do compile } */
+
+typedef void (*argmatch_exit_fn)();
+int a;
+void __argmatch_die () { __builtin_exit (0); }
+
+int
+main ()
+{
+  while (1)
+{
+  argmatch_exit_fn b = __argmatch_die;
+  if (a)
+   b ();
+}
+  return 0;
+}
Index: gcc/tree-cfg.c
===
--- gcc/tree-cfg.c  (revision 221591)
+++ gcc/tree-cfg.c  (working copy)
@@ -7824,6 +7824,13 @@ remove_edge_and_dominated_blocks (edge e
   basic_block bb, dbb;
   bitmap_iterator bi;
 
+  /* If we are removing a path inside a non-root loop that may change
+ loop ownership of blocks or remove loops.  Mark loops for fixup.  */
+  if (current_loops
+  && loop_outer (e->src->loop_father) != NULL
+  && e->src->loop_father == e->dest->loop_father)
+loops_state_set (LOOPS_NEED_FIXUP);
+
   if (!dom_info_available_p (CDI_DOMINATORS))
 {
   remove_edge (e);


Re: [Patch 1/2, Fortran, pr60322] [OOP] Incorrect bounds on polymorphic dummy array

2015-03-24 Thread Paul Richard Thomas
Dear Andre,

Dominique pointed out to me that the 'loc' patch causes a ICE in the
testsuite. It seems that 'loc' should provide the address of the class
container in some places and the address of the data in others. I will
put my thinking cap on tonight :-)

Cheers

Paul

On 23 March 2015 at 13:43, Andre Vehreschild  wrote:
> Hi Mikael,
>
> thanks for looking at the patch. Please note, that Paul has sent an addendum 
> to
> the patches for 60322, which I deliberately have attached.
>
>>  26/02/2015 18:17, Andre Vehreschild a écrit :
>> > This first patch is only preparatory and does not change any of the
>> > semantics of gfortran at all.
>> Sure?
>
> With the counterexample you found below, this of course is a wrong statement.
>
>> > diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
>> > index ab6f7a5..d28cf77 100644
>> > --- a/gcc/fortran/expr.c
>> > +++ b/gcc/fortran/expr.c
>> > @@ -4059,10 +4060,10 @@ gfc_lval_expr_from_sym (gfc_symbol *sym)
>> >lval->symtree = gfc_find_symtree (sym->ns->sym_root, sym->name);
>> >
>> >/* It will always be a full array.  */
>> > -  lval->rank = sym->as ? sym->as->rank : 0;
>> > +  as = sym->as;
>> > +  lval->rank = as ? as->rank : 0;
>> >if (lval->rank)
>> > -gfc_add_full_array_ref (lval, sym->ts.type == BT_CLASS ?
>> > -   CLASS_DATA (sym)->as : sym->as);
>> > +gfc_add_full_array_ref (lval, as);
>>
>> This is a change of semantics.  Or do you know that sym->ts.type !=
>> BT_CLASS?
>
> You are completely right. I have made a mistake here. I have to tell the 
> truth,
> I never ran a regtest with only part 1 of the patches applied. The second part
> of the patch will correct this, by setting the variable as depending on 
> whether
> type == BT_CLASS or not. Sorry for the mistake.
>
>> > diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
>> > index 3664824..e571a17 100644
>> > --- a/gcc/fortran/trans-decl.c
>> > +++ b/gcc/fortran/trans-decl.c
>> > @@ -1013,16 +1017,24 @@ gfc_build_dummy_array_decl (gfc_symbol * sym, tree
>> > dummy) tree decl;
>> >tree type;
>> >gfc_array_spec *as;
>> > +  symbol_attribute *array_attr;
>> >char *name;
>> >gfc_packed packed;
>> >int n;
>> >bool known_size;
>> >
>> > -  if (sym->attr.pointer || sym->attr.allocatable
>> > -  || (sym->as && sym->as->type == AS_ASSUMED_RANK))
>> > +  /* Use the array as and attr.  */
>> > +  as = sym->as;
>> > +  array_attr = &sym->attr;
>> > +
>> > +  /* The pointer attribute is always set on a _data component, therefore
>> > check
>> > + the sym's attribute only.  */
>> > +  if (sym->attr.pointer || array_attr->allocatable
>> > +  || (as && as->type == AS_ASSUMED_RANK))
>> >  return dummy;
>> >
>> Any reason to sometimes use array_attr, sometimes not, like here?
>> By the way, the comment is misleading: for classes, there is the
>> class_pointer attribute (and it is a pain, I know).
>
> Yes, and a good one. Array_attr is sometimes sym->attr and sometimes
> CLASS_DATA(sym)->attr aka sym->ts.u.derived->components->attr. In the later
> case .pointer is always set to 1 in the _data component's attr. I.e., the 
> above
> if, would always yield true for a class_array, which is not intended, but 
> rather
> destructive. I know about the class_pointer attribute, but I figured, that it
> is not relevant here. Any idea how to formulate the comment better, to reflect
> what I just explained?
>
> Regards,
> Andre
> --
> Andre Vehreschild * Email: vehre ad gmx dot de
>
>
> -- Forwarded message --
> From: Paul Richard Thomas 
> To: Andre Vehreschild , Dominique Dhumieres 
> Cc:
> Date: Sun, 22 Mar 2015 21:20:20 +0100
> Subject: Bug in intrinsic LOC for scalar class objects
> Dear Andre and Dominique,
>
> I have found that LOC is returning the address of the class container
> rather than the _data component for class scalars. See the source
> below, which you will recognise! A fix is attached.
>
> Note that the scalar allocate fails with MOLD= and so I substituted SOURCE=.
>
> Cheers
>
> Paul
>
> class(*), allocatable :: a(:), e ! Change 'e' to an array and
> second memcpy works correctly
>  ! Problem is with loc(e), which
> returns the address of the
>  ! class container.
> allocate (e, source = 99.0)
> allocate (a(2), source = [1.0, 2.0])
> call add_element_poly (a,e)
> select type (a)
>   type is (real)
> print *, a
> end select
>
> contains
>
> subroutine add_element_poly(a,e)
>   use iso_c_binding
>   class(*),allocatable,intent(inout),target :: a(:)
>   class(*),intent(in),target :: e
>   class(*),allocatable,target :: tmp(:)
>   type(c_ptr) :: dummy
>
>   interface
> function memcpy(dest,src,n) bind(C,name="memcpy") result(res)
>   import
>   type(c_ptr) :: res
>   integer(c_intptr_t),value :: dest
>   integer(c_intptr_t),v

Re: [commited, Fortran, pr64787 a.o., v1] Invalid code on sourced allocation of class(*) character string

2015-03-24 Thread Andre Vehreschild
Hi Paul, hi all,

Paul, thanks for the review. I have commited the patch for 64787 as r221621.

Regards,
Andre

gcc/fortran/ChangeLog

2015-03-24  Andre Vehreschild  

PR fortran/64787
PR fortran/57456
PR fortran/63230
* class.c (gfc_add_component_ref):  Free no longer needed
ref-chains to prevent memory loss.
(find_intrinsic_vtab): For deferred length char arrays or
unlimited polymorphic objects, store the size in bytes of one
character in the size component of the vtab.
* gfortran.h: Added gfc_add_len_component () define.
* trans-array.c (gfc_trans_create_temp_array): Switched to new
function name for getting a class' vtab's field.
(build_class_array_ref): Likewise.
(gfc_array_init_size): Using the size information from allocate
more consequently now, i.e., the typespec of the entity to
allocate is no longer needed.  This is to address the last open
comment in PR fortran/57456.
(gfc_array_allocate): Likewise.
(structure_alloc_comps): gfc_copy_class_to_class () needs to
know whether the class is unlimited polymorphic.
* trans-array.h: Changed interface of gfc_array_allocate () to
reflect the no longer needed typespec.
* trans-expr.c (gfc_find_and_cut_at_last_class_ref): New.
(gfc_reset_len): New.
(gfc_get_class_array_ref): Switch to new function name for
getting a class' vtab's field.
(gfc_copy_class_to_class):  Added flag to know whether the class
to copy is unlimited polymorphic.  Adding _len dependent code
then, which calls ->vptr->copy () with four arguments adding
the length information ->vptr->copy(from, to, from_len, to_cap).
(gfc_conv_procedure_call): Switch to new function name for
getting a class' vtab's field.
(alloc_scalar_allocatable_for_assignment): Use the string_length
as computed by gfc_conv_expr and not the statically backend_decl
which may be incorrect when ref-ing.
(gfc_trans_assignment_1): Use the string_length variable and
not the rse.string_length.  The former has been computed more
generally.
* trans-intrinsic.c (gfc_conv_intrinsic_sizeof): Switch to new
function name for getting a class' vtab's field.
(gfc_conv_intrinsic_storage_size): Likewise.
(gfc_conv_intrinsic_transfer): Likewise.
* trans-stmt.c (gfc_trans_allocate): Restructured to evaluate
source=expr3 only once before the loop over the objects to
allocate, when the objects are not arrays. Doing correct _len
initialization and calling of vptr->copy () fixing PR 64787.
(gfc_trans_deallocate): Reseting _len to 0, preventing future
errors.
* trans.c (gfc_build_array_ref): Switch to new function name
for getting a class' vtab's field.
(gfc_add_comp_finalizer_call): Likewise.
* trans.h: Define the prototypes for the gfc_class_vtab_*_get ()
and gfc_vptr_*_get () functions.
Added gfc_find_and_cut_at_last_class_ref () and
gfc_reset_len () routine prototype.  Added flag to
gfc_copy_class_to_class () prototype to signal an unlimited
polymorphic entity to copy.



gcc/testsuite/ChangeLog

2015-03-24  Andre Vehreschild  

* gfortran.dg/allocate_alloc_opt_13.f90: Added tests for
source= and mold= expressions functionality.
* gfortran.dg/allocate_class_4.f90: New test.
* gfortran.dg/unlimited_polymorphic_20.f90: Added test whether
copying an unlimited polymorhpic object containing a char array
to another unlimited polymorphic object respects the _len
component.
* gfortran.dg/unlimited_polymorphic_22.f90: Extended to check
whether deferred length char array allocate works, unlimited
polymorphic object allocation from a string works and if
allocating an array of deferred length strings works.
* gfortran.dg/unlimited_polymorphic_24.f03: New test.
-- 
Andre Vehreschild * Email: vehre ad gmx dot de 
Index: gcc/fortran/ChangeLog
===
--- gcc/fortran/ChangeLog	(Revision 221620)
+++ gcc/fortran/ChangeLog	(Arbeitskopie)
@@ -1,3 +1,62 @@
+2015-03-24  Andre Vehreschild  
+
+	PR fortran/64787
+	PR fortran/57456
+	PR fortran/63230
+	* class.c (gfc_add_component_ref):  Free no longer needed
+	ref-chains to prevent memory loss.
+	(find_intrinsic_vtab): For deferred length char arrays or
+	unlimited polymorphic objects, store the size in bytes of one
+	character in the size component of the vtab.
+	* gfortran.h: Added gfc_add_len_component () define.
+	* trans-array.c (gfc_trans_create_temp_array): Switched to new
+	function name for getting a class' vtab's field.
+	(build_class_array_ref): Likewise.
+	(gfc_array_init_size): Using the size informatio

[committed] Fix SLP vectorization (PR tree-optimization/65533)

2015-03-24 Thread Jakub Jelinek
Hi!

Even if vect_build_slp_tree on child fails, it might have pushed some
nodes to SLP_TREE_CHILDREN (child) vector before returning false.
If we retry, we need to start with no grandchildren of course.

Bootstrapped/regtested on x86_64-linux and i686-linux, acked by Richard in
the PR, committed to trunk so far.

2015-03-24  Jakub Jelinek  

PR tree-optimization/65533
* tree-vect-slp.c (vect_build_slp_tree): Before re-trying
with swapped operands, call vect_free_slp_tree on
SLP_TREE_CHILDREN of child and truncate the SLP_TREE_CHILDREN
vector.

* gcc.dg/pr65533.c: New test.

--- gcc/tree-vect-slp.c.jj  2015-03-23 16:15:30.0 +0100
+++ gcc/tree-vect-slp.c 2015-03-24 08:54:51.524143880 +0100
@@ -1035,13 +1035,20 @@ vect_build_slp_tree (loop_vec_info loop_
 behavior.  */
  && *npermutes < 4)
{
+ unsigned int j;
+ slp_tree grandchild;
+
  /* Roll back.  */
  *max_nunits = old_max_nunits;
  loads->truncate (old_nloads);
+ FOR_EACH_VEC_ELT (SLP_TREE_CHILDREN (child), j, grandchild)
+   vect_free_slp_tree (grandchild);
+ SLP_TREE_CHILDREN (child).truncate (0);
+
  /* Swap mismatched definition stmts.  */
  dump_printf_loc (MSG_NOTE, vect_location,
   "Re-trying with swapped operands of stmts ");
- for (unsigned j = 0; j < group_size; ++j)
+ for (j = 0; j < group_size; ++j)
if (!matches[j])
  {
gimple tem = oprnds_info[0]->def_stmts[j];
--- gcc/testsuite/gcc.dg/pr65533.c.jj   2015-03-24 08:52:24.437577841 +0100
+++ gcc/testsuite/gcc.dg/pr65533.c  2015-03-24 08:51:55.0 +0100
@@ -0,0 +1,25 @@
+/* PR tree-optimization/65533 */
+/* { dg-do compile } */
+/* { dg-options "-Ofast -w" } */
+
+struct A { int a[2]; };
+struct B { double b[2]; };
+struct C { double c[4][1]; };
+
+static inline void
+bar (struct B *x, double y, double z)
+{
+  x->b[0] = y;
+  x->b[1] = z;
+}
+
+void baz (struct B *);
+
+void
+foo (struct C *x, struct A *y)
+{
+  struct B d;
+  bar (&d, x->c[1][0] * y->a[0] + x->c[0][1] * y->a[1] + x->c[0][0] * 
x->c[0][1],
+   x->c[0][0] * y->a[0] + x->c[0][1] * y->a[1] + x->c[0][1] * y->a[0] + 
x->c[0][0]);
+  baz (&d);
+}

Jakub


Re: [PATCH] pr 63354 - gcc -pg -mprofile-kernel creates unused stack frames on leaf functions on ppc64le

2015-03-24 Thread Segher Boessenkool
On Mon, Mar 23, 2015 at 08:50:27PM -0600, Martin Sebor wrote:
>   PR target/63354
>   * gcc/config/rs6000/linux64.h (ARGET_KEEP_LEAF_WHEN_PROFILED): 
>   Define.
> >>>^ typo
> 
> It's fixed in version 2 of the patch posted here:
> https://gcc.gnu.org/ml/gcc-patches/2015-03/msg00793.html

Iain means the macro should be defined in rs6000.h, not linux64.h.

> >This ^ will cause a bootstrap fail for every rs6000 target that doesn't 
> >include linux64.h.
> >(because rs6000_keep_leaf_when_profiled will be "defined but unused").
> >
> >Since ISTM you intend this to apply to all rs6000 sub-targets, you might 
> >as well move it to rs6000.h?


Segher


Re: [committed, Fortran, pr55901, v1] [OOP] type is (character(len=*)) misinterpreted as array and Re: [Patch, Fortran, v1] Cosmetics and code simplify

2015-03-24 Thread Andre Vehreschild
Dear Paul, Dear Mikael, hi all,

thanks for reviewing. I have just committed the patches for:

[Patch, Fortran, pr55901, v1] [OOP] type is (character(len=*)) misinterpreted
as array, and
[Patch, Fortran, v1] Cosmetics and code simplify

as r221627.

Regards,
Andre

2015-03-24  Andre Vehreschild  

PR fortran/55901
* trans-expr.c (gfc_conv_structure): Fixed indendation.
Using integer_zero_node now instead of explicitly
constructing a integer constant zero node.
(gfc_conv_derived_to_class): Add handling of _len component,
i.e., when the rhs has a string_length then assign that to
class' _len, else assign 0.
(gfc_conv_intrinsic_to_class): Likewise.

On Mon, 23 Mar 2015 12:28:03 +0100
Paul Richard Thomas  wrote:

> Dear Andre,
> 
> Yes, that's right.  The first three (vtab rework 1/2 and pr64787) are
> combined and reformatted in the .diff file that I sent you. Please use
> that and then apply the pr55901 patch. This is what I am okaying.
> 
> Cheers
> 
> Paul
> 
> On 23 March 2015 at 10:45, Andre Vehreschild  wrote:
> > Hi Paul,
> >
> > thanks for the reviews. Let me ask one questions before I do something
> > wrong. You have reviewed and approved (with changes) the patches:
> >
> > - vtab_access_rework1_v1.patch
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00074.html
> > - vtab_access_rework2_v1.patch
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00075.html
> > - pr64787_v2.patch
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00085.html
> > and
> > - pr55901_v1.patch
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00086.html
> > , right?
> >
> > I am asking so explicitly, because there are four more patches from me in
> > the wild, that await review (not necessarily from you, Paul), namely:
> >
> > - pr60322_base_1.patch
> > https://gcc.gnu.org/ml/fortran/2015-02/msg00105.html
> > - pr60322_3.patch
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00032.html
> > - crashfix2_v1.patch (small patch, ~100 loc))
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00063.html
> > and
> > - cosm_simp.patch (tiny patch, ~20 loc)
> > https://gcc.gnu.org/ml/fortran/2015-03/msg00088.html
> >
> > Please don't get me wrong on this. I just want to prevent misunderstandings
> > here. The latter four patches are not yet approved, right?
> >
> > I will now apply the 4.9-trunk patch and wait for your answer before
> > applying the above four on vtab_rework pr64787 and pr55901.
> >
> > Regards,
> > Andre
> >
> >
> >
> > On Mon, 23 Mar 2015 08:33:51 +0100
> > Paul Richard Thomas  wrote:
> >
> >> Dear Andre,
> >>
> >> I am persuaded by the arguments of Jerry and Dominique that this is
> >> good for trunk. Please commit as early as possible in order that any
> >> regressions can be caught, if possible, before release.
> >>
> >> Thanks
> >>
> >> Paul
> >>
> >> On 21 March 2015 at 15:11, Paul Richard Thomas
> >>  wrote:
> >> > Dear Andre,
> >> >
> >> > I have applied the three preliminary patches but have not yet applied
> >> > the attached one for PR55901. As advertised the composite patch
> >> > bootstraps and regtests on FC21,x86_64.
> >> >
> >> > I went through gfc_trans_allocate and cleaned up the formatting and
> >> > some of the text in the comments. You did a heroic job to tidy up this
> >> > function and so I thought that I should do my bit - one of the
> >> > feature, previously, was that the line length often went well in
> >> > excess of the gcc style guide limit of 72 and this tended to make it
> >> > somewhat unreadable. I have not been rigorous about this, especially
> >> > when readability would be impaired thereby, but it does look a lot
> >> > better now. The composite diff is attached.
> >> >
> >> > Not only does the Metcalf example run correctly but also the PGI
> >> > Insider linked list example.  I have attached a version of this
> >> > modified to function as a gfortran.dg testcase. With the attributions
> >> > in there, I do not think that there are any copyright issues. The
> >> > article itself has no copyright notice.
> >> >
> >> > I would very much like to say that this is OK for trunk but we are
> >> > hard up against the end of stage 4 and so it should really wait for
> >> > backporting to 5.2.
> >> >
> >> > Thanks for the patches
> >> >
> >> > Paul
> >> >
> >> > On 19 March 2015 at 16:13, Andre Vehreschild  wrote:
> >> >> Hi all,
> >> >>
> >> >> please find attached the parts missing to stop valgrind's complaining
> >> >> about the use of uninitialized memory. The issue was, that when
> >> >> constructing a temporary class-object to call a routine with unlimited
> >> >> polymorphic arguments, the _len component was never set. This is fixed
> >> >> by this patch now.
> >> >>
> >> >> Note, the patch is based on all these preliminary patches:
> >> >>
> >> >> https://gcc.gnu.org/ml/fortran/2015-03/msg00074.html
> >> >> https://gcc.gnu.org/ml/fortran/2015-03/msg00075.ht

[Ada] New attribute typ'Deref (address-expr)

2015-03-24 Thread Arnaud Charlet
This attribute is equivalent to (atyp!(address-expr)).all where atyp is a
general-access-to-typ type. Right now, only the front end changes are done.
The back end needs to adapt to this change too.

The following is a test which should compile and run silently

 1. with System; use System;
 2. procedure Deref_Test is
 3.X : Integer := 4;
 4.Y : Address := X'Address;
 5. begin
 6.if Integer'Deref (Y) /= 4 then
 7.   raise Program_Error;
 8.end if;
 9. end Deref_Test;

For now it will blow up with a GCC error in the back end, which does
not know about this attribute yet.

Tested on x86_64-pc-linux-gnu, committed on trunk

2015-03-24  Robert Dewar  

* exp_attr.adb: Add entry for typ'Deref.
* sem_attr.adb (Deref): New GNAT attribute.
* sem_attr.ads: Add entry for new GNAT attribute Deref.
* snames.ads-tmpl: Add entries for new attribute Deref.

Index: exp_attr.adb
===
--- exp_attr.adb(revision 221624)
+++ exp_attr.adb(working copy)
@@ -7103,6 +7103,7 @@
   when Attribute_Bit_Order|
Attribute_Code_Address |
Attribute_Definite |
+   Attribute_Deref|
Attribute_Null_Parameter   |
Attribute_Passed_By_Reference  |
Attribute_Pool_Address |
Index: sem_attr.adb
===
--- sem_attr.adb(revision 221624)
+++ sem_attr.adb(working copy)
@@ -3540,6 +3540,16 @@
  Check_Floating_Point_Type_0;
  Set_Etype (N, Standard_Boolean);
 
+  ---
+  -- Deref --
+  ---
+
+  when Attribute_Deref =>
+ Check_Type;
+ Check_E1;
+ Resolve (E1, RTE (RE_Address));
+ Set_Etype (N, P_Type);
+
   -
   -- Descriptor_Size --
   -
@@ -9642,6 +9652,7 @@
Attribute_Count|
Attribute_Default_Bit_Order|
Attribute_Default_Scalar_Storage_Order |
+   Attribute_Deref|
Attribute_Elaborated   |
Attribute_Elab_Body|
Attribute_Elab_Spec|
Index: sem_attr.ads
===
--- sem_attr.ads(revision 221624)
+++ sem_attr.ads(working copy)
@@ -6,7 +6,7 @@
 --  --
 -- S p e c  --
 --  --
---  Copyright (C) 1992-2014, Free Software Foundation, Inc. --
+--  Copyright (C) 1992-2015, Free Software Foundation, Inc. --
 --  --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
@@ -42,9 +42,9 @@
-- Implementation Dependent Attributes --
-
 
-   --  This section describes the implementation dependent attributes
-   --  provided in GNAT, as well as constructing an array of flags
-   --  indicating which attributes these are.
+   --  This section describes the implementation dependent attributes provided
+   --  in GNAT, as well as constructing an array of flags indicating which
+   --  attributes these are.
 
Attribute_Impl_Def : Attribute_Class_Array := Attribute_Class_Array'(
 
@@ -152,6 +152,17 @@
   --  Default_Scalar_Storage_Order, or equal to Default_Bit_Order if
   --  unspecified) as a System.Bit_Order value. This is a static attribute.
 
+  ---
+  -- Deref --
+  ---
+
+  Attribute_Deref => True,
+  --  typ'Deref (expr) is valid only if expr is of type System'Address.
+  --  The result is an object of type typ that is obtained by treating the
+  --  address as an access-to-typ value that points to the result. It is
+  --  basically equivalent to (atyp!expr).all where atyp is an access type
+  --  for the type.
+
   ---
   -- Elab_Body --
   ---
Index: snames.ads-tmpl
===
--- snames.ads-tmpl (revision 221624)
+++ snames.ads-tmpl (working copy)
@@ -845,6 +845,7 @@
Name_Definite   : constant Name_Id := N + $;
Name_Delta  : constant Name_Id := N + $;
Name_Denorm : constant Name_Id := N + $;
+   Name_Deref  : constant Name_Id := N 

Re: [PATCH 3/3] Fix dbr_schedule for -freorder-blocks-and-partition

2015-03-24 Thread Kaz Kojima
Steven Bosscher  wrote:
> This patch merely papers over another issue, probably a missing
> CROSSING_JUMP_P test.

Perhaps.  Surely it has looked the current DBR is not so well for
crossing jumps and my fix might be a bit ad-hoc.
The first part of the patch could be rewritten with checking if one
of the following jumps is crossing, though I thought that checking
NOTE_INSN_SWITCH_TEXT_SECTIONS is straight forward to see the jump
is trivial or not.

Regards,
kaz


Re: [PATCH] Make wider use of "v" constraint in i386.md

2015-03-24 Thread Kirill Yukhin
Hello,
On 23 Mar 19:02, Ilya Tocar wrote:
> Hi,
> 
> I've renamed EXT_SSE_REG_P into EXT_REX_SSE_REG_P for consistency.
> Ok for stage1?
Patch is OK for stage1.

--
Thanks, K


> On 19 Mar 12:24, Ilya Tocar wrote:
> > Hi,
> > 
> > There were some discussion about "x" constraints being too conservative
> > for some patterns in i386.md.
> > Patch below fixes it. This is probably stage1 material.
> > 
> > ChangeLog:
> > 
> > gcc/
> > 
> 2015-03-23  Ilya Tocar  
> 
>   * config/i386/i386.h (EXT_REX_SSE_REG_P): New.
>   * config/i386/i386.md (*cmpi_mixed): Use "v"
>   constraint.
>   (*cmpi_sse): Ditto.
>   (*movxi_internal_avx512f): Ditto.
>   (define_split): Check for xmm16+, when splitting scalar float_extend.
>   (*extendsfdf2_mixed): Use "v" constraint.
>   (*extendsfdf2_sse): Ditto.
>   (define_split): Check for xmm16+, when splitting scalar float_truncate.
>   (*truncdfsf_fast_sse): Use "v" constraint.
>   (fix_trunc_sse): Ditto.
>   (*float2_sse): Ditto.
>   (define_peephole2): Check for xmm16+, when converting scalar
>   float_truncate.
>   (define_peephole2): Check for xmm16+, when converting scalar
>   float_extend.
>   (*fop__comm_mixed): Use "v" constraint.
>   (*fop__comm_sse): Ditto.
>   (*fop__1_mixed): Ditto.
>   (*sqrt2_sse): Ditto.
>   (*ieee_s3): Ditto.
> 
> 
> ---
>  gcc/config/i386/i386.h  |  2 ++
>  gcc/config/i386/i386.md | 82 
> +++--
>  2 files changed, 47 insertions(+), 37 deletions(-)
> 
> diff --git a/gcc/config/i386/i386.h b/gcc/config/i386/i386.h
> index 1e755d3..70a471b 100644
> --- a/gcc/config/i386/i386.h
> +++ b/gcc/config/i386/i386.h
> @@ -1477,6 +1477,8 @@ enum reg_class
>  #define REX_SSE_REGNO_P(N) \
>IN_RANGE ((N), FIRST_REX_SSE_REG, LAST_REX_SSE_REG)
>  
> +#define EXT_REX_SSE_REG_P(X) (REG_P (X) && EXT_REX_SSE_REGNO_P (REGNO (X)))
> +
>  #define EXT_REX_SSE_REGNO_P(N) \
>IN_RANGE ((N), FIRST_EXT_REX_SSE_REG, LAST_EXT_REX_SSE_REG)
>  
> diff --git a/gcc/config/i386/i386.md b/gcc/config/i386/i386.md
> index 1129b93..dc1cd20 100644
> --- a/gcc/config/i386/i386.md
> +++ b/gcc/config/i386/i386.md
> @@ -1639,8 +1639,8 @@
>  (define_insn "*cmpi_mixed"
>[(set (reg:FPCMP FLAGS_REG)
>   (compare:FPCMP
> -   (match_operand:MODEF 0 "register_operand" "f,x")
> -   (match_operand:MODEF 1 "nonimmediate_operand" "f,xm")))]
> +   (match_operand:MODEF 0 "register_operand" "f,v")
> +   (match_operand:MODEF 1 "nonimmediate_operand" "f,vm")))]
>"TARGET_MIX_SSE_I387
> && SSE_FLOAT_MODE_P (mode)"
>"* return output_fp_compare (insn, operands, true,
> @@ -1666,8 +1666,8 @@
>  (define_insn "*cmpi_sse"
>[(set (reg:FPCMP FLAGS_REG)
>   (compare:FPCMP
> -   (match_operand:MODEF 0 "register_operand" "x")
> -   (match_operand:MODEF 1 "nonimmediate_operand" "xm")))]
> +   (match_operand:MODEF 0 "register_operand" "v")
> +   (match_operand:MODEF 1 "nonimmediate_operand" "vm")))]
>"TARGET_SSE_MATH
> && SSE_FLOAT_MODE_P (mode)"
>"* return output_fp_compare (insn, operands, true,
> @@ -1959,8 +1959,8 @@
> (set_attr "length_immediate" "1")])
>  
>  (define_insn "*movxi_internal_avx512f"
> -  [(set (match_operand:XI 0 "nonimmediate_operand" "=x,x ,m")
> - (match_operand:XI 1 "vector_move_operand"  "C ,xm,x"))]
> +  [(set (match_operand:XI 0 "nonimmediate_operand" "=v,v ,m")
> + (match_operand:XI 1 "vector_move_operand"  "C ,vm,v"))]
>"TARGET_AVX512F && !(MEM_P (operands[0]) && MEM_P (operands[1]))"
>  {
>switch (which_alternative)
> @@ -4003,7 +4003,9 @@
> (match_operand:SF 1 "nonimmediate_operand")))]
>"TARGET_USE_VECTOR_FP_CONVERTS
> && optimize_insn_for_speed_p ()
> -   && reload_completed && SSE_REG_P (operands[0])"
> +   && reload_completed && SSE_REG_P (operands[0])
> +   && (!EXT_REX_SSE_REG_P (operands[0])
> +   || TARGET_AVX512VL)"
> [(set (match_dup 2)
>(float_extend:V2DF
>  (vec_select:V2SF
> @@ -4048,9 +4050,9 @@
>"operands[2] = gen_rtx_REG (SFmode, REGNO (operands[0]));")
>  
>  (define_insn "*extendsfdf2_mixed"
> -  [(set (match_operand:DF 0 "nonimmediate_operand" "=f,m,x")
> +  [(set (match_operand:DF 0 "nonimmediate_operand" "=f,m,v")
>  (float_extend:DF
> -   (match_operand:SF 1 "nonimmediate_operand" "fm,f,xm")))]
> +   (match_operand:SF 1 "nonimmediate_operand" "fm,f,vm")))]
>"TARGET_SSE2 && TARGET_MIX_SSE_I387"
>  {
>switch (which_alternative)
> @@ -4071,8 +4073,8 @@
> (set_attr "mode" "SF,XF,DF")])
>  
>  (define_insn "*extendsfdf2_sse"
> -  [(set (match_operand:DF 0 "nonimmediate_operand" "=x")
> -(float_extend:DF (match_operand:SF 1 "nonimmediate_operand" "xm")))]
> +  [(set (match_operand:DF 0 "nonimmediate_operand" "=v")
> +(float_extend:DF (match_operand:SF 1 "nonimmediate_operand" "vm")))]
>"TARGET_SSE2 && TARGET_SSE_MATH"
>"%vcvtss2sd\t{%1, %d0|%d0, %1}"
>[(

[PATCH] Fix PR65538

2015-03-24 Thread Martin Liška

Hi.

In following patch, I've added missing delete call for all item summaries that 
are
allocated within a function_summary container in case the container does not use
GGC memory allocation.

Can boostrap on ppc64le and no regression is seen on x86_64-linux-pc.

Ready for trunk?
Thanks,
Martin
>From c9912b88e8a381e6be7dc1e4be4f7b8859d72e2f Mon Sep 17 00:00:00 2001
From: mliska 
Date: Tue, 24 Mar 2015 13:58:50 +0100
Subject: [PATCH] Fix PR65538.

gcc/ChangeLog:

2015-03-24  Martin Liska  

	PR tree-optimization/65538
	* symbol-summary.h (function_summary::~function_summary):
	Relese memory for allocated summaries in case non-GGC template
	instance.
---
 gcc/symbol-summary.h | 6 ++
 1 file changed, 6 insertions(+)

diff --git a/gcc/symbol-summary.h b/gcc/symbol-summary.h
index 8d7e42c..35615ba 100644
--- a/gcc/symbol-summary.h
+++ b/gcc/symbol-summary.h
@@ -81,6 +81,12 @@ public:
 m_symtab_insertion_hook = NULL;
 m_symtab_removal_hook = NULL;
 m_symtab_duplication_hook = NULL;
+
+/* Release all summaries in case we use non-GGC memory.  */
+typedef typename hash_map ::iterator map_iterator;
+if (!m_ggc)
+  for (map_iterator it = m_map.begin (); it != m_map.end (); ++it)
+	delete (*it).second;
   }
 
   /* Traverses all summarys with a function F called with
-- 
2.1.4



Re: [CHKP, PATCH] Fix instrumented indirect calls with propagated pointers

2015-03-24 Thread Jakub Jelinek
On Tue, Mar 24, 2015 at 12:22:27PM +0300, Ilya Enkovich wrote:
> 2015-03-24 11:33 GMT+03:00 Jakub Jelinek :
> > On Thu, Mar 19, 2015 at 11:29:44AM +0300, Ilya Enkovich wrote:
> >> +  /* We might propagate instrumented function pointer into
> >> + not instrumented function and vice versa.  In such a
> >> + case we need to either fix function declaration or
> >> + remove bounds from call statement.  */
> >> +  if (callee)
> >> +skip_bounds = chkp_redirect_edge (e);
> >
> > I just want to say that I'm not really excited about all this compile time
> > cost that is added everywhere unconditionally for chkp.
> > I think much better would be to guard most of it with proper option check
> > first and only do the more expensive part if the option has been used.
> 
> Agree, overhead for not instrumented code should be minimized.
> Unfortunately there is no option check I can use to guard chkp codes
> due to LTO. Currently it is allowed to pass -fcheck-pointer-bounds for
> IL generation and don't pass it for final code generation. I suppose I
> may set this (or some new) flag if see instrumented node when read
> cgraph and then use it to guard chkp related codes. Would it be
> acceptable?

The question is what you want to do in the LTO case for the different cases,
in particular a TU compiled with -fcheck-pointer-bounds and LTO link without
that, or TU compiled without -fcheck-pointer-bounds and LTO link with it.
It could be handled as LTO incompatible option, where lto1 would error out
if you try to mix -fcheck-pointer-bounds with -fno-check-pointer-bounds
code, or e.g. similar to var-tracking, you could consider adjusting the IL
upon LTO reading if if some TU has been built with -fcheck-pointer-bounds
and the LTO link is -fno-check-pointer-bounds.  Dunno what will happen
with -fno-check-pointer-bounds TUs LTO linked with -fcheck-pointer-bounds.
Or another possibility is to or in -fcheck-pointer-bounds from all TUs.

> Maybe replace attribute usage with a new flag in tree_decl_with_vis structure?

Depends, might be better to stick it into cgraph_node instead, depends on
whether you are querying it already early in the FEs or just during GIMPLE
when the cgraph node should be created too.

Jakub


[PATCH] Fix PR65519

2015-03-24 Thread Richard Biener

The following fixes PR65519 - we were using gimple_build from
gimple_simplify which isn't a good idea as that doesn't properly
fail when materializing stmts with operands we don't want
(SSA_NAME_OCCURS_IN_ABNORMAL_PHI).

Bootstrapped on x86_64-unknown-linux-gnu, testing in progress.

Richard.

2015-03-24  Richard Biener  

PR middle-end/65519
* genmatch.c (expr::gen_transform): Re-write to avoid
using gimple_build.

* gnat.dg/specs/opt2.ads: New testcase.

Index: gcc/genmatch.c
===
--- gcc/genmatch.c  (revision 221624)
+++ gcc/genmatch.c  (working copy)
@@ -1742,22 +1742,18 @@ expr::gen_transform (FILE *f, const char
 
   if (gimple)
 {
-  /* ???  Have another helper that is like gimple_build but may
-fail if seq == NULL.  */
-  fprintf (f, "  if (!seq)\n"
-  "{\n"
-  "  res = gimple_simplify (%s, %s", opr, type);
+  /* ???  Building a stmt can fail for various reasons here, seq being
+ NULL or the stmt referencing SSA names occuring in abnormal PHIs.
+So if we fail here we should continue matching other patterns.  */
+  fprintf (f, "  code_helper tem_code = %s;\n"
+  "  tree tem_ops[3] = { ", opr);
   for (unsigned i = 0; i < ops.length (); ++i)
-   fprintf (f, ", ops%d[%u]", depth, i);
-  fprintf (f, ", seq, valueize);\n");
-  fprintf (f, "  if (!res) return false;\n");
-  fprintf (f, "}\n");
-  fprintf (f, "  else\n");
-  fprintf (f, "res = gimple_build (seq, UNKNOWN_LOCATION, %s, %s",
-  opr, type);
-  for (unsigned i = 0; i < ops.length (); ++i)
-   fprintf (f, ", ops%d[%u]", depth, i);
-  fprintf (f, ", valueize);\n");
+   fprintf (f, "ops%d[%u]%s", depth, i,
+i == ops.length () - 1 ? " };\n" : ", ");
+  fprintf (f, "  gimple_resimplify%d (seq, &tem_code, %s, tem_ops, 
valueize);\n",
+  ops.length (), type);
+  fprintf (f, "  res = maybe_push_res_to_seq (tem_code, %s, tem_ops, 
seq);\n"
+  "  if (!res) return false;\n", type);
 }
   else
 {
@@ -1771,7 +1767,7 @@ expr::gen_transform (FILE *f, const char
fprintf (f, ", ops%d[%u]", depth, i);
   fprintf (f, ");\n");
 }
-  fprintf (f, "  %s = res;\n", dest);
+  fprintf (f, "%s = res;\n", dest);
   fprintf (f, "}\n");
 }
 
Index: gcc/testsuite/gnat.dg/specs/opt2.ads
===
*** gcc/testsuite/gnat.dg/specs/opt2.ads(revision 0)
--- gcc/testsuite/gnat.dg/specs/opt2.ads(revision 0)
***
*** 0 
--- 1,11 
+ -- { dg-do compile }
+ -- { dg-options "-O2" }
+ 
+ with Ada.Strings.Unbounded; use Ada.Strings.Unbounded;
+ with Interfaces;use Interfaces;
+ 
+ package Opt2 is
+ 
+   type Arr is array (Unsigned_32 range <>) of Unbounded_String;
+ 
+ end P;


[PATCH] IPA ICF: make hash values finer

2015-03-24 Thread Martin Liška

Hello.

Following patch should be final speed-up patch for IPA ICF. It just basically 
enhances hash values of a symbol,
computed in a TU. Having finer hash values, we do not spend so much time in WPA 
phase. It shows, we can reduce
utilization from 14% -> 9% (_w/o_ WPA streaming out). Time report and ICF dump 
are added as attachment.

Second, very small, part of the patch replaces add_ptr with add_int (for 
ultimate_alias_target).

Can boostrap on ppc64le-linux-pc and no regression seen on x86_64-linux-pc.
I've been running LTO builds for chrome, firefox and inkscape.

Ready for trunk?
Thanks,
Martin
  1   false returned: '' (compare_phi_node:1426)
  4   false returned: '' (compare_operand:490)
  4   false returned: 'different dependence info' 
(compare_memory_operand:351)
  5   false returned: 'alignment mismatch' (equals_wpa:1530)
 11   false returned: 'TREE_CODE mismatch' (equals:1625)
 19   false returned: 'switch label_exprs are different' 
(compare_gimple_switch:950)
 42   false returned: 'INTEGER_CST precision mismatch' (equals:1708)
 49   false returned: 'ASM strings are different' (compare_gimple_asm:1027)
 57   false returned: 'case high values are different' 
(compare_gimple_switch:941)
 57   false returned: 'operator new flags are different' (equals_wpa:422)
163   false returned: '' (compare_operand:493)
195   false returned: '' (compare_phi_node:1449)
196   false returned: 'PHI node comparison returns false' 
(equals_private:774)
282   false returned: 'different operand volatility' 
(compare_memory_operand:312)
283   false returned: 'ao alias sets are different' 
(compare_memory_operand:316)
399   false returned: 'variables types are different' (equals:1596)
448   false returned: 'Unknown TREE code reached' (compare_operand:572)
477   false returned: 'Declaration mismatch' (equals:1704)
478   false returned: 'case low values are different' 
(compare_gimple_switch:935)
624   false returned: '' (compare_operand:472)
689   false returned: 'different number of arguments' (equals_wpa:407)
915   false returned: 'memory operands are different' 
(compare_gimple_call:805)
   1469   false returned: 'DECL_DISREGARD_INLINE_LIMITS are different' 
(equals_wpa:416)
   3298   false returned: '' (compare_operand:437)
   4918   false returned: 'Target flags are different' (equals_wpa:467)
   6036   false returned: 'different access alignment' 
(compare_memory_operand:334)
   7209   false returned: 'one type is not polymorphic' 
(compatible_polymorphic_types_p:258)
  10177   false returned: '' (equals_private:719)
  10979   false returned: 'OBJ_TYPE_REF OTR type mismatch' (compare_operand:523)
  11271   false returned: '' (equals_private:694)
  11282   false returned: 'DELC_CXX_CONSTRUCTOR mismatch' (equals_wpa:433)
  11624   false returned: 'alias sets are different' (compatible_types_p:278)
  11662   false returned: '' (compare_gimple_call:767)
  16327   false returned: 'virtual or final flag mismatch' (equals_wpa:1571)
  21104   false returned: 'METHOD_TYPE and FUNCTION_TYPE mismatch' 
(equals_wpa:523)
  26301   false returned: 'result types are different' (equals_wpa:487)
  32513   false returned: 'different references' (compare_cgraph_references:374)
  60327   false returned: 'DELC_CXX_DESTRUCTOR mismatch' (equals_wpa:436)
  73746   false returned: 'decl_or_type flags are different' (equals_wpa:439)
  91856   false returned: 'references to virtual tables can not be merged' 
(compare_cgraph_references:360)
 195276   false returned: 'argument type is different' (equals_wpa:498)
 209619   false returned: 'call function types are not compatible' 
(compare_gimple_call:789)
 223350   false returned: 'different tree types' (compatible_types_p:269)
 427168   false returned: 'ctor polymorphic type mismatch' (equals_wpa:452)
 507495   false returned: 'types are not compatible' (compatible_types_p:275)
 567596   false returned: 'memory operands are different' 
(compare_gimple_assign:844)
 628846   false returned: 'optimization flags are different' (equals_wpa:481)
 815465   false returned: '' (equals_private:737)
15707328   false returned: 'inline attributes are different' (equals_wpa:419)
18891178   false returned: 'THIS pointer ODR type mismatch' (equals_wpa:527)
19311137   false returned: 'types are not same for ODR' 
(compatible_polymorphic_types_p:260)

Execution times (seconds)
 phase setup :   0.00 ( 0%) usr   0.00 ( 0%) sys   0.00 ( 0%) wall  
  1978 kB ( 0%) ggc
 phase opt and generate  :  96.43 (45%) usr   2.13 (46%) sys  98.52 (45%) wall 
2497753 kB (12%) ggc
 phase stream in : 120.12 (55%) usr   2.54 (54%) sys 122.61 (55%) 
wall18700766 kB (88%) ggc
 callgraph optimization  :   0.81 ( 0%) usr   0.00 ( 0%) sys   0.82 ( 0%) wall  
14 kB ( 0%) ggc
 ipa dead code removal   :   6.85 ( 3%) usr   0.04 ( 1%) sys   6.76 ( 3%) wall  
 0 kB ( 0%) ggc
 ipa virtual call target :   4.04 ( 2%) usr   0.07

[patch] libstdc++/33394 add testcase

2015-03-24 Thread Jonathan Wakely

Adding a testcase so the bug can be closed.

I believe the segfault was fixed for 3.4.0 by
https://gcc.gnu.org/r67912

Tested x86_64-linux, committed to trunk.

commit c2ae41d5312dce3b4b81653efba477b232dd39f1
Author: Jonathan Wakely 
Date:   Tue Mar 24 14:31:58 2015 +

	PR libstdc++/33394
	* testsuite/21_strings/basic_string/pthread33394.cc: Add test.

diff --git a/libstdc++-v3/testsuite/21_strings/basic_string/pthread33394.cc b/libstdc++-v3/testsuite/21_strings/basic_string/pthread33394.cc
new file mode 100644
index 000..c706504
--- /dev/null
+++ b/libstdc++-v3/testsuite/21_strings/basic_string/pthread33394.cc
@@ -0,0 +1,49 @@
+// Copyright (C) 2015 Free Software Foundation, Inc.
+//
+// This file is part of the GNU ISO C++ Library.  This library is free
+// software; you can redistribute it and/or modify it under the
+// terms of the GNU General Public License as published by the
+// Free Software Foundation; either version 3, or (at your option)
+// any later version.
+
+// This library is distributed in the hope that it will be useful,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+// GNU General Public License for more details.
+
+// You should have received a copy of the GNU General Public License along
+// with this library; see the file COPYING3.  If not see
+// .
+
+// { dg-do run { target *-*-freebsd* *-*-dragonfly* *-*-netbsd* *-*-linux* *-*-gnu* *-*-solaris* *-*-cygwin *-*-darwin* } }
+// { dg-options "-pthread" { target *-*-freebsd* *-*-dragonfly* *-*-netbsd* *-*-linux* *-*-gnu* *-*-solaris* } }
+
+// { dg-options "-DITERATIONS=1000" { target simulator } }
+#ifndef ITERATIONS
+#define ITERATIONS 5
+#endif
+
+// https://gcc.gnu.org/bugzilla/show_bug.cgi?id=32261
+
+#include 
+#include 
+
+extern "C" void* thread_function(void*) {
+for (int k = 0; k < ITERATIONS; k++) {
+std::string my_str;
+my_str += "foo";
+}
+return 0;
+}
+
+int main()
+{
+pthread_t thread1, thread2;
+
+pthread_create(&thread1, NULL, thread_function, NULL);
+pthread_create(&thread2, NULL, thread_function, NULL);
+
+void* exitcode;
+pthread_join(thread1, &exitcode);
+pthread_join(thread2, &exitcode);
+}


Re: [CHKP, PATCH] Fix instrumented indirect calls with propagated pointers

2015-03-24 Thread Richard Biener
On Tue, Mar 24, 2015 at 3:06 PM, Jakub Jelinek  wrote:
> On Tue, Mar 24, 2015 at 12:22:27PM +0300, Ilya Enkovich wrote:
>> 2015-03-24 11:33 GMT+03:00 Jakub Jelinek :
>> > On Thu, Mar 19, 2015 at 11:29:44AM +0300, Ilya Enkovich wrote:
>> >> +  /* We might propagate instrumented function pointer into
>> >> + not instrumented function and vice versa.  In such a
>> >> + case we need to either fix function declaration or
>> >> + remove bounds from call statement.  */
>> >> +  if (callee)
>> >> +skip_bounds = chkp_redirect_edge (e);
>> >
>> > I just want to say that I'm not really excited about all this compile time
>> > cost that is added everywhere unconditionally for chkp.
>> > I think much better would be to guard most of it with proper option check
>> > first and only do the more expensive part if the option has been used.
>>
>> Agree, overhead for not instrumented code should be minimized.
>> Unfortunately there is no option check I can use to guard chkp codes
>> due to LTO. Currently it is allowed to pass -fcheck-pointer-bounds for
>> IL generation and don't pass it for final code generation. I suppose I
>> may set this (or some new) flag if see instrumented node when read
>> cgraph and then use it to guard chkp related codes. Would it be
>> acceptable?
>
> The question is what you want to do in the LTO case for the different cases,
> in particular a TU compiled with -fcheck-pointer-bounds and LTO link without
> that, or TU compiled without -fcheck-pointer-bounds and LTO link with it.
> It could be handled as LTO incompatible option, where lto1 would error out
> if you try to mix -fcheck-pointer-bounds with -fno-check-pointer-bounds
> code, or e.g. similar to var-tracking, you could consider adjusting the IL
> upon LTO reading if if some TU has been built with -fcheck-pointer-bounds
> and the LTO link is -fno-check-pointer-bounds.  Dunno what will happen
> with -fno-check-pointer-bounds TUs LTO linked with -fcheck-pointer-bounds.
> Or another possibility is to or in -fcheck-pointer-bounds from all TUs.
>
>> Maybe replace attribute usage with a new flag in tree_decl_with_vis 
>> structure?
>
> Depends, might be better to stick it into cgraph_node instead, depends on
> whether you are querying it already early in the FEs or just during GIMPLE
> when the cgraph node should be created too.

I also wonder why it is necessary to execute pass_chkp_instrumentation_passes
when mpx is not active.

That is, can we guard that properly in

void
pass_manager::execute_early_local_passes ()
{
  execute_pass_list (cfun, pass_build_ssa_passes_1->sub);
  execute_pass_list (cfun, pass_chkp_instrumentation_passes_1->sub);
  execute_pass_list (cfun, pass_local_optimization_passes_1->sub);
}

(why's that so oddly wrapped?)

class pass_chkp_instrumentation_passes

also has no gate that guards with flag_mpx or so.

That would save a IL walk over all functions (fixup_cfg) and a cgraph
edge rebuild.

Richard.

> Jakub


[PATCH] Rewrite lto streamer DFS from recursion to worklist (PR lto/65515)

2015-03-24 Thread Jakub Jelinek
Hi!

Without this patch, compilation of limits-fndefn.c with -flto
needs huge amounts of stack (more than 20 frames in backtrace).
This patch reworks it so that we use a vector worklist instead,
most of the DFS::DFS_write_tree function body has been moved
into DFS::DFS and DFS_write_tree now just pushes the tree after a few quick
initial checks into the worklist vector.  When operating on the worklist,
we process (most of) the worklist entries twice, first with w.cstate == NULL
is the case where we call DFS_write_tree{,_body} on it and maybe push
further trees into the worklist.  Then the second case is when w.cstate !=
NULL, where we handle the rest.
Without the patch,
ulimit -s 25050
make check-gcc RUNTESTFLAGS=compile.exp=limits-fndefn.c
still works on x86_64-linux in bootstrapped compiler, but
ulimit -s 25000
make check-gcc RUNTESTFLAGS=compile.exp=limits-fndefn.c
already ICEs.
With the patch, even
ulimit -s 64
make check-gcc RUNTESTFLAGS=compile.exp=limits-fndefn.c
works.

Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?

2015-03-24  Jakub Jelinek  

PR lto/65515
* lto-streamer-out.c (DFS::worklist): New struct.
(DFS::worklist_vec): New data member.
(DFS::next_dfs_num): Remove.
(DFS::DFS): Rewritten using worklist instead of recursion,
using most of code from DFS::DFS_write_tree.
(DFS::DFS_write_tree_body): Remove SINGLE_P argument, don't
pass it to DFS_write_tree calls.
(DFS::DFS_write_tree): Remove SINGLE_P argument, after
quick initial checks push it into worklist_vec and return.

--- gcc/lto-streamer-out.c.jj   2015-03-24 11:42:27.0 +0100
+++ gcc/lto-streamer-out.c  2015-03-24 13:09:26.916706309 +0100
@@ -485,31 +485,225 @@ private:
 unsigned int dfsnum;
 unsigned int low;
   };
+  struct worklist
+  {
+tree expr;
+sccs *from_state;
+sccs *cstate;
+bool ref_p;
+bool this_ref_p;
+  };
 
   static int scc_entry_compare (const void *, const void *);
 
   void DFS_write_tree_body (struct output_block *ob,
-   tree expr, sccs *expr_state, bool ref_p,
-   bool single_p);
+   tree expr, sccs *expr_state, bool ref_p);
 
   void DFS_write_tree (struct output_block *ob, sccs *from_state,
-  tree expr, bool ref_p, bool this_ref_p,
-  bool single_p);
+  tree expr, bool ref_p, bool this_ref_p);
+
   hashval_t
   hash_scc (struct output_block *ob, unsigned first, unsigned size);
 
-  unsigned int next_dfs_num;
   hash_map sccstate;
+  vec worklist_vec;
   struct obstack sccstate_obstack;
 };
 
 DFS::DFS (struct output_block *ob, tree expr, bool ref_p, bool this_ref_p,
  bool single_p)
 {
+  unsigned int next_dfs_num = 1;
   sccstack.create (0);
   gcc_obstack_init (&sccstate_obstack);
-  next_dfs_num = 1;
-  DFS_write_tree (ob, NULL, expr, ref_p, this_ref_p, single_p);
+  worklist_vec = vNULL;
+  DFS_write_tree (ob, NULL, expr, ref_p, this_ref_p);
+  while (!worklist_vec.is_empty ())
+{
+  worklist &w = worklist_vec.last ();
+  expr = w.expr;
+  sccs *from_state = w.from_state;
+  sccs *cstate = w.cstate;
+  ref_p = w.ref_p;
+  this_ref_p = w.this_ref_p;
+  if (cstate == NULL)
+   {
+ sccs **slot = &sccstate.get_or_insert (expr);
+ cstate = *slot;
+ if (cstate)
+   {
+ gcc_checking_assert (from_state);
+ if (cstate->dfsnum < from_state->dfsnum)
+   from_state->low = MIN (cstate->dfsnum, from_state->low);
+ worklist_vec.pop ();
+ continue;
+   }
+
+ scc_entry e = { expr, 0 };
+ /* Not yet visited.  DFS recurse and push it onto the stack.  */
+ *slot = cstate = XOBNEW (&sccstate_obstack, struct sccs);
+ sccstack.safe_push (e);
+ cstate->dfsnum = next_dfs_num++;
+ cstate->low = cstate->dfsnum;
+ w.cstate = cstate;
+
+ if (streamer_handle_as_builtin_p (expr))
+   ;
+ else if (TREE_CODE (expr) == INTEGER_CST
+  && !TREE_OVERFLOW (expr))
+   DFS_write_tree (ob, cstate, TREE_TYPE (expr), ref_p, ref_p);
+ else
+   {
+ DFS_write_tree_body (ob, expr, cstate, ref_p);
+
+ /* Walk any LTO-specific edges.  */
+ if (DECL_P (expr)
+ && TREE_CODE (expr) != FUNCTION_DECL
+ && TREE_CODE (expr) != TRANSLATION_UNIT_DECL)
+   {
+ /* Handle DECL_INITIAL for symbols.  */
+ tree initial
+   = get_symbol_initial_value 
(ob->decl_state->symtab_node_encoder,
+   expr);
+ DFS_write_tree (ob, cstate, initial, ref_p, ref_p);
+   }
+   }
+ continue;
+   }
+
+  /* See if we found an SCC.  */
+ 

[PATCH][AArch64][Testsuite] Fix gcc.target/aarch64/c-output-template-3.c

2015-03-24 Thread Alan Lawrence
Following Richard Biener's patch at 
https://gcc.gnu.org/ml/gcc-patches/2015-03/msg01064.html (r221532), 
gcc.target/aarch64/c-output-template-3.c fails with:


c-output-template-3.c: In function 'test':
c-output-template-3.c:7:5: error: impossible constraint in 'asm'
 __asm__ ("@ %c0" : : "S" (&test + 4));

This patch fixes the test by changing options to -O in a similar manner to 
Richard's fixes to gcc.dg/pr15347.c and c-c++-common/pr19807-1.c.


Ok for trunk?

Cheers, Alan

gcc/testsuite/ChangeLog:

gcc.target/aarch64/c-output-template.c: Add -O, remove
-Wno-pointer-arith.
diff --git a/gcc/testsuite/gcc.target/aarch64/c-output-template-3.c b/gcc/testsu
index c28837c..8bde4cb 100644
--- a/gcc/testsuite/gcc.target/aarch64/c-output-template-3.c
+++ b/gcc/testsuite/gcc.target/aarch64/c-output-template-3.c
@@ -1,5 +1,5 @@
 /* { dg-do compile } */
-/* { dg-options "-Wno-pointer-arith" } */
+/* { dg-options "-O" } */
 
 void
 test (void)

[debug-early] emit debug for Fortran named decls

2015-03-24 Thread Aldy Hernandez
I thought we could do without this, but rest_of_decl_compilation is not 
called for constant decls, so I've put back what the Fortran FE 
originally had.  This fixes a gdb regression.


Committed to branch.

Aldy
commit 0f6f7418836c533a49a5464828a0461aec437ebc
Author: Aldy Hernandez 
Date:   Tue Mar 24 09:23:50 2015 -0700

Emit early debug from gfc_emit_parameter_debug_info.

diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index dba6362..107a7d8 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -4776,6 +4776,7 @@ gfc_emit_parameter_debug_info (gfc_symbol *sym)
  TREE_TYPE (decl),
  sym->attr.dimension,
  false, false);
+  debug_hooks->early_global_decl (decl);
 }
 
 


[PATCH, bootstrap]: Add bootstrap-lto-noplugin build configuration (PR65537)

2015-03-24 Thread Uros Bizjak
Hello!

Attached patch introduces bootstrap-lto-noplugin bootstrap
configuration for hosts that do not support linker plugin (e.g. CentOS
5.11 with binutils 2.17). Also, the patch adds some additional
documentation to bootstrap-lto option.

config/ChangeLog:

2015-03-24  Uros Bizjak  

PR bootstrap/65537
* bootstrap-lto-noplugin.mk: New build configuration.

gcc/ChangeLog:

2015-03-24  Uros Bizjak  

PR bootstrap/65537
* doc/install.texi (Building a native compiler): Document new
bootstrap-lto-noplugin configuration.  Mention that bootstrap-lto
configuration assumes that the host supports the linker plugin.

Patch was bootstrapped and tested on x86_64-linux-gnu (CentOS 5.11)
host, configured with --with-build-config=bootstrap-lto build
configuration.

OK for mainline?

Uros.
Index: config/bootstrap-lto-noplugin.mk
===
--- config/bootstrap-lto-noplugin.mk(revision 0)
+++ config/bootstrap-lto-noplugin.mk(working copy)
@@ -0,0 +1,6 @@
+# This option enables LTO for stage2 and stage3 on
+# hosts without linker plugin support.
+
+STAGE2_CFLAGS += -flto=jobserver -frandom-seed=1 -ffat-lto-objects
+STAGE3_CFLAGS += -flto=jobserver -frandom-seed=1 -ffat-lto-objects
+STAGEprofile_CFLAGS += -fno-lto
Index: gcc/doc/install.texi
===
--- gcc/doc/install.texi(revision 221636)
+++ gcc/doc/install.texi(working copy)
@@ -2519,8 +2519,14 @@
 @item @samp{bootstrap-lto}
 Enables Link-Time Optimization for host tools during bootstrapping.
 @samp{BUILD_CONFIG=bootstrap-lto} is equivalent to adding
-@option{-flto} to @samp{BOOT_CFLAGS}.
+@option{-flto} to @samp{BOOT_CFLAGS}.  This option assumes that the host
+supports the linker plugin (e.g. GNU ld version 2.21 or later or GNU gold
+version 2.21 or later).
 
+@item @samp{bootstrap-lto-noplugin}
+This option is similar to @code{bootstrap-lto}, but is intended for
+hosts that do not support the linker plugin.
+
 @item @samp{bootstrap-debug}
 Verifies that the compiler generates the same executable code, whether
 or not it is asked to emit debug information.  To this end, this


[Patch, Fortran, pr60322] was: [Patch 1/2, Fortran, pr60322] [OOP] Incorrect bounds on polymorphic dummy array

2015-03-24 Thread Andre Vehreschild
Hi all,

I have worked on the comments Mikael gave me. I am now checking for
class_pointer in the way he pointed out.

Furthermore did I *join the two parts* of the patch into this one, because
keeping both in sync was no benefit but only tedious and did not prove to be
reviewed faster.

Paul, Dominique: I have addressed the LOC issue that came up lately. Or rather
the patch addressed it already. I feel like this is not tested very well, not
the loc() call nor the sizeof() call as given in the 57305 second's download.
Unfortunately, is that download not runable. I would love to see a test similar
to that download, but couldn't come up with one, that satisfied me. Given that
the patch's review will last some days, I still have enough time to come up
with something beautiful which I will add then.

Bootstraps and regtests ok on x86_64-linux-gnu/F20.

Regards,
Andre


On Tue, 24 Mar 2015 11:13:27 +0100
Paul Richard Thomas  wrote:

> Dear Andre,
> 
> Dominique pointed out to me that the 'loc' patch causes a ICE in the
> testsuite. It seems that 'loc' should provide the address of the class
> container in some places and the address of the data in others. I will
> put my thinking cap on tonight :-)
> 
> Cheers
> 
> Paul
> 
> On 23 March 2015 at 13:43, Andre Vehreschild  wrote:
> > Hi Mikael,
> >
> > thanks for looking at the patch. Please note, that Paul has sent an
> > addendum to the patches for 60322, which I deliberately have attached.
> >
> >>  26/02/2015 18:17, Andre Vehreschild a écrit :
> >> > This first patch is only preparatory and does not change any of the
> >> > semantics of gfortran at all.
> >> Sure?
> >
> > With the counterexample you found below, this of course is a wrong
> > statement.
> >
> >> > diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
> >> > index ab6f7a5..d28cf77 100644
> >> > --- a/gcc/fortran/expr.c
> >> > +++ b/gcc/fortran/expr.c
> >> > @@ -4059,10 +4060,10 @@ gfc_lval_expr_from_sym (gfc_symbol *sym)
> >> >lval->symtree = gfc_find_symtree (sym->ns->sym_root, sym->name);
> >> >
> >> >/* It will always be a full array.  */
> >> > -  lval->rank = sym->as ? sym->as->rank : 0;
> >> > +  as = sym->as;
> >> > +  lval->rank = as ? as->rank : 0;
> >> >if (lval->rank)
> >> > -gfc_add_full_array_ref (lval, sym->ts.type == BT_CLASS ?
> >> > -   CLASS_DATA (sym)->as : sym->as);
> >> > +gfc_add_full_array_ref (lval, as);
> >>
> >> This is a change of semantics.  Or do you know that sym->ts.type !=
> >> BT_CLASS?
> >
> > You are completely right. I have made a mistake here. I have to tell the
> > truth, I never ran a regtest with only part 1 of the patches applied. The
> > second part of the patch will correct this, by setting the variable as
> > depending on whether type == BT_CLASS or not. Sorry for the mistake.
> >
> >> > diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
> >> > index 3664824..e571a17 100644
> >> > --- a/gcc/fortran/trans-decl.c
> >> > +++ b/gcc/fortran/trans-decl.c
> >> > @@ -1013,16 +1017,24 @@ gfc_build_dummy_array_decl (gfc_symbol * sym,
> >> > tree dummy) tree decl;
> >> >tree type;
> >> >gfc_array_spec *as;
> >> > +  symbol_attribute *array_attr;
> >> >char *name;
> >> >gfc_packed packed;
> >> >int n;
> >> >bool known_size;
> >> >
> >> > -  if (sym->attr.pointer || sym->attr.allocatable
> >> > -  || (sym->as && sym->as->type == AS_ASSUMED_RANK))
> >> > +  /* Use the array as and attr.  */
> >> > +  as = sym->as;
> >> > +  array_attr = &sym->attr;
> >> > +
> >> > +  /* The pointer attribute is always set on a _data component, therefore
> >> > check
> >> > + the sym's attribute only.  */
> >> > +  if (sym->attr.pointer || array_attr->allocatable
> >> > +  || (as && as->type == AS_ASSUMED_RANK))
> >> >  return dummy;
> >> >
> >> Any reason to sometimes use array_attr, sometimes not, like here?
> >> By the way, the comment is misleading: for classes, there is the
> >> class_pointer attribute (and it is a pain, I know).
> >
> > Yes, and a good one. Array_attr is sometimes sym->attr and sometimes
> > CLASS_DATA(sym)->attr aka sym->ts.u.derived->components->attr. In the later
> > case .pointer is always set to 1 in the _data component's attr. I.e., the
> > above if, would always yield true for a class_array, which is not intended,
> > but rather destructive. I know about the class_pointer attribute, but I
> > figured, that it is not relevant here. Any idea how to formulate the
> > comment better, to reflect what I just explained?
> >
> > Regards,
> > Andre
> > --
> > Andre Vehreschild * Email: vehre ad gmx dot de
> >
> >
> > -- Forwarded message --
> > From: Paul Richard Thomas 
> > To: Andre Vehreschild , Dominique Dhumieres
> >  Cc:
> > Date: Sun, 22 Mar 2015 21:20:20 +0100
> > Subject: Bug in intrinsic LOC for scalar class objects
> > Dear Andre and Dominique,
> >
> > I have found that LOC is returning the address of the class container
> > rath

[debug-early] avoid unnecessary dwarf passes

2015-03-24 Thread Aldy Hernandez
I've been trying to squash DIEs that get generated too late, and here 
are some minor fixes.


First, I'm now caching CONST_DECL DIEs.  No sense recreating them in 
late debug.


Second, I've limited gen_generic_params_dies() to early dwarf.  I don't 
think we get any additional location info or anything later.


Last, and similarly as above, imported modules shouldn't need to be 
generated in late debug at all.  I don't think they were, but no sense 
going through them as part of process_scope_var in late debug.


Committed to branch.

Aldy
commit ae58778141d336360ea4a7cb7238896eebbe797f
Author: Aldy Hernandez 
Date:   Tue Mar 24 10:17:38 2015 -0700

Cache CONST_DECL dies.

Avoid unnecessary dwarf passes.

diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index 044869d..48e2eed 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -19080,7 +19080,8 @@ gen_subprogram_die (tree decl, dw_die_ref context_die)
   /* XXX */
   if (!lookup_decl_die (decl))
equate_decl_number_to_die (decl, subr_die);
-  gen_generic_params_dies (decl);
+  if (early_dwarf_dumping)
+   gen_generic_params_dies (decl);
 }
 
   /* Now output descriptions of the arguments for this function. This gets
@@ -19713,7 +19714,12 @@ gen_const_die (tree decl, dw_die_ref context_die)
   dw_die_ref const_die;
   tree type = TREE_TYPE (decl);
 
+  const_die = lookup_decl_die (decl);
+  if (const_die)
+return;
+
   const_die = new_die (DW_TAG_constant, context_die, decl);
+  equate_decl_number_to_die (decl, const_die);
   add_name_and_src_coords_attributes (const_die, decl);
   add_type_attribute (const_die, type, TYPE_QUAL_CONST, context_die);
   if (TREE_PUBLIC (decl))
@@ -21018,8 +21024,11 @@ process_scope_var (tree stmt, tree decl, tree origin, 
dw_die_ref context_die)
   if (die != NULL && die->die_parent == NULL)
 add_child_die (context_die, die);
   else if (TREE_CODE (decl_or_origin) == IMPORTED_DECL)
-dwarf2out_imported_module_or_decl_1 (decl_or_origin, DECL_NAME 
(decl_or_origin),
-stmt, context_die);
+{
+  if (early_dwarf_dumping)
+   dwarf2out_imported_module_or_decl_1 (decl_or_origin, DECL_NAME 
(decl_or_origin),
+stmt, context_die);
+}
   else
 gen_decl_die (decl, origin, context_die);
 }


Re: [PATCH] IPA ICF: make hash values finer

2015-03-24 Thread Jan Hubicka
> >From 1943aa293c1ff7622cf9090a834d7bd9dfaaf086 Mon Sep 17 00:00:00 2001
> From: mliska 
> Date: Mon, 23 Mar 2015 15:36:11 +0100
> Subject: [PATCH] IPA ICF: enhance hash value calculated in TU
> 
> gcc/ChangeLog:
> 
> 2015-03-23  Jan Hubicka  
>   Martin Liska  
> 
>   * ipa-icf-gimple.h (return_with_result): Add missing colon to dump.
>   * ipa-icf.c (sem_function::get_hash): Hash new declaration properties.
>   (sem_item::add_type): New function.
>   (sem_function::hash_stmt): Add TREE_TYPE of gimple_op.
>   (sem_function::compare_polymorphic_p): Do not consider indirect calls.
>   (sem_item_optimizer::update_hash_by_addr_refs): Add ODR type to hash.
>   (sem_function::equals_wpa): Fix typo.
>   * ipa-icf.h (sem_item::add_type): New function.
>   (symbol_compare_hashmap_traits): Replace hashing of pointer with symbol
>   order.

OK,
thanks!
Honza


Re: [PATCH] Fix PR65538

2015-03-24 Thread Jan Hubicka
> Hi.
> 
> In following patch, I've added missing delete call for all item summaries 
> that are
> allocated within a function_summary container in case the container does not 
> use
> GGC memory allocation.
> 
> Can boostrap on ppc64le and no regression is seen on x86_64-linux-pc.
> 
> Ready for trunk?
> Thanks,
> Martin

> >From c9912b88e8a381e6be7dc1e4be4f7b8859d72e2f Mon Sep 17 00:00:00 2001
> From: mliska 
> Date: Tue, 24 Mar 2015 13:58:50 +0100
> Subject: [PATCH] Fix PR65538.
> 
> gcc/ChangeLog:
> 
> 2015-03-24  Martin Liska  
> 
>   PR tree-optimization/65538
>   * symbol-summary.h (function_summary::~function_summary):
>   Relese memory for allocated summaries in case non-GGC template
>   instance.
> ---
>  gcc/symbol-summary.h | 6 ++
>  1 file changed, 6 insertions(+)
> 
> diff --git a/gcc/symbol-summary.h b/gcc/symbol-summary.h
> index 8d7e42c..35615ba 100644
> --- a/gcc/symbol-summary.h
> +++ b/gcc/symbol-summary.h
> @@ -81,6 +81,12 @@ public:
>  m_symtab_insertion_hook = NULL;
>  m_symtab_removal_hook = NULL;
>  m_symtab_duplication_hook = NULL;
> +
> +/* Release all summaries in case we use non-GGC memory.  */
> +typedef typename hash_map ::iterator 
> map_iterator;
> +if (!m_ggc)
> +  for (map_iterator it = m_map.begin (); it != m_map.end (); ++it)
> + delete (*it).second;

I think you sould also do the walk with GGC memory and call ggc_free.
During WPA we almost never call ggc_collect so it is better to keep things 
explicitly freed.
OK with that change.

Honza


Re: [PATCH][AArch64][Testsuite] Fix gcc.target/aarch64/c-output-template-3.c

2015-03-24 Thread Alan Lawrence

Hmmm. This is not the right fix: the tests Richard fixed, were failing because
of lack of constant propagation and DCE at compile-time, which then didn't
eliminate the call to link_error. The AArch64 test is failing because this from
aarch64/constraints.md:

(define_constraint "S"
   "A constraint that matches an absolute symbolic address."
   (and (match_code "const,symbol_ref,label_ref")
(match_test "aarch64_symbolic_address_p (op)")))

previously was seeing (and being satisfied by):

(const:DI (plus:DI (symbol_ref:DI ("test") [flags 0x3] )
 (const_int 4 [0x4])))

but following Richard's patch the constraint is evaluated only on:

(reg/f:DI 73 [ D.2670 ])


--Alan

Alan Lawrence wrote:
Following Richard Biener's patch at 
https://gcc.gnu.org/ml/gcc-patches/2015-03/msg01064.html (r221532), 
gcc.target/aarch64/c-output-template-3.c fails with:


c-output-template-3.c: In function 'test':
c-output-template-3.c:7:5: error: impossible constraint in 'asm'
  __asm__ ("@ %c0" : : "S" (&test + 4));

This patch fixes the test by changing options to -O in a similar manner to 
Richard's fixes to gcc.dg/pr15347.c and c-c++-common/pr19807-1.c.


Ok for trunk?

Cheers, Alan

gcc/testsuite/ChangeLog:

gcc.target/aarch64/c-output-template.c: Add -O, remove
-Wno-pointer-arith.





[debug-early] emit early dwarf for locally scoped functions

2015-03-24 Thread Aldy Hernandez

Hi Jason.

I found that for locally scoped functions we were not emitting early 
dwarf.  I've removed the restriction that only emitted non 
function-context functions to handle the case below.  BTW, this 
shouldn't be a (bloat) problem, as we are going to clean up unused DIEs 
later (well, next week :)).


void foobar ()
{
  class Object {
  public:
char Object_method ()
{
  return 5;
}
  };

  Object local;
  local.Object_method();
}

There was also a GDB regression with the above test (distilled from 
gdb.cp/local.cc) where Object_method's type was being generated as


char Object_method (const Object *)

(or something like it).  The problem was that gen_formal_types_die was 
creating nameless DIEs for the formal parameters when generating an 
object's members, but mainline was removing these nameless DIEs and I 
had mistakenly removed that bit.  I'm putting the code back in, but 
guarding it with early_dwarf_dumping, since by the time we get to late 
debug, we should have the correct named parameters which should then be 
augmented with location information.


This patch fixes the gdb.cp/local.cc regressions, while generating early 
dwarf for Object_method and associates.


I'm committing to the branch.  Let me know if you have a problem with this.

Tested with the guality.exp suite as well as the GDB testsuite.

Aldy
commit 8673cbf8204fcd7099507293a859b173343a0f9a
Author: Aldy Hernandez 
Date:   Tue Mar 24 10:47:30 2015 -0700

Emit early dwarf for locally scoped functions.

Only remove cached DW_TAG_formal_parameter's when early dwarf dumping.

diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c
index e60acd5..4a7b14d 100644
--- a/gcc/cgraphunit.c
+++ b/gcc/cgraphunit.c
@@ -2444,8 +2444,7 @@ symbol_table::finalize_compilation_unit (void)
  locally scoped symbols.  */
   struct cgraph_node *cnode;
   FOR_EACH_FUNCTION_WITH_GIMPLE_BODY (cnode)
-if (!decl_function_context (cnode->decl))
-  (*debug_hooks->early_global_decl) (cnode->decl);
+(*debug_hooks->early_global_decl) (cnode->decl);
 
   /* Clean up anything that needs cleaning up after initial debug
  generation.  */
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index 48e2eed..bcc 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -18792,6 +18792,18 @@ gen_subprogram_die (tree decl, dw_die_ref context_die)
 parameters so they can be augmented with location
 information later.  */
  remove_AT (subr_die, DW_AT_declaration);
+
+ /* gen_formal_types_die could have created nameless DIEs for
+the formal parameters when generating an object's
+members.  Remove if early dumping; they will be shortly
+recreated correctly.  If we're not early dumping, we
+should've already removed them and should have actual
+named parameters.  */
+ if (early_dwarf_dumping)
+   {
+ remove_AT (subr_die, DW_AT_object_pointer);
+ remove_child_TAG (subr_die, DW_TAG_formal_parameter);
+   }
}
   /* Make a specification pointing to the previously built
 declaration.  */


C++ PATCH for c++/65498 (ICE with constexpr template argument)

2015-03-24 Thread Jason Merrill
This testcase was breaking because is_same::operator() is only used in 
constexpr evaluation, so cgraph decides it isn't used and throws it 
away.  Then mangling tries to use it for constexpr evaluation while 
re-instantiating F under get_mostly_instantiated_function_type, and 
sadness ensues.


It occurred to me that we really ought to be able to avoid re-doing this 
instantiation, since DECL_TI_TEMPLATE of a function is a partially 
instantiated template that already has the type we want.  And indeed 
this seems to work well, even fixing a bug in mangling.


Tested x86_64-pc-linux-gnu, applying to trunk.
commit 11b13941b2b09f20cb0d42a48199b17a927f624f
Author: Jason Merrill 
Date:   Mon Mar 23 18:44:04 2015 -0400

	PR c++/65498
	* pt.c (get_mostly_instantiated_function_type): Just return the
	type of the partially instantiated template in DECL_TI_TEMPLATE.

diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index ea82621..c649cad 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -20748,62 +20748,8 @@ tsubst_enum (tree tag, tree newtag, tree args)
 tree
 get_mostly_instantiated_function_type (tree decl)
 {
-  tree fn_type;
-  tree tmpl;
-  tree targs;
-  tree tparms;
-  int parm_depth;
-
-  tmpl = most_general_template (DECL_TI_TEMPLATE (decl));
-  targs = DECL_TI_ARGS (decl);
-  tparms = DECL_TEMPLATE_PARMS (tmpl);
-  parm_depth = TMPL_PARMS_DEPTH (tparms);
-
-  /* There should be as many levels of arguments as there are levels
- of parameters.  */
-  gcc_assert (parm_depth == TMPL_ARGS_DEPTH (targs));
-
-  fn_type = TREE_TYPE (tmpl);
-
-  if (parm_depth == 1)
-/* No substitution is necessary.  */
-;
-  else
-{
-  int i;
-  tree partial_args;
-
-  /* Replace the innermost level of the TARGS with NULL_TREEs to
-	 let tsubst know not to substitute for those parameters.  */
-  partial_args = make_tree_vec (TREE_VEC_LENGTH (targs));
-  for (i = 1; i < TMPL_ARGS_DEPTH (targs); ++i)
-	SET_TMPL_ARGS_LEVEL (partial_args, i,
-			 TMPL_ARGS_LEVEL (targs, i));
-  SET_TMPL_ARGS_LEVEL (partial_args,
-			   TMPL_ARGS_DEPTH (targs),
-			   make_tree_vec (DECL_NTPARMS (tmpl)));
-
-  /* Make sure that we can see identifiers, and compute access
-	 correctly.  */
-  push_access_scope (decl);
-
-  ++processing_template_decl;
-  /* Now, do the (partial) substitution to figure out the
-	 appropriate function type.  */
-  fn_type = tsubst (fn_type, partial_args, tf_error, NULL_TREE);
-  --processing_template_decl;
-
-  /* Substitute into the template parameters to obtain the real
-	 innermost set of parameters.  This step is important if the
-	 innermost set of template parameters contains value
-	 parameters whose types depend on outer template parameters.  */
-  TREE_VEC_LENGTH (partial_args)--;
-  tparms = tsubst_template_parms (tparms, partial_args, tf_error);
-
-  pop_access_scope (decl);
-}
-
-  return fn_type;
+  /* For a function, DECL_TI_TEMPLATE is partially instantiated.  */
+  return TREE_TYPE (DECL_TI_TEMPLATE (decl));
 }
 
 /* Return truthvalue if we're processing a template different from
diff --git a/gcc/testsuite/g++.dg/cpp0x/constexpr-targ2.C b/gcc/testsuite/g++.dg/cpp0x/constexpr-targ2.C
new file mode 100644
index 000..285d6c9
--- /dev/null
+++ b/gcc/testsuite/g++.dg/cpp0x/constexpr-targ2.C
@@ -0,0 +1,40 @@
+// PR c++/65498
+// { dg-do compile { target c++11 } }
+
+template 
+struct is_same
+{
+  enum { value = false };
+  constexpr bool operator()() const noexcept { return value; }
+};
+
+template 
+struct is_same
+{
+  enum { value = true };
+  constexpr bool operator()() const noexcept { return value; }
+};
+
+template 
+struct enable_if { };
+
+template 
+struct enable_if { typedef T type; };
+
+struct A;
+
+template 
+struct F { };
+
+template 
+struct F{}()>::type> {
+template 
+F(MakeDependent) {
+auto ICE_HERE = __func__;
+(void)ICE_HERE; // avoid -Wunused-variable
+}
+};
+
+int main() {
+F{1};
+}
diff --git a/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-template13.C b/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-template13.C
index 2b1a605..01fe3f6 100644
--- a/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-template13.C
+++ b/gcc/testsuite/g++.dg/cpp0x/lambda/lambda-template13.C
@@ -20,5 +20,5 @@ void bar ()
   c.foo (1);
 }
 
-// { dg-final { scan-assembler "_ZN8functionC1IZN1CIiE3fooIiEEvT_S_Ed_UlvE_EET_" } }
+// { dg-final { scan-assembler "_ZN8functionC1IZN1CIiE3fooIiEEvT_S_Ed_UlvE_EES4_" } }
 // { dg-final { scan-assembler-not "_ZZN1CIiE3fooIiEEvT_8functionEd_NKUlvE_clEv" } }


libgo/gotools patch committed: Fix go get dependencies

2015-03-24 Thread Ian Lance Taylor
PR 65462 points out a problem with the way that the gccgo version of
go get handles dependencies, a problem due to the fact that with gccgo
the source code of the standard packages is not normally available.
This patch from Lynn Boger fixes the problem.  Bootstrapped and ran Go
testsuite on x86_64-unknown-linux-gnu.  Committed to mainline.

Ian

gotools/ChangeLog:

2015-03-24  Ian Lance Taylor  

PR go/65462
* Makefile.am (go_cmd_go_files): Add $(libgodir)/zstdpkglist.go.
* Makefile.in: Rebuild.
Index: libgo/Makefile.am
===
--- libgo/Makefile.am   (revision 221440)
+++ libgo/Makefile.am   (working copy)
@@ -978,6 +978,20 @@ s-version: Makefile
$(SHELL) $(srcdir)/mvifdiff.sh version.go.tmp version.go
$(STAMP) $@
 
+noinst_DATA = zstdpkglist.go
+
+# Generate the list of go std packages that were included in libgo
+zstdpkglist.go: s-zstdpkglist; @true
+s-zstdpkglist: Makefile
+   rm -f zstdpkglist.go.tmp
+   echo 'package main' > zstdpkglist.go.tmp
+   echo "" >> zstdpkglist.go.tmp
+   echo 'var stdpkg = map[string]bool{' >> zstdpkglist.go.tmp
+   echo $(libgo_go_objs) 'unsafe.lo' | sed 's/\.lo /\": true,\n/g' | sed 
's/\.lo/\": true,/' | sed 's/-go//' | grep -v _c | sed 's/^/\t\"/' | sort | 
uniq >> zstdpkglist.go.tmp
+   echo '}' >> zstdpkglist.go.tmp
+   $(SHELL) $(srcdir)/mvifdiff.sh zstdpkglist.go.tmp zstdpkglist.go
+   $(STAMP) $@
+
 go_sort_files = \
go/sort/search.go \
go/sort/sort.go
Index: libgo/go/cmd/go/build.go
===
--- libgo/go/cmd/go/build.go(revision 221440)
+++ libgo/go/cmd/go/build.go(working copy)
@@ -132,7 +132,8 @@ var buildLdflags []string// -ldflags
 var buildGccgoflags []string // -gccgoflags flag
 var buildRace bool   // -race flag
 
-var reqPkgSrc bool // req src for Imports
+// Require the source for go std packages
+var reqStdPkgSrc bool
 var buildContext = build.Default
 var buildToolchain toolchain = noToolchain{}
 
@@ -187,9 +188,9 @@ func addBuildFlags(cmd *Command) {
cmd.Flag.BoolVar(&buildRace, "race", false, "")
switch build.Default.Compiler {
case "gc":
-   reqPkgSrc = true
+   reqStdPkgSrc = true
case "gccgo":
-   reqPkgSrc = false
+   reqStdPkgSrc = false
}
 }
 
@@ -579,7 +580,7 @@ func (b *builder) action(mode buildMode,
// are writing is not the cgo we need to use.
 
if goos == runtime.GOOS && goarch == runtime.GOARCH && !buildRace {
-   if reqPkgSrc {
+   if reqStdPkgSrc {
if len(p.CgoFiles) > 0 || p.Standard && p.ImportPath == 
"runtime/cgo" {
var stk importStack
p1 := loadPackage("cmd/cgo", &stk)
Index: libgo/go/cmd/go/pkg.go
===
--- libgo/go/cmd/go/pkg.go  (revision 221440)
+++ libgo/go/cmd/go/pkg.go  (working copy)
@@ -112,7 +112,11 @@ func (p *Package) copyBuild(pp *build.Pa
p.ConflictDir = pp.ConflictDir
// TODO? Target
p.Goroot = pp.Goroot
-   p.Standard = p.Goroot && p.ImportPath != "" && 
!strings.Contains(p.ImportPath, ".")
+   if buildContext.Compiler == "gccgo" {
+   p.Standard = stdpkg[p.ImportPath]
+   } else {
+   p.Standard = p.Goroot && p.ImportPath != "" && 
!strings.Contains(p.ImportPath, ".")
+   }
p.GoFiles = pp.GoFiles
p.CgoFiles = pp.CgoFiles
p.IgnoredGoFiles = pp.IgnoredGoFiles
@@ -582,7 +586,7 @@ func (p *Package) load(stk *importStack,
continue
}
p1 := loadImport(path, p.Dir, stk, p.build.ImportPos[path])
-   if !reqPkgSrc && p1.Root == "" {
+   if !reqStdPkgSrc && p1.Standard {
continue
}
if p1.local {
Index: libgo/go/cmd/go/test.go
===
--- libgo/go/cmd/go/test.go (revision 221440)
+++ libgo/go/cmd/go/test.go (working copy)
@@ -384,17 +384,18 @@ func runTest(cmd *Command, args []string
delete(deps, "unsafe")
 
all := []string{}
-   if reqPkgSrc {
-   for path := range deps {
-   if !build.IsLocalImport(path) {
-   all = append(all, path)
-   }
+   for path := range deps {
+   if !build.IsLocalImport(path) {
+   all = append(all, path)
}
}
sort.Strings(all)
 
a := &action{}
for _, p := range packagesForBuild(all) {
+   if !reqStdPkgSrc && p.Stand

[PATCH, ARM] Fix arm_subsi3_insn alternatives

2015-03-24 Thread Yvan Roux
Hi,

after the issue with duplicated alternatives exhibited by PR64208, I
checked the arm.md file and found that *arm_subsi3_insn has a
duplication where alt 4 is (r,rI,r) and alt 6 is (r,r,r), this results
in emitting an rsb instruction instead of a sub one, but it has also
an impact on scheduling as the type attribute affected to alt 4 is
alu_imm when it could only involve registers.

This is fixed by this small patch. Cross builded and regtested for
arm/armeb targets.
Ok for trunk (maybe for stage 1 as no PR is attached to that) ?

Cheers,
Yvan

 2105-03-24  Yvan Roux  

* config/arm/arm.md ("*arm_subsi3_insn"): Fixed redundant alternatives.
diff --git a/gcc/config/arm/arm.md b/gcc/config/arm/arm.md
index 164ac13..b4e50c2 100644
--- a/gcc/config/arm/arm.md
+++ b/gcc/config/arm/arm.md
@@ -1177,9 +1177,9 @@
 
 ; ??? Check Thumb-2 split length
 (define_insn_and_split "*arm_subsi3_insn"
-  [(set (match_operand:SI   0 "s_register_operand" "=l,l ,l ,l ,r 
,r,r,rk,r")
-   (minus:SI (match_operand:SI 1 "reg_or_int_operand" "l ,0 ,l 
,Pz,rI,r,r,k ,?n")
- (match_operand:SI 2 "reg_or_int_operand" "l ,Py,Pd,l ,r 
,I,r,r ,r")))]
+  [(set (match_operand:SI   0 "s_register_operand" "=l,l ,l ,l 
,r,r,r,rk,r")
+   (minus:SI (match_operand:SI 1 "reg_or_int_operand" "l ,0 ,l ,Pz,I,r,r,k 
,?n")
+ (match_operand:SI 2 "reg_or_int_operand" "l ,Py,Pd,l ,r,I,r,r 
,r")))]
   "TARGET_32BIT"
   "@
sub%?\\t%0, %1, %2


Re: [Patch, libstdc++/65420] Use constexpr variables as regex_constans flags

2015-03-24 Thread Tim Shen
On Sun, Mar 15, 2015 at 11:27 PM, Tim Shen  wrote:
> Here's the simple version of it.

Ping?


-- 
Regards,
Tim Shen


Re: [PATCH] pr 63354 - gcc -pg -mprofile-kernel creates unused stack frames on leaf functions on ppc64le

2015-03-24 Thread Martin Sebor

I'm assuming that you mean a cross-compile (which is a stage1 without -werror). 
 If you look in the build output (I just repeated this on x86_64-darwin12 X 
powerpc-darwin9) you'll see:

/GCC/gcc-trunk/gcc/config/rs6000/rs6000.c:24404:1: warning: ‘bool 
rs6000_keep_leaf_when_profiled()’ defined but not used [-Wunused-function]
  rs6000_keep_leaf_when_profiled (void)
  ^

this becomes a bootstrap error at stage#2.  If you don't see that, then I have 
don't have the same patch applied as you :).


Yes, I meant a cross-compile. I don't have a Darwin environment
but I managed to reproduce it while building stage1 with -Werror
(after fixing a number of problems that cause the build to fail
earlier on). Thanks for your patience.

Attached is an updated patch with your suggested change (i.e.,
defining the TARGET_KEEP_LEAF_WHEN_PROFILED macro in rs6000.h
instead of linux64.h).

I tested the patch by building stage1 with -Werror for both
powerpc64-darwin9 and powerpc64-unknown-linux-gnu (both on
the latter target).

Martin
2015-03-24  Anton Blanchard  

	PR target/63354
	* config/rs6000/rs6000.h (TARGET_KEEP_LEAF_WHEN_PROFILED): Define.
	* config/rs6000/rs6000.c (rs6000_keep_leaf_when_profiled): New
	function.

2015-03-24  Martin Sebor  

	PR target/63354
	* gcc.target/powerpc/pr63354.c: New test.

diff --git a/gcc/config/rs6000/rs6000.c b/gcc/config/rs6000/rs6000.c
index 31b46ea..f1508b9 100644
--- a/gcc/config/rs6000/rs6000.c
+++ b/gcc/config/rs6000/rs6000.c
@@ -24397,6 +24397,23 @@ rs6000_output_function_prologue (FILE *file,
   rs6000_pic_labelno++;
 }
 
+/* -mprofile-kernel code calls mcount before the function prologue,
+   so a profiled leaf function should stay a leaf function.  */
+
+static bool
+rs6000_keep_leaf_when_profiled (void)
+{
+  switch (DEFAULT_ABI)
+{
+  case ABI_AIX:
+  case ABI_ELFv2:
+   return TARGET_PROFILE_KERNEL;
+
+  default:
+   return true;
+}
+}
+
 /* Non-zero if vmx regs are restored before the frame pop, zero if
we restore after the pop when possible.  */
 #define ALWAYS_RESTORE_ALTIVEC_BEFORE_POP 0
diff --git a/gcc/config/rs6000/rs6000.h b/gcc/config/rs6000/rs6000.h
index ef6bb2f..50394b0 100644
--- a/gcc/config/rs6000/rs6000.h
+++ b/gcc/config/rs6000/rs6000.h
@@ -703,6 +703,9 @@ extern unsigned char rs6000_recip_bits[];
 #define TARGET_CPU_CPP_BUILTINS() \
   rs6000_cpu_cpp_builtins (pfile)
 
+#undef TARGET_KEEP_LEAF_WHEN_PROFILED
+#define TARGET_KEEP_LEAF_WHEN_PROFILED rs6000_keep_leaf_when_profiled
+
 /* This is used by rs6000_cpu_cpp_builtins to indicate the byte order
we're compiling for.  Some configurations may need to override it.  */
 #define RS6000_CPU_CPP_ENDIAN_BUILTINS()	\
diff --git a/gcc/testsuite/gcc.target/powerpc/pr63354.c b/gcc/testsuite/gcc.target/powerpc/pr63354.c
new file mode 100644
index 000..9e635cc
--- /dev/null
+++ b/gcc/testsuite/gcc.target/powerpc/pr63354.c
@@ -0,0 +1,10 @@
+/* { dg-do compile { target { powerpc64*-*-linux* } } } */
+/* { dg-options "-O2 -pg -mprofile-kernel" } */
+
+int foo (void)
+{
+  return 1;
+}
+
+/* { dg-final { scan-assembler "bl _mcount" } } */
+/* { dg-final { scan-assembler-not "(addi|stdu) 1," } } */


libgo patch committed: Add support for PPC32 relocs to debug/elf

2015-03-24 Thread Ian Lance Taylor
PR 65417 points out that the gccgo debug/elf package does not support
PPC32 relocations, which means that the cgo tool does not work
correctly.  This patch fixes that.  This is a backport of
http://golang.org/cl/7590 from the master library sources.
Bootstrapped and ran Go testsuite on x86_64-unknown-linux-gnu.
Committed to mainline.

Ian
diff -r 6ed23fc8eac4 libgo/go/debug/elf/file.go
--- a/libgo/go/debug/elf/file.goTue Mar 24 12:43:53 2015 -0700
+++ b/libgo/go/debug/elf/file.goTue Mar 24 13:51:18 2015 -0700
@@ -532,6 +532,9 @@
if f.Class == ELFCLASS64 && f.Machine == EM_AARCH64 {
return f.applyRelocationsARM64(dst, rels)
}
+   if f.Class == ELFCLASS32 && f.Machine == EM_PPC {
+   return f.applyRelocationsPPC(dst, rels)
+   }
if f.Class == ELFCLASS64 && f.Machine == EM_PPC64 {
return f.applyRelocationsPPC64(dst, rels)
}
@@ -677,6 +680,46 @@
return nil
 }
 
+func (f *File) applyRelocationsPPC(dst []byte, rels []byte) error {
+   // 12 is the size of Rela32.
+   if len(rels)%12 != 0 {
+   return errors.New("length of relocation section is not a 
multiple of 12")
+   }
+
+   symbols, _, err := f.getSymbols(SHT_SYMTAB)
+   if err != nil {
+   return err
+   }
+
+   b := bytes.NewReader(rels)
+   var rela Rela32
+
+   for b.Len() > 0 {
+   binary.Read(b, f.ByteOrder, &rela)
+   symNo := rela.Info >> 8
+   t := R_PPC(rela.Info & 0xff)
+
+   if symNo == 0 || symNo > uint32(len(symbols)) {
+   continue
+   }
+   sym := &symbols[symNo-1]
+   if SymType(sym.Info&0xf) != STT_SECTION {
+   // We don't handle non-section relocations for now.
+   continue
+   }
+
+   switch t {
+   case R_PPC_ADDR32:
+   if rela.Off+4 >= uint32(len(dst)) || rela.Addend < 0 {
+   continue
+   }
+   f.ByteOrder.PutUint32(dst[rela.Off:rela.Off+4], 
uint32(rela.Addend))
+   }
+   }
+
+   return nil
+}
+
 func (f *File) applyRelocationsPPC64(dst []byte, rels []byte) error {
// 24 is the size of Rela64.
if len(rels)%24 != 0 {
diff -r 6ed23fc8eac4 libgo/go/debug/elf/file_test.go
--- a/libgo/go/debug/elf/file_test.go   Tue Mar 24 12:43:53 2015 -0700
+++ b/libgo/go/debug/elf/file_test.go   Tue Mar 24 13:51:18 2015 -0700
@@ -261,6 +261,12 @@
},
},
{
+   "testdata/go-relocation-test-gcc5-ppc.obj",
+   []relocationTestEntry{
+   {0, &dwarf.Entry{Offset: 0xb, Tag: 
dwarf.TagCompileUnit, Children: true, Field: []dwarf.Field{dwarf.Field{Attr: 
dwarf.AttrProducer, Val: "GNU C11 5.0.0 20150116 (experimental) -Asystem=linux 
-Asystem=unix -Asystem=posix -g"}, dwarf.Field{Attr: dwarf.AttrLanguage, Val: 
int64(12)}, dwarf.Field{Attr: dwarf.AttrName, Val: 
"go-relocation-test-gcc5-ppc.c"}, dwarf.Field{Attr: dwarf.AttrCompDir, Val: 
"/tmp"}, dwarf.Field{Attr: dwarf.AttrLowpc, Val: uint64(0x0)}, 
dwarf.Field{Attr: dwarf.AttrHighpc, Val: int64(0x44)}, dwarf.Field{Attr: 
dwarf.AttrStmtList, Val: int64(0),
+   },
+   },
+   {
"testdata/go-relocation-test-gcc482-ppc64le.obj",
[]relocationTestEntry{
{0, &dwarf.Entry{Offset: 0xb, Tag: 
dwarf.TagCompileUnit, Children: true, Field: []dwarf.Field{dwarf.Field{Attr: 
dwarf.AttrProducer, Val: "GNU C 4.8.2 -Asystem=linux -Asystem=unix 
-Asystem=posix -msecure-plt -mtune=power8 -mcpu=power7 -gdwarf-2 
-fstack-protector"}, dwarf.Field{Attr: dwarf.AttrLanguage, Val: int64(1)}, 
dwarf.Field{Attr: dwarf.AttrName, Val: "go-relocation-test-gcc482-ppc64le.c"}, 
dwarf.Field{Attr: dwarf.AttrCompDir, Val: "/tmp"}, dwarf.Field{Attr: 
dwarf.AttrLowpc, Val: uint64(0x0)}, dwarf.Field{Attr: dwarf.AttrHighpc, Val: 
uint64(0x24)}, dwarf.Field{Attr: dwarf.AttrStmtList, Val: int64(0),
diff -r 6ed23fc8eac4 libgo/go/debug/elf/testdata/go-relocation-test-gcc5-ppc.obj
Binary file libgo/go/debug/elf/testdata/go-relocation-test-gcc5-ppc.obj has 
changed


Re: [PATCH] Rewrite lto streamer DFS from recursion to worklist (PR lto/65515)

2015-03-24 Thread Jakub Jelinek
On Tue, Mar 24, 2015 at 04:19:46PM +0100, Jakub Jelinek wrote:
> Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?

Also tested with
../configure --with-build-config=bootstrap-lto 
--enable-languages=c,c++,fortran,objc,obj-c++,go
make -j16; make -j16 -k check
on x86_64-linux, no regressions.

Jakub


Re: [PATCH] Fix PR65538

2015-03-24 Thread Martin Liška
On 03/24/2015 06:38 PM, Jan Hubicka wrote:
>> Hi.
>>
>> In following patch, I've added missing delete call for all item summaries 
>> that are
>> allocated within a function_summary container in case the container does not 
>> use
>> GGC memory allocation.
>>
>> Can boostrap on ppc64le and no regression is seen on x86_64-linux-pc.
>>
>> Ready for trunk?
>> Thanks,
>> Martin
> 
>> >From c9912b88e8a381e6be7dc1e4be4f7b8859d72e2f Mon Sep 17 00:00:00 2001
>> From: mliska 
>> Date: Tue, 24 Mar 2015 13:58:50 +0100
>> Subject: [PATCH] Fix PR65538.
>>
>> gcc/ChangeLog:
>>
>> 2015-03-24  Martin Liska  
>>
>>  PR tree-optimization/65538
>>  * symbol-summary.h (function_summary::~function_summary):
>>  Relese memory for allocated summaries in case non-GGC template
>>  instance.
>> ---
>>  gcc/symbol-summary.h | 6 ++
>>  1 file changed, 6 insertions(+)
>>
>> diff --git a/gcc/symbol-summary.h b/gcc/symbol-summary.h
>> index 8d7e42c..35615ba 100644
>> --- a/gcc/symbol-summary.h
>> +++ b/gcc/symbol-summary.h
>> @@ -81,6 +81,12 @@ public:
>>  m_symtab_insertion_hook = NULL;
>>  m_symtab_removal_hook = NULL;
>>  m_symtab_duplication_hook = NULL;
>> +
>> +/* Release all summaries in case we use non-GGC memory.  */
>> +typedef typename hash_map ::iterator 
>> map_iterator;
>> +if (!m_ggc)
>> +  for (map_iterator it = m_map.begin (); it != m_map.end (); ++it)
>> +delete (*it).second;
> 
> I think you sould also do the walk with GGC memory and call ggc_free.
> During WPA we almost never call ggc_collect so it is better to keep things 
> explicitly freed.
> OK with that change.
> 
> Honza
> 

There's updated version of patch, I've been testing. I'm going to install the 
patch
after it finishes.

Thanks,
Martin
>From 8ae68cd2c69287c26543b22fa7afe2ff5cdcda8c Mon Sep 17 00:00:00 2001
From: mliska 
Date: Tue, 24 Mar 2015 13:58:50 +0100
Subject: [PATCH] Fix PR65538.

gcc/ChangeLog:

2015-03-24  Martin Liska  

	PR tree-optimization/65538
	* symbol-summary.h (function_summary::~function_summary):
	Relese memory for allocated summaries in case non-GGC template
	instance.
---
 gcc/symbol-summary.h | 15 +++
 1 file changed, 15 insertions(+)

diff --git a/gcc/symbol-summary.h b/gcc/symbol-summary.h
index 8d7e42c..9a87891 100644
--- a/gcc/symbol-summary.h
+++ b/gcc/symbol-summary.h
@@ -81,6 +81,12 @@ public:
 m_symtab_insertion_hook = NULL;
 m_symtab_removal_hook = NULL;
 m_symtab_duplication_hook = NULL;
+
+/* Release all summaries in case we use non-GGC memory.  */
+typedef typename hash_map ::iterator map_iterator;
+if (!m_ggc)
+  for (map_iterator it = m_map.begin (); it != m_map.end (); ++it)
+	release ((*it).second);
   }
 
   /* Traverses all summarys with a function F called with
@@ -106,6 +112,15 @@ public:
 return m_ggc ? new (ggc_alloc  ()) T() : new T () ;
   }
 
+  /* Release an item that is stored within map.  */
+  void release (T *item)
+  {
+if (m_ggc)
+  ggc_free (item);
+else
+  delete item;
+  }
+
   /* Getter for summary callgraph node pointer.  */
   T* get (cgraph_node *node)
   {
-- 
2.1.4



Re: [PATCH] Fix PR65538

2015-03-24 Thread Jakub Jelinek
On Tue, Mar 24, 2015 at 10:54:25PM +0100, Martin Liška wrote:
> --- a/gcc/symbol-summary.h
> +++ b/gcc/symbol-summary.h
> @@ -81,6 +81,12 @@ public:
>  m_symtab_insertion_hook = NULL;
>  m_symtab_removal_hook = NULL;
>  m_symtab_duplication_hook = NULL;
> +
> +/* Release all summaries in case we use non-GGC memory.  */
> +typedef typename hash_map ::iterator 
> map_iterator;
> +if (!m_ggc)
> +  for (map_iterator it = m_map.begin (); it != m_map.end (); ++it)
> + release ((*it).second);

You haven't removed the now unnecessary if (!m_ggc) guard.

> @@ -106,6 +112,15 @@ public:
>  return m_ggc ? new (ggc_alloc  ()) T() : new T () ;
>}
>  
> +  /* Release an item that is stored within map.  */
> +  void release (T *item)
> +  {
> +if (m_ggc)
> +  ggc_free (item);

Perhaps run also the item's destructor first?  I know that
inline_summary doesn't have a user destructor, so it will expand to nothing,
so it would be just for completeness.

> +else
> +  delete item;
> +  }
> +

Jakub


[Patch, fortran] PR65532 shape mismatch error with data partial initialization

2015-03-24 Thread Mikael Morin
Hello,

here is a fix for the regression I introduced with my PR64952 patch.

The regression is a spurious shape mismatch error message coming from a
variable partial initialization through data statements.
Before the patch at the time of the shape check, the initialization is
still unset as processing of data statements comes after that point, so
that no error message is issued.
The PR64952 introduce an extra call to gfc_resolve, which may make
resolve_types be called more than once.  And the second times it is, the
data statements have been processed and error messages are issued.

The patch I propose here adds a flag to remember the function has been
called, and skip it the second time.
I considered reusing the existing 'resolved' field, but I had to
slightly change its semantics to prevent regressing somewhere, and I was
not completely sure how safe that change was.
I have finally preferred this safer patch keeping the existing field
completely untouched.

Regression tested on x86_64-unknown-linux-gnu. OK for trunk?

Mikael

2015-03-24  Mikael Morin  

PR fortran/64952
PR fortran/65532
* gfortran.h (struct gfc_namespace): New field 'types_resolved'.
* resolve.c (resolve_types): Return early if field 'types_resolved'
is set.  Set 'types_resolved' at the end.

2015-03-24  Mikael Morin  

PR fortran/64952
PR fortran/65532
* gfortran.dg/data_initialized_3.f90: New.
Index: gfortran.h
===
--- gfortran.h	(révision 221586)
+++ gfortran.h	(copie de travail)
@@ -1691,6 +1691,9 @@ typedef struct gfc_namespace
  Holds -1 during resolution.  */
   signed resolved:2;
 
+  /* Set when resolve_types has been called for this namespace.  */
+  unsigned types_resolved:1;
+
   /* Set to 1 if code has been generated for this namespace.  */
   unsigned translated:1;
 
Index: resolve.c
===
--- resolve.c	(révision 221586)
+++ resolve.c	(copie de travail)
@@ -14942,6 +14942,9 @@ resolve_types (gfc_namespace *ns)
   gfc_equiv *eq;
   gfc_namespace* old_ns = gfc_current_ns;
 
+  if (ns->types_resolved)
+return;
+
   /* Check that all IMPLICIT types are ok.  */
   if (!ns->seen_implicit_none)
 {
@@ -15016,6 +15019,8 @@ resolve_types (gfc_namespace *ns)
 
   gfc_resolve_omp_udrs (ns->omp_udr_root);
 
+  ns->types_resolved = 1;
+
   gfc_current_ns = old_ns;
 }
 

! { dg-do compile }
!
! PR fortran/65532
! The partial initialization through data statements was producing
! shape mismatch errors.
!
! Contributed by Harald Anlauf  

module gfcbug131
  implicit none
contains
  DOUBLE PRECISION FUNCTION d1mach(i)
INTEGER, INTENT(IN) :: i

INTEGER :: small(4)
INTEGER :: large(4)
INTEGER :: right(4)
INTEGER :: diver(4)
INTEGER :: LOG10(4)
DOUBLE PRECISION :: dmach(5)

EQUIVALENCE (dmach(1),small(1))
EQUIVALENCE (dmach(2),large(1))
EQUIVALENCE (dmach(3),right(1))
EQUIVALENCE (dmach(4),diver(1))
EQUIVALENCE (dmach(5),LOG10(1))

DATA small(1),small(2) /  0,1048576 /
DATA large(1),large(2) / -1, 2146435071 /
DATA right(1),right(2) /  0, 1017118720 /
DATA diver(1),diver(2) /  0, 1018167296 /
DATA LOG10(1),LOG10(2) / 1352628735, 1070810131 /

d1mach = dmach(i)
  END FUNCTION d1mach

  DOUBLE PRECISION FUNCTION foo (x)
DOUBLE PRECISION, INTENT(IN) :: x
foo = SQRT (d1mach(4))
  END FUNCTION foo

end module gfcbug131




Re: [PATCH] Fix PR65538

2015-03-24 Thread Jan Hubicka
> On Tue, Mar 24, 2015 at 10:54:25PM +0100, Martin Liška wrote:
> > --- a/gcc/symbol-summary.h
> > +++ b/gcc/symbol-summary.h
> > @@ -81,6 +81,12 @@ public:
> >  m_symtab_insertion_hook = NULL;
> >  m_symtab_removal_hook = NULL;
> >  m_symtab_duplication_hook = NULL;
> > +
> > +/* Release all summaries in case we use non-GGC memory.  */
> > +typedef typename hash_map ::iterator 
> > map_iterator;
> > +if (!m_ggc)
> > +  for (map_iterator it = m_map.begin (); it != m_map.end (); ++it)
> > +   release ((*it).second);
> 
> You haven't removed the now unnecessary if (!m_ggc) guard.
> 
> > @@ -106,6 +112,15 @@ public:
> >  return m_ggc ? new (ggc_alloc  ()) T() : new T () ;
> >}
> >  
> > +  /* Release an item that is stored within map.  */
> > +  void release (T *item)
> > +  {
> > +if (m_ggc)
> > +  ggc_free (item);
> 
> Perhaps run also the item's destructor first?  I know that
> inline_summary doesn't have a user destructor, so it will expand to nothing,
> so it would be just for completeness.

Yep, calling destructors is a good idea.  OK with that change
and fix Jakub pointed out.

Honza
> 
> > +else
> > +  delete item;
> > +  }
> > +
> 
>   Jakub


[v3] Fix libstdc++/65543

2015-03-24 Thread Paolo Carlini

Hi,

as I said in the audit trail, this isn't a regression but the fix seems 
safe enough to me even for mainline: it's matter of reverting a dumb, 
supposedly "cosmetic" change of mine dating back to 2009. I mean to 
apply it to 4_9 and 4_8 too. Tested x86_64-linux.


Thanks,
Paolo.

/
2015-03-25  Paolo Carlini  

PR libstdc++/65543
* include/std/istream (operator>>(basic_istream<>&&, _Tp&): Revert
thinko in r150387.
* include/std/ostream (operator<<(basic_ostream<>&&, const _Tp&):
Likewise.
* testsuite/27_io/rvalue_streams-2.cc: Likewise.
Index: include/std/istream
===
--- include/std/istream (revision 221642)
+++ include/std/istream (working copy)
@@ -922,7 +922,10 @@
   template
 inline basic_istream<_CharT, _Traits>&
 operator>>(basic_istream<_CharT, _Traits>&& __is, _Tp& __x)
-{ return (__is >> __x); }
+{ 
+  __is >> __x;
+  return __is;
+}
 #endif // C++11
 
 _GLIBCXX_END_NAMESPACE_VERSION
Index: include/std/ostream
===
--- include/std/ostream (revision 221642)
+++ include/std/ostream (working copy)
@@ -626,7 +626,10 @@
   template
 inline basic_ostream<_CharT, _Traits>&
 operator<<(basic_ostream<_CharT, _Traits>&& __os, const _Tp& __x)
-{ return (__os << __x); }
+{
+  __os << __x;
+  return __os;
+}
 #endif // C++11
 
 _GLIBCXX_END_NAMESPACE_VERSION
Index: testsuite/27_io/rvalue_streams-2.cc
===
--- testsuite/27_io/rvalue_streams-2.cc (revision 0)
+++ testsuite/27_io/rvalue_streams-2.cc (working copy)
@@ -0,0 +1,35 @@
+// { dg-options "-std=gnu++11" }
+// { dg-do compile }
+
+// Copyright (C) 2015 Free Software Foundation, Inc.
+//
+// This file is part of the GNU ISO C++ Library.  This library is free
+// software; you can redistribute it and/or modify it under the
+// terms of the GNU General Public License as published by the
+// Free Software Foundation; either version 3, or (at your option)
+// any later version.
+
+// This library is distributed in the hope that it will be useful,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+// GNU General Public License for more details.
+
+// You should have received a copy of the GNU General Public License along
+// with this library; see the file COPYING3.  If not see
+// .
+
+#include 
+
+struct A {};
+
+void operator<<(std::ostream&, const A&) { }
+void operator>>(std::istream&, A&) { }
+
+// PR libstdc++/65543
+int main()
+{
+  A a;
+
+  std::ostringstream() << a;
+  std::istringstream() >> a;
+}


[rl78] fix 'p' test

2015-03-24 Thread DJ Delorie

Mis-applied patch, committed.

* config/rl78/rl78.c (rl78_print_operand_1): Move 'p' test to
correct clause.

Index: config/rl78/rl78.c
===
--- config/rl78/rl78.c  (revision 221648)
+++ config/rl78/rl78.c  (working copy)
@@ -1641,20 +1641,20 @@ rl78_print_operand_1 (FILE * file, rtx o
   && GET_CODE (XEXP (XEXP (op, 0), 0)) == REG
   && REGNO (XEXP (XEXP (op, 0), 0)) == 2)
{
  rl78_print_operand_1 (file, XEXP (XEXP (op, 0), 1), 'u');
  fprintf (file, "[");
  rl78_print_operand_1 (file, XEXP (XEXP (op, 0), 0), 0);
- if (letter == 'p' && GET_CODE (XEXP (op, 0)) == REG)
-   fprintf (file, "+0");
  fprintf (file, "]");
}
  else
{
  fprintf (file, "[");
  rl78_print_operand_1 (file, XEXP (op, 0), letter);
+ if (letter == 'p' && GET_CODE (XEXP (op, 0)) == REG)
+   fprintf (file, "+0");
  fprintf (file, "]");
}
}
   break;
 
 case REG: