Re: [Patch, libfortran] PR 52434/48878/38199 Improve floating point formatted writes

2012-03-15 Thread Janne Blomqvist
On Thu, Mar 15, 2012 at 01:52, Jerry DeLisle jvdeli...@charter.net wrote:
 I like the idea behind this patch.  I confess, I have not studied the two
 test cases that you are modifying, but the changes seem to stick out with
 too many digits there.  Is this really correct?
 When I get another moment, I will look closer. Maybe you can explain the
 need for this change a little more.  Sorry if I am being to careful. Its
 been many months since I delved into the formatting code.

The reason is that with the patch, the default rounding is whatever
snprintf() gives us. At least with glibc, snprintf() rounds ties to
even, but I'm not sure all implementations do this rather than
rounding ties to away. So the testcase changes just make sure that
we're not rounding a tie. E.g. 1.25 rounded to two significant
digits is 1.2 if one rounds ties to even, 1.3 if ties are rounded
away. So using 1.250001 ensures that the rounded value is 1.3 with
both rounding modes.

I suppose another option would be to assume that rounding is ties to
even, and keep an eye out for regressions on other targets.


-- 
Janne Blomqvist


[Ada] Implement Ada 2012 attributes First_Valid and Last_Valid

2012-03-15 Thread Arnaud Charlet
This patch implements the new attributes First_Valid and Last_Valid.
These apply to static discrete types with at least one valid value.
The static discrete type may have a static predicate (which is the
case where these attributes are useful). They return the lowest and
highest values for which valid values (that is values that satisfy
any static predicate) exist.

The following shows error detection in action (compiled with
-gnat12 -gnatj60 -gnatld7)

 1. procedure FLValidError (P : Integer) is
 2.subtype R1 is integer range 1 .. 0;
 3.subtype R2 is integer range 1 .. 10
 4.  with Dynamic_Predicate = R2  P;
 5.subtype R3 is integer range 1 .. 10
 6.  with Static_Predicate = R3  12;
 7.subtype R4 is integer range 1 .. P;
 8.
 9.Val : Integer;
10.
11. begin
12.Val := Float'First_Valid;   -- Not discrete
  |
 prefix of First_Valid attribute must be
discrete type

13.Val := Float'Last_Valid;-- Not discrete
  |
 prefix of Last_Valid attribute must be
discrete type

14.Val := R1'First_Valid;  -- No values
  |
 prefix of First_Valid attribute must be
subtype with at least one value

15.Val := R1'Last_Valid;   -- No values
  |
 prefix of Last_Valid attribute must be
subtype with at least one value

16.Val := R2'First_Valid;  -- Dynamic predicate
  |
 prefix of First_Valid attribute may not have
dynamic predicate

17.Val := R2'Last_Valid;   -- Dynamic_Predicate
  |
 prefix of Last_Valid attribute may not have
dynamic predicate

18.Val := R3'First_Valid;  -- No values
  |
 prefix of First_Valid attribute must be
subtype with at least one value

19.Val := R3'Last_Valid;   -- No values
  |
 prefix of Last_Valid attribute must be
subtype with at least one value

20.Val := R4'First_Valid;  -- Non-static subtype
  |
 prefix of First_Valid attribute must be a
static subtype

21.Val := R4'Last_Valid;   -- Non-static subtype
  |
 prefix of Last_Valid attribute must be a
static subtype

22. end FLValidError;

The following compiles and executes quietly

 1. procedure FLRange is
 2.subtype R1 is Integer range 1 .. 10;
 3.subtype R2 is Integer range 1 .. 10
 4.  with Static_Predicate = R2  2 or R2  9;
 5.subtype R3 is Integer range 1 .. 10
 6.  with Static_Predicate = R3  3 or R3  8;
 7.subtype R4 is Integer range 1 .. 10
 8.  with Static_Predicate = R4 = 3 and R4 = 9;
 9.
10.procedure Fail is
11.begin
12.   raise Program_Error;
13.end Fail;
14.
15. begin
16.if R1'First_Valid /= 1 or else R1'Last_Valid /= 10 then
17.   Fail;
18.end if;
19.
20.if R2'First_Valid /= 1 or else R2'Last_Valid /= 10 then
21.   Fail;
22.end if;
23.
24.if R3'First_Valid /= 1 or else R3'Last_Valid /= 10 then
25.   Fail;
26.end if;
27.
28.if R4'First_Valid /= 3 or else R4'Last_Valid /= 9 then
29.   Fail;
30.end if;
31. end FLRange;

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

2012-03-15  Robert Dewar  de...@adacore.com

* exp_attr.adb (Expand_N_Attribute_Reference): Add handling
of First_Valid/Last_Valid.
* sem_attr.adb (Check_First_Last_Valid): New procedure
(Analyze_Attribute): Add handling of First_Valid and Last_Valid
(Eval_Attribute): ditto.
* snames.ads-tmpl: Add entries for First_Valid and Last_Valid.

Index: exp_attr.adb
===
--- exp_attr.adb(revision 185390)
+++ exp_attr.adb(working copy)
@@ -5701,10 +5701,12 @@
Attribute_Enabled  |
Attribute_Epsilon  |
Attribute_Fast_Math|
+   Attribute_First_Valid  |
Attribute_Has_Access_Values|
Attribute_Has_Discriminants|
Attribute_Has_Tagged_Values|
Attribute_Large|
+   Attribute_Last_Valid   |
Attribute_Machine_Emax |
Attribute_Machine_Emin |
Attribute_Machine_Mantissa |
Index: sem_attr.adb
===
--- sem_attr.adb(revision 185390)
+++ sem_attr.adb(working copy)
@@ -217,10 +217,14 @@
   --  allowed with a type that 

[Ada] Cleaning up of quantified expression analysis and expansion.

2012-03-15 Thread Arnaud Charlet
This patch corrects the previous messy and erroneous analysis of quantified
expression.

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

2012-03-15  Vincent Pucci  pu...@adacore.com

* exp_ch4.adb (Expand_N_Quantified_Expression): Expand the
original quantified expression node.
* sem_ch4.adb (Analyze_Quantified_Expression): Properly analyze
the quantified expression and preserve the original non-analyzed
quantified expression when an expansion is needed.
* sem_ch5.adb (Analyze_Iteration_Scheme): Special treatment
for quantified expressions.
(Analyze_Iterator_Specification): Special treatment for quantified
expressions.

Index: sem_ch5.adb
===
--- sem_ch5.adb (revision 185390)
+++ sem_ch5.adb (working copy)
@@ -2087,8 +2087,18 @@
 
Check_Controlled_Array_Attribute (DS);
 
-   Make_Index (DS, LP, In_Iter_Schm = True);
+   --  The index is not processed during the analysis of a
+   --  quantified expression but delayed to its expansion where the
+   --  quantified expression is transformed into an expression with
+   --  actions.
 
+   if Nkind (Parent (N)) /= N_Quantified_Expression
+ or else Operating_Mode = Check_Semantics
+ or else Alfa_Mode
+   then
+  Make_Index (DS, LP, In_Iter_Schm = True);
+   end if;
+
Set_Ekind (Id, E_Loop_Parameter);
 
--  If the loop is part of a predicate or precondition, it may
@@ -2097,14 +2107,7 @@
--  because the second one may be created in a different scope,
--  e.g. a precondition procedure, leading to a crash in GIGI.
 
-   --  Note that if the parent node is a quantified expression,
-   --  this preservation is delayed until the expansion of the
-   --  quantified expression where the node is rewritten as an
-   --  expression with actions.
-
-   if (No (Etype (Id)) or else Etype (Id) = Any_Type)
- and then Nkind (Parent (N)) /= N_Quantified_Expression
-   then
+   if No (Etype (Id)) or else Etype (Id) = Any_Type then
   Set_Etype (Id, Etype (DS));
end if;
 
@@ -2241,14 +2244,14 @@
   --  If domain of iteration is an expression, create a declaration for
   --  it, so that finalization actions are introduced outside of the loop.
   --  The declaration must be a renaming because the body of the loop may
-  --  assign to elements.
+  --  assign to elements. In case of a quantified expression, this
+  --  declaration is delayed to its expansion where the node is rewritten
+  --  as an expression with actions.
 
-  --  Note that if the parent node is a quantified expression, this
-  --  declaration is created during the expansion of the quantified
-  --  expression where the node is rewritten as an expression with actions.
-
   if not Is_Entity_Name (Iter_Name)
-and then Nkind (Parent (Parent (N))) /= N_Quantified_Expression
+and then (Nkind (Parent (Parent (N))) /= N_Quantified_Expression
+   or else Operating_Mode = Check_Semantics
+   or else Alfa_Mode)
   then
  declare
 Id   : constant Entity_Id := Make_Temporary (Loc, 'R', Iter_Name);
Index: exp_ch4.adb
===
--- exp_ch4.adb (revision 185390)
+++ exp_ch4.adb (working copy)
@@ -7891,9 +7891,22 @@
   Cond : Node_Id;
   Decl : Node_Id;
   I_Scheme : Node_Id;
+  Original_N   : Node_Id;
   Test : Node_Id;
 
begin
+  --  Retrieve the original quantified expression (non analyzed)
+
+  if Present (Loop_Parameter_Specification (N)) then
+ Original_N := Parent (Parent (Loop_Parameter_Specification (N)));
+  else
+ Original_N := Parent (Parent (Iterator_Specification (N)));
+  end if;
+
+  --  Rewrite N with the original quantified expression
+
+  Rewrite (N, Original_N);
+
   Decl :=
 Make_Object_Declaration (Loc,
   Defining_Identifier = Tnn,
@@ -7904,13 +7917,6 @@
 
   Cond := Relocate_Node (Condition (N));
 
-  --  Reset flag analyzed in the condition to force its analysis. Required
-  --  since the previous analysis was done with expansion disabled (see
-  --  Resolve_Quantified_Expression) and hence checks were not inserted
-  --  and record comparisons have not been expanded.
-
-  Reset_Analyzed_Flags (Cond);
-
   if Is_Universal then
  Cond := Make_Op_Not (Loc, Cond);
   end if;
@@ -7926,9 +7932,14 @@
 Make_Exit_Statement (Loc)));
 
   if Present (Loop_Parameter_Specification (N)) then
- 

[Ada] Misuse of constant class-wide objects

2012-03-15 Thread Arnaud Charlet
An object declaration of a class-wide object with a tag-indeterminate initial
value is rewritten as a renaming of a dereference. The renaming must preserve
the kind of the object (constant or variable). Previous to this patch, the
compiler failed to reject a call to a primitive operation with an in-out
controlling formal, when the actual was a constant class-wide object.

Compiling main.adb in -gnat05 mode must yield:

main.adb:16:04: actual for I must be a variable

---
with Element; use Element;
procedure Main
is
   Object : constant Element.I_Interface'Class := Element.T_Class'(null record);
begin
   Object.Add;
end Main;
---
package Element is

   type I_Interface is interface;

   procedure Add (I : in out I_Interface) is abstract;

   function Create return I_Interface'Class;

   type T_Class is new I_Interface with null record;

   overriding procedure Add (I : in out T_Class) is null;
end Element;

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

2012-03-15  Ed Schonberg  schonb...@adacore.com

* exp_ch3.adb (Expand_N_Object_Declaration): When rewriting the
declaration of a class-wide object, retain the Ekind to prevent
subsequent misuse of constants.

Index: exp_ch3.adb
===
--- exp_ch3.adb (revision 185390)
+++ exp_ch3.adb (working copy)
@@ -4829,10 +4829,12 @@
   --  object renaming declaration ---because these identifiers
   --  were previously added by Enter_Name to the current scope.
   --  We must preserve the homonym chain of the source entity
-  --  as well.
+  --  as well. We must also preserve the kind of the entity,
+  --  which may be a constant.
 
   Set_Chars (Defining_Identifier (N), Chars (Def_Id));
   Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
+  Set_Ekind (Defining_Identifier (N), Ekind (Def_Id));
   Exchange_Entities (Defining_Identifier (N), Def_Id);
end;
 end if;


[Ada] Missing finalization call of interface class-wide object

2012-03-15 Thread Arnaud Charlet
This patch corrects the code which detects whether an interface class-wide
object has been initialized by a controlled function call.


-- Source --


--  element.ads

with Ada.Containers.Indefinite_Doubly_Linked_Lists;
with Ada.Containers.Indefinite_Holders;

package Element is
   type I_Interface is interface;
   procedure Add (I : in out I_Interface) is abstract;
   function = (Left, Right : I_Interface) return Boolean is abstract;
   procedure Clear (Self : in out I_Interface'Class);

   package Interface_Holder is new Ada.Containers.Indefinite_Holders
 (Element_Type = I_Interface'Class,
  =  = =);

   function Create return I_Interface'Class;

   type T_Abstract_Element is abstract tagged null record;
   function = (Left, Right : T_Abstract_Element) return Boolean;
   type T_Concrete_Element is new T_Abstract_Element with null record;

   package Element_Collection is
 new Ada.Containers.Indefinite_Doubly_Linked_Lists
   (Element_Type = T_Abstract_Element'Class);

   type T_Class is new I_Interface with record
  Attributs : Element_Collection.List;
   end record;

   overriding procedure Add (I : in out T_Class);
   overriding function = (Left, Right : T_Class) return Boolean is (True);
end Element;

--  element.adb

package body Element is
   function Create return I_Interface'Class is
   begin
  return T_Class'(Attributs = Element_Collection.Empty_List);
   end Create;

   overriding procedure Add (I : in out T_Class) is
   begin
  I.Attributs.Append (T_Concrete_Element'(null record));
   end Add;

   function = (Left, Right : T_Abstract_Element) return Boolean is
   begin
  return False;
   end =;

   procedure Clear (Self : in out I_Interface'Class) is
  Elmt : T_Class := T_Class (Self);
   begin
  Elmt.Attributs.Clear;
   end Clear;
end Element;

--  main.adb

with Element; use type Element.I_Interface;

procedure Main is
   Holder : Element.Interface_Holder.Holder :=
  Element.Interface_Holder.To_Holder (Element.Create);
begin
   for I in 1 .. 100 loop
  declare
 Object : Element.I_Interface'Class := Holder.Element;
  begin
 Object.Add;
 Holder.Replace_Element (Object);
  end;
   end loop;
end Main;

-
-- Compilation and expected output --
-

$ gnatmake -q -gnat12 main.adb -largs -lgmem
$ ./main
$ gnatmem ./main
$ Global information
$ --
$Total number of allocations:30203
$Total number of deallocations  :30203
$Final Water Mark (non freed mem)   :   0 Bytes
$High Water Mark:  13.98 Kilobytes

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

2012-03-15  Hristian Kirtchev  kirtc...@adacore.com

* exp_util.adb (Initialized_By_Ctrl_Function): Add code to
process the case when a function call appears in object.operation
format.

Index: exp_util.adb
===
--- exp_util.adb(revision 185390)
+++ exp_util.adb(working copy)
@@ -3960,11 +3960,28 @@
   --
 
   function Initialized_By_Ctrl_Function (N : Node_Id) return Boolean is
- Expr : constant Node_Id := Original_Node (Expression (N));
+ Expr : Node_Id := Original_Node (Expression (N));
+
   begin
+ if Nkind (Expr) = N_Function_Call then
+Expr := Name (Expr);
+ end if;
+
+ --  The function call may appear in object.operation format. Strip
+ --  all prefixes and retrieve the function name.
+
+ loop
+if Nkind (Expr) = N_Selected_Component then
+   Expr := Selector_Name (Expr);
+else
+   exit;
+end if;
+ end loop;
+
  return
-Nkind (Expr) = N_Function_Call
-  and then Needs_Finalization (Etype (Expr));
+   Nkind_In (Expr, N_Expanded_Name, N_Identifier)
+ and then Ekind (Entity (Expr)) = E_Function
+ and then Needs_Finalization (Etype (Entity (Expr)));
   end Initialized_By_Ctrl_Function;
 
   --


[Ada] Ada 2012 AI05-288: conformance for formal access-to-subprogram types

2012-03-15 Thread Arnaud Charlet
AI05-288 specifies that subtype conformance is required for actual types for
generic formal access-to-subprogram types, rather than just mode conformance.
This is a binding interpretation.

Compiling pack2.adb must yield:

pack2.adb:4:37: not subtype conformant with declaration at pack1.ads:2
pack2.adb:4:37: type of N does not match

generic
type ACC is access procedure (N : Natural);
package Pack1 is
procedure Test1 (A : out ACC);
end Pack1;
---
package body Pack1 is
procedure Test1 (A : out ACC) is
begin
null;
end Test1;
end Pack1;
---
package Pack2 is
procedure Cause_A_Problem;
end Pack2;
---
with Pack1;
package body Pack2 is
type Actual_Acc is access procedure (N : Integer);
package New_Pack1 is new Pack1 (Actual_Acc);
procedure Cause_A_Problem is
X : Actual_Acc;
begin
New_Pack1.Test1 (X);
X (-1);   -- PROBLEM
end Cause_A_Problem;
end Pack2;
---

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

2012-03-15  Ed Schonberg  schonb...@adacore.com

* sem_ch6.ads, sem_ch6.adb (Check_Subtype_Conformant): add
Get_Inst formal, so that conformance within an instantiation
follows renamings of formals. This is similar to what is already
done in Check_Mode_conformant.
* sem_ch12.adb (Vailidate_Access_Subprogram_Instance): check that
formal and actual are subtype conformant. Previously only mode
conformance was required.

Index: sem_ch12.adb
===
--- sem_ch12.adb(revision 185390)
+++ sem_ch12.adb(working copy)
@@ -10433,7 +10433,11 @@
 Abandon_Instantiation (Actual);
  end if;
 
- Check_Mode_Conformant
+ --  In Ada 2012, actuals for access_to_subprograms must be subtype
+ --  conformant with the generic formal. Previous to AI05-288 only mode
+ --  conformance was required.
+
+ Check_Subtype_Conformant
(Designated_Type (Act_T),
 Designated_Type (A_Gen_T),
 Actual,
Index: sem_ch6.adb
===
--- sem_ch6.adb (revision 185390)
+++ sem_ch6.adb (working copy)
@@ -7251,14 +7251,16 @@
  (New_Id   : Entity_Id;
   Old_Id   : Entity_Id;
   Err_Loc  : Node_Id := Empty;
-  Skip_Controlling_Formals : Boolean := False)
+  Skip_Controlling_Formals : Boolean := False;
+  Get_Inst : Boolean := False)
is
   Result : Boolean;
   pragma Warnings (Off, Result);
begin
   Check_Conformance
 (New_Id, Old_Id, Subtype_Conformant, True, Result, Err_Loc,
- Skip_Controlling_Formals = Skip_Controlling_Formals);
+ Skip_Controlling_Formals = Skip_Controlling_Formals,
+ Get_Inst = Get_Inst);
end Check_Subtype_Conformant;
 
---
Index: sem_ch6.ads
===
--- sem_ch6.ads (revision 185390)
+++ sem_ch6.ads (working copy)
@@ -28,7 +28,7 @@
 
type Conformance_Type is
  (Type_Conformant, Mode_Conformant, Subtype_Conformant, Fully_Conformant);
-   pragma Ordered (Conformance_Type);
+   --  pragma Ordered (Conformance_Type);
--  Conformance type used in conformance checks between specs and bodies,
--  and for overriding. The literals match the RM definitions of the
--  corresponding terms. This is an ordered type, since each conformance
@@ -141,7 +141,8 @@
  (New_Id   : Entity_Id;
   Old_Id   : Entity_Id;
   Err_Loc  : Node_Id := Empty;
-  Skip_Controlling_Formals : Boolean := False);
+  Skip_Controlling_Formals : Boolean := False;
+  Get_Inst : Boolean := False);
--  Check that two callable entities (subprograms, entries, literals)
--  are subtype conformant, post error message if not (RM 6.3.1(16)),
--  the flag being placed on the Err_Loc node if it is specified, and


Re: [dwarf]:

2012-03-15 Thread Tristan Gingold
Thanks, committed.

(And sorry for the truncated subject).

Tristan.

On Mar 14, 2012, at 6:50 PM, Jason Merrill wrote:

 OK.
 
 Jason



Re: [C] Handle #pragma before a parameter

2012-03-15 Thread Tristan Gingold
Thanks, committed.

Tristan.

On Mar 14, 2012, at 5:33 PM, Joseph S. Myers wrote:

 On Wed, 14 Mar 2012, Tristan Gingold wrote:
 
 Hi,
 
 it happens that some system headers on VMS have #pragma between parameters.  
 This is spotted by building the Ada runtime.
 
 This patch simply handles them.
 
 Manually tested by building for ia64-hp-openvms.
 No regressions for c on x86_64-darwin.
 
 Ok for trunk ?
 
 OK.
 
 -- 
 Joseph S. Myers
 jos...@codesourcery.com



[Ada] New pragma and aspect Contract_Case to refine contracts

2012-03-15 Thread Arnaud Charlet
A new pragma and aspect Contract_Case is defined, which allows defining
fine-grain specifications that can complement or replace the contract given
by a precondition and a postcondition. Additionally, the Contract_Case pragma
or aspect can be used by testing and formal verification tools. The compiler
checks its validity and, depending on the assertion policy at the point of
declaration of the pragma or aspect, it may insert a check in the executable.

When compiled with assertions enabled (-gnata) and run, the following code
raises an exception:

$ ./main
$ raised SYSTEM.ASSERTIONS.ASSERT_FAILURE : failed contract case from p.ads:3

--- main.adb
 1. with P; use P;
 2.
 3. procedure Main is
 4.X : Integer;
 5. begin
 6.X := 10;
 7.Incr (X);
 8.X := -10;
 9.Incr (X);
10. end Main;

--- p.adb
 1. package body P is
 2.procedure Incr (X : in out Integer) is
 3.begin
 4.   if X /= -10 then
 5.  X := X + 1;
 6.   end if;
 7.end Incr;
 8. end P;

--- p.ads
 1. package P is
 2.procedure Incr (X : in out Integer) with
 3.  Contract_Case = (Name = ,
 4.Mode = Nominal,
 5.Requires = X  0,
 6.Ensures  = X = X'Old + 1);
 7. end P;
---

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

2012-03-15  Yannick Moy  m...@adacore.com

* aspects.adb, aspects.ads (Aspect_Id): New GNAT aspect
Aspect_Contract_Case.
* gnat_rm.texi Document the new pragma/aspect
Contract_Case. Correct the documentation of the existing
pragma/aspect Test_Case with the new semantics.
* sem_attr.adb (Analyze_Attribute): Allow use of 'Result in the
Ensures component of a Contract_Case pragma.
* sem_ch13.adb (Analyze_Aspect_Specifications): Check new aspect
and translate it into a pragma.
(Check_Aspect_At_Freeze_Point): Take into account the new aspect.
* sem_ch3.adb, sinfo.adb, sinfo.ads Renaming of TC (for test case)
into CTC (for contract and test case).
* sem_ch6.adb (Process_PPCs): Generate Check pragmas from
Contract_Case pragmas, similarly to what is done already for
postconditions.
* sem_prag.adb, sem_prag.ads (Check_Contract_Or_Test_Case):
Renaming of Check_Test_Case.
(Analyze_Pragma, Sig_Flags): Take into account the new pragma.
* sem_util.adb, sem_util.ads Renaming to take into account the
new pragma, so that functions which applied only to Test_Case
now apply to both Test_Case and Contract_Case.
* par-prag.adb, sem_warn.adb, snames.ads-tmpl Take into account
the new pragma.

Index: sem_ch3.adb
===
--- sem_ch3.adb (revision 185390)
+++ sem_ch3.adb (working copy)
@@ -2204,9 +2204,9 @@
 
Check_Subprogram_Contract (Sent);
 
-   Prag := Spec_TC_List (Contract (Sent));
+   Prag := Spec_CTC_List (Contract (Sent));
while Present (Prag) loop
-  Analyze_TC_In_Decl_Part (Prag, Sent);
+  Analyze_CTC_In_Decl_Part (Prag, Sent);
   Prag := Next_Pragma (Prag);
end loop;
 end if;
Index: gnat_rm.texi
===
--- gnat_rm.texi(revision 185410)
+++ gnat_rm.texi(working copy)
@@ -120,6 +120,7 @@
 * Pragma Complete_Representation::
 * Pragma Complex_Representation::
 * Pragma Component_Alignment::
+* Pragma Contract_Case::
 * Pragma Convention_Identifier::
 * Pragma CPP_Class::
 * Pragma CPP_Constructor::
@@ -855,6 +856,7 @@
 * Pragma Complete_Representation::
 * Pragma Complex_Representation::
 * Pragma Component_Alignment::
+* Pragma Contract_Case::
 * Pragma Convention_Identifier::
 * Pragma CPP_Class::
 * Pragma CPP_Constructor::
@@ -1704,6 +1706,108 @@
 pragma @code{Pack}, pragma @code{Component_Alignment}, or a record rep
 clause), the GNAT uses the default alignment as described previously.
 
+@node Pragma Contract_Case
+@unnumberedsec Pragma Contract_Case
+@cindex Contract cases
+@findex Contract_Case
+@noindent
+Syntax:
+
+@smallexample @c ada
+pragma Contract_Case (
+   [Name =] static_string_Expression
+  ,[Mode =] (Nominal | Robustness)
+ [, Requires =  Boolean_Expression]
+ [, Ensures  =  Boolean_Expression]);
+@end smallexample
+
+@noindent
+The @code{Contract_Case} pragma allows defining fine-grain specifications
+that can complement or replace the contract given by a precondition and a
+postcondition. Additionally, the @code{Contract_Case} pragma can be used
+by testing and formal verification tools. The compiler checks its validity and,
+depending on the assertion policy at the point of declaration of the pragma,
+it may insert a check in the executable. For 

[Ada] Issue warning on suspicious contract cases when -gnatw.t is set

2012-03-15 Thread Arnaud Charlet
The warning option -gnatw.t already issued warnings on suspicious
postconditions. This extends it to contract cases, which is a GNAT
pragma/aspect allowing to express fine-grain contracts. GNAT now detects
these cases on the following code:

$ gcc -c -gnatc -gnatw.t -gnat12 p.ads

 1. package P is
 2.function A_Is_Positive (X : Integer) return Boolean with
 3.  Contract_Case = (Name= normal case,
 |
 warning: Ensures component refers only to pre-state
 warning: contract cases do not mention result

 4.Mode= Nominal,
 5.Ensures = X = 0);
 6.procedure A_Incr (X : in Integer; Y : out Integer) with
 7.  Contract_Case = (Name= normal case,
 |
 warning: Ensures component refers only to pre-state

 8.Mode= Nominal,
 9.Ensures = X = X + 1);
10. end P;

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

2012-03-15  Yannick Moy  m...@adacore.com

* gnat_ugn.texi Document the extension of option -gnatw.t.
* sem_ch3.adb (Analyze_Declaration): Check for suspicious
contracts only after contract cases have been semantically
analyzed.
* sem_ch6.adb (Check_Subprogram_Contract): Consider also Ensures
components of contract cases for detecting suspicious contracts.

Index: sem_ch3.adb
===
--- sem_ch3.adb (revision 185415)
+++ sem_ch3.adb (working copy)
@@ -2196,19 +2196,26 @@
Spec := Specification (Original_Node (Decl));
Sent := Defining_Unit_Name (Spec);
 
+   --  Analyze preconditions and postconditions
+
Prag := Spec_PPC_List (Contract (Sent));
while Present (Prag) loop
   Analyze_PPC_In_Decl_Part (Prag, Sent);
   Prag := Next_Pragma (Prag);
end loop;
 
-   Check_Subprogram_Contract (Sent);
+   --  Analyze contract-cases and test-cases
 
Prag := Spec_CTC_List (Contract (Sent));
while Present (Prag) loop
   Analyze_CTC_In_Decl_Part (Prag, Sent);
   Prag := Next_Pragma (Prag);
end loop;
+
+   --  At this point, entities have been attached to identifiers.
+   --  This is required to be able to detect suspicious contracts.
+
+   Check_Subprogram_Contract (Sent);
 end if;
 
 Next (Decl);
Index: gnat_ugn.texi
===
--- gnat_ugn.texi   (revision 185410)
+++ gnat_ugn.texi   (working copy)
@@ -5696,9 +5696,11 @@
 @emph{Activate warnings on suspicious contracts.}
 @cindex @option{-gnatw.t} (@command{gcc})
 This switch activates warnings on suspicious postconditions (whether a
-pragma @code{Postcondition} or a @code{Post} aspect in Ada 2012). A
-function postcondition is suspicious when it does not mention the result
-of the function. A procedure postcondition is suspicious when it only
+pragma @code{Postcondition} or a @code{Post} aspect in Ada 2012)
+and suspicious contract cases (pragma @code{Contract_Case}). A
+function postcondition or contract case is suspicious when no postcondition
+or contract case for this function mentions the result of the function.
+A procedure postcondition or contract case is suspicious when it only
 refers to the pre-state of the procedure, because in that case it should
 rather be expressed as a precondition. The default is that such warnings
 are not generated. This warning can also be turned on using @option{-gnatwa}.
Index: sem_ch6.adb
===
--- sem_ch6.adb (revision 185415)
+++ sem_ch6.adb (working copy)
@@ -6953,6 +6953,9 @@
   --  Last postcondition on the subprogram, or else Empty if either no
   --  postcondition or only inherited postconditions.
 
+  Last_Contract_Case : Node_Id := Empty;
+  --  Last contract-case on the subprogram, or else Empty
+
   Attribute_Result_Mentioned : Boolean := False;
   --  Whether attribute 'Result is mentioned in a postcondition
 
@@ -6971,9 +6974,14 @@
   --  reference to attribute 'Old, in order to ignore its prefix, which
   --  is precisely evaluated in the pre-state. Otherwise return OK.
 
+  procedure Process_Contract_Cases (Spec : Node_Id);
+  --  This processes the Spec_CTC_List from Spec, processing any contract
+  --  case from the list. The caller has checked that Spec_CTC_List is
+  --  non-Empty.
+
   procedure Process_Post_Conditions (Spec : Node_Id; Class : Boolean);
   --  This processes the Spec_PPC_List from Spec, processing any
-  --  postconditions from the list. If Class is True, then only
+  --  postcondition from the list. If Class is 

[Ada] Switch to control maximum number of instantiations

2012-03-15 Thread Arnaud Charlet
This patch adds the switch (-gnateinn, MAX_INSTANTIATIONS=nn in VMS)
to control the maximum number of instantiations. This may be used to
increase the limit from the default of 8000 in the very rare case
where a single unit legitimately has more than 8000 instantiations.

The following program:

 1. procedure MaxInst is
 2.generic package P is
 3.   X : Integer;
 4.end;
 5.
 6.package P1 is new P;
 7.package P2 is new P;
 8.package P4 is new P;
 9.package P5 is new P;
10.package P6 is new P;
11.package P7 is new P;
12.package P8 is new P;
13.package P9 is new P;
14. begin
15.null;
16. end;

If compiled with -gnatei4 -gnatj64, yields

maxinst.adb:12:04: too many instantiations, exceeds max of 4,
   limit can be changed using -gnateinn switch
compilation abandoned

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

2012-03-15  Robert Dewar  de...@adacore.com

* errout.ads: Add entry for translating -gnateinn to
/MAX_INSTANTIATIONS for VMS.
* hostparm.ads (Max_Instantiations): Moved to Opt.
* opt.ads (Maximum_Instantiations): Moved from Hostparm, and renamed.
* sem_ch12.adb (Maximum_Instantiations): New name of
Max_Instantiations (Analyze_Package_Instantiation): Change error
msg for too many instantiations (mention -gnateinn switch).
* switch-c.adb (Scan_Front_End_Switches): Implement -gnateinn switch.
* switch.ads: Minor comment update.
* usage.adb (Usage): Output line for -maxeinn switch.
* vms_data.ads: Add entry for MAX_INSTANTIATIONS (-gnateinn).

Index: switch-c.adb
===
--- switch-c.adb(revision 185390)
+++ switch-c.adb(working copy)
@@ -6,7 +6,7 @@
 --  --
 -- B o d y  --
 --  --
---  Copyright (C) 2001-2011, Free Software Foundation, Inc. --
+--  Copyright (C) 2001-2012, 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- --
@@ -482,6 +482,13 @@
  Generate_Processed_File := True;
  Ptr := Ptr + 1;
 
+  --  -gnatei (max number of instantiations)
+
+  when 'i' =
+ Ptr := Ptr + 1;
+ Scan_Pos
+   (Switch_Chars, Max, Ptr, Maximum_Instantiations, C);
+
   --  -gnateI (index of unit in multi-unit source)
 
   when 'I' =
Index: usage.adb
===
--- usage.adb   (revision 185390)
+++ usage.adb   (working copy)
@@ -6,7 +6,7 @@
 --  --
 --B o d y   --
 --  --
---  Copyright (C) 1992-2011, Free Software Foundation, Inc. --
+--  Copyright (C) 1992-2012, 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- --
@@ -197,6 +197,11 @@
Write_Switch_Char (eG);
Write_Line (Generate preprocessed source);
 
+   --  Line for -gnatei switch
+
+   Write_Switch_Char (einn);
+   Write_Line (Set maximumum number of instantiations to nn);
+
--  Line for -gnateI switch
 
Write_Switch_Char (eInn);
Index: sem_ch12.adb
===
--- sem_ch12.adb(revision 185417)
+++ sem_ch12.adb(working copy)
@@ -34,7 +34,6 @@
 with Fname;use Fname;
 with Fname.UF; use Fname.UF;
 with Freeze;   use Freeze;
-with Hostparm;
 with Itypes;   use Itypes;
 with Lib;  use Lib;
 with Lib.Load; use Lib.Load;
@@ -3784,8 +3783,10 @@
 --  Here is a defence against a ludicrous number of instantiations
 --  caused by a circular set of instantiation attempts.
 
-if Pending_Instantiations.Last  Hostparm.Max_Instantiations then
-   Error_Msg_N (too many instantiations, N);
+if Pending_Instantiations.Last  Maximum_Instantiations then
+   Error_Msg_Uint_1 := UI_From_Int (Maximum_Instantiations);
+   Error_Msg_N (too many instantiations, exceeds max of^, N);
+   

[Ada] Add unit file name for subunits in Alfa section of ALI file

2012-03-15 Thread Arnaud Charlet
The unit file name is needed when processing Alfa references from subunits,
in the formal verification backend of GNAT. Thus, add the unit file name
information for subunits in the line of the Alfa section that gives the
subunit file name.

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

2012-03-15  Yannick Moy  m...@adacore.com

* alfa.ads Update the decription of ALI sections.
(Alfa_File_Record): Add a component Unit_File_Name to store the
unit file name for subunits.
* get_alfa.adb, put_alfa.adb Adapt to the possible presence of
a unit file name.
* lib-xref-alfa.adb (Add_Alfa_File): For subunits, retrieve the
file name of the unit.

Index: alfa.ads
===
--- alfa.ads(revision 185390)
+++ alfa.ads(working copy)
@@ -6,7 +6,7 @@
 --  --
 -- S p e c  --
 --  --
--- Copyright (C) 2011, Free Software Foundation, Inc.   --
+--  Copyright (C) 2011-2012, 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- --
@@ -70,7 +70,7 @@
--  subprogram declaration and body, when both present, define two different
--  scopes.
 
-   --FD dependency-number filename
+   --FD dependency-number filename (- unit-filename)?
 
--  This header precedes scope information for the unit identified by
--  dependency number and file name. The dependency number is the index
@@ -89,6 +89,8 @@
--  reading of the Alfa information, and means that the Alfa information
--  can stand on its own without needing other parts of the ALI file.
 
+   --  The optional unit filename is given only for subunits.
+
--FS . scope line type col entity (- spec-file . spec-scope)?
 
--  (The ? mark stands for an optional entry in the syntax)
@@ -314,6 +316,10 @@
   File_Name : String_Ptr;
   --  Pointer to file name in ALI file
 
+  Unit_File_Name : String_Ptr;
+  --  Pointer to file name for unit in ALI file, when File_Name refers to a
+  --  subunit. Otherwise null.
+
   File_Num : Nat;
   --  Dependency number in ALI file
 
Index: put_alfa.adb
===
--- put_alfa.adb(revision 185390)
+++ put_alfa.adb(working copy)
@@ -6,7 +6,7 @@
 --  --
 -- B o d y  --
 --  --
--- Copyright (C) 2011, Free Software Foundation, Inc.   --
+--  Copyright (C) 2011-2012, 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- --
@@ -49,6 +49,18 @@
 Write_Info_Char (F.File_Name (N));
  end loop;
 
+ --  If file is a subunit, print the file name for the unit
+
+ if F.Unit_File_Name /= null then
+Write_Info_Char (' ');
+Write_Info_Char ('-');
+Write_Info_Char ('');
+Write_Info_Char (' ');
+for N in F.Unit_File_Name'Range loop
+   Write_Info_Char (F.Unit_File_Name (N));
+end loop;
+ end if;
+
  Write_Info_Terminate;
 
  --  Loop through scope entries for this file
Index: lib-xref-alfa.adb
===
--- lib-xref-alfa.adb   (revision 185390)
+++ lib-xref-alfa.adb   (working copy)
@@ -6,7 +6,7 @@
 --  --
 -- B o d y  --
 --  --
--- Copyright (C) 2011, Free Software Foundation, Inc.   --
+--  Copyright (C) 2011-2012, 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- --
@@ -214,6 +214,8 @@
 
   S : constant Source_File_Index := Source_Index (U);
 
+  File_Name, Unit_File_Name : String_Ptr;
+
begin
   --  Source file 

[Ada] Remove redundant warning on function postcondition not mentioning 'Result

2012-03-15 Thread Arnaud Charlet
When all function postconditions and contract-cases get a warning for only
referring to pre-state, there is no need to issue another warning for not
mentioning 'Result. This is in particular the case when there is a single
postcondition.

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

2012-03-15  Yannick Moy  m...@adacore.com

* sem_ch6.adb (Check_Subprogram_Contract): Do
not issue warning on missing 'Result in postcondition if all
postconditions and contract-cases already get a warning for only
referring to pre-state.

Index: sem_ch6.adb
===
--- sem_ch6.adb (revision 185421)
+++ sem_ch6.adb (working copy)
@@ -6937,6 +6937,10 @@
   Attribute_Result_Mentioned : Boolean := False;
   --  Whether attribute 'Result is mentioned in a postcondition
 
+  No_Warning_On_Some_Postcondition : Boolean := False;
+  --  Whether there exists a postcondition or a contract-case without a
+  --  corresponding warning.
+
   Post_State_Mentioned : Boolean := False;
   --  Whether some expression mentioned in a postcondition can have a
   --  different value in the post-state than in the pre-state.
@@ -7081,7 +7085,9 @@
Post_State_Mentioned := False;
Ignored := Find_Post_State (Arg);
 
-   if not Post_State_Mentioned then
+   if Post_State_Mentioned then
+  No_Warning_On_Some_Postcondition := True;
+   else
   Error_Msg_N (?`Ensures` component refers only to pre-state,
Prag);
end if;
@@ -7133,7 +7139,9 @@
   Post_State_Mentioned := False;
   Ignored := Find_Post_State (Arg);
 
-  if not Post_State_Mentioned then
+  if Post_State_Mentioned then
+ No_Warning_On_Some_Postcondition := True;
+  else
  Error_Msg_N
(?postcondition refers only to pre-state, Prag);
   end if;
@@ -7177,12 +7185,15 @@
   end if;
 
   --  Issue warning for functions whose postcondition does not mention
-  --  'Result after all postconditions have been processed.
+  --  'Result after all postconditions have been processed, and provided
+  --  all postconditions do not already get a warning that they only refer
+  --  to pre-state.
 
   if Ekind_In (Spec_Id, E_Function, E_Generic_Function)
 and then (Present (Last_Postcondition)
or else Present (Last_Contract_Case))
 and then not Attribute_Result_Mentioned
+and then No_Warning_On_Some_Postcondition
   then
  if Present (Last_Postcondition) then
 if Present (Last_Contract_Case) then


[Ada] Indirect calls in static elaboration model

2012-03-15 Thread Arnaud Charlet
This patch makes the static elaboration model more conservative in the case of
indirect calls, by treating Subp'Access as a call for elaboration purposes.

The following test should print 3, even when compiled with the binder switch
-p, which enables pessimistic (worst-case) elaboration order.

gnatmake -f a4 -bargs -p

Expected output:

warning: use of -p switch questionable
warning: since all units compiled with static elaboration model
 3

package a1 is
   function f return Integer;
end a1;

with a2;
package body a1 is
   function f return integer is
   begin
  return a2.f;
   end;
end a1;

package a2 is
   function f return Integer;
end a2;

package body a2 is
   function Ident (X : Integer) return Integer is
   begin
  return X;
   end;

   Var : Integer := Ident (3);

   function f return Integer is
   begin
  return Var;
   end f;
end a2;

with a1;
package a3 is
   type P is access function return Integer;
   PP : P := a1.f'Access;
   R  : Integer := PP.all;
end a3;

with a3;
with Text_IO; use Text_IO;
procedure a4 is
begin
   Put_Line (a3.R'Img);
end;

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

2012-03-15  Bob Duff  d...@adacore.com

* debug.adb: Add new debug switch -gnatd.U, which disables the
support added below, in case someone trips over a cycle, and needs
to disable this.
* sem_attr.adb (Analyze_Access_Attribute):
Treat Subp'Access as a call for elaboration purposes.
* sem_elab.ads, sem_elab.adb (Check_Elab_Call): Add support
for Subp'Access.

Index: debug.adb
===
--- debug.adb   (revision 185390)
+++ debug.adb   (working copy)
@@ -138,7 +138,7 @@
--  d.R
--  d.S  Force Optimize_Alignment (Space)
--  d.T  Force Optimize_Alignment (Time)
-   --  d.U
+   --  d.U  Ignore indirect calls for static elaboration
--  d.V
--  d.W  Print out debugging information for Walk_Library_Items
--  d.X  Use Expression_With_Actions
@@ -642,6 +642,12 @@
 
--  d.T  Force Optimize_Alignment (Time) mode as the default
 
+   --  d.U  Ignore indirect calls for static elaboration. The static
+   --   elaboration model is conservative, especially regarding indirect
+   --   calls. If you say Proc'Access, it will assume you might call
+   --   Proc. This can cause elaboration cycles at bind time. This flag
+   --   reverts to the behavior of earlier compilers.
+
--  d.W  Print out debugging information for Walk_Library_Items, including
--   the order in which units are walked. This is primarily for use in
--   debugging CodePeer mode.
Index: sem_attr.adb
===
--- sem_attr.adb(revision 185420)
+++ sem_attr.adb(working copy)
@@ -28,6 +28,7 @@
 with Atree;use Atree;
 with Casing;   use Casing;
 with Checks;   use Checks;
+with Debug;use Debug;
 with Einfo;use Einfo;
 with Errout;   use Errout;
 with Eval_Fat;
@@ -54,6 +55,7 @@
 with Sem_Ch10; use Sem_Ch10;
 with Sem_Dim;  use Sem_Dim;
 with Sem_Dist; use Sem_Dist;
+with Sem_Elab; use Sem_Elab;
 with Sem_Elim; use Sem_Elim;
 with Sem_Eval; use Sem_Eval;
 with Sem_Res;  use Sem_Res;
@@ -644,6 +646,13 @@
Kill_Current_Values;
 end if;
 
+--  Treat as call for elaboration purposes and we are all
+--  done. Suppress this treatment under debug flag.
+
+if not Debug_Flag_Dot_UU then
+   Check_Elab_Call (N);
+end if;
+
 return;
 
  --  Component is an operation of a protected type
Index: sem_elab.adb
===
--- sem_elab.adb(revision 185390)
+++ sem_elab.adb(working copy)
@@ -6,7 +6,7 @@
 --  --
 -- B o d y  --
 --  --
---  Copyright (C) 1997-2011, Free Software Foundation, Inc. --
+--  Copyright (C) 1997-2012, 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- --
@@ -180,7 +180,7 @@
   Inter_Unit_Only   : Boolean;
   Generate_Warnings : Boolean := True;
   In_Init_Proc  : Boolean := False);
-   --  This is the internal recursive routine that is called to check for a
+   --  This is the internal recursive routine that is called to check for
--  possible elaboration error. The argument N is a subprogram call or
--  generic instantiation to be checked, and E is the entity of the called
--  subprogram, or instantiated generic unit. The 

Re: [Patch/cfgexpand]: also consider assembler_name to call expand_main_function

2012-03-15 Thread Richard Guenther
On Wed, 14 Mar 2012, Tristan Gingold wrote:

 
 On Mar 14, 2012, at 5:08 PM, Richard Guenther wrote:
 
  On Wed, 14 Mar 2012, Tristan Gingold wrote:
  
  Hi,
  
  the code to call expand_main_function currently only checks DECL_NAME.  
  This leads
  to a hack in ada/gcc-interface/utils.c to handle the gnatbind generated 
  file that could
  declare:
  
  package ada_main is
  …
function my_main
  (argc : Integer;
   argv : System.Address;
   envp : System.Address)
   return Integer;
pragma Export (C, my_main, main);
  …
  end ada_main;
  
  But expand_main_function is also called for function whose name is main 
  but assembly name isn't.  Eg:
  
  package pkg is
procedure main;
  end pkg;
  
  So I think we should consider the assembler name is set, otherwise the 
  decl name.
  
  Manually tested on ia64-hp-openvms (where this issue was discovered).
  No C regressions for x86_64-darwin.
  
  Ok for trunk ?
  
  There are more checks for MAIN_NAME_P, so this certainly isn't enough.
  And if it is a good idea then the whole check, whether a FUNCTION_DECL
  is considered 'main' should be put into a function in tree.[ch] and
  used everywhere.  Note that what is 'main' is controlled by
  main_identifier_node, controlled by frontends.  So - why is that not
  enough to control for Ada?
 
 Indeed, I think we could handle this issue in gigi for Ada.  (I also think
 we don't want to handle crazy C code such as 'int my_main () asm (main)'.
 
 But, unless I missed something, doing this in gigi won't work with LTO.

Well.  To make this work in LTO the main function (thus, the program
entry point) should be marked at cgraph level and all users of
MAIN_NAME_P should instead check a flag on the cgraph node.

 Will write a predicate in tree.[ch].

Please instead transition main-ness to the cgraph.

Thanks,
Richard.

[Patch, Fortran] PR52585 - Fix ASSOCIATE with proc-pointer dummies

2012-03-15 Thread Tobias Burnus
A rather obvious patch: With proc-pointer dummies, one compared the 
address of the pointer and not of the pointer target.


Build and regtested on x86-64-linux.
OK for the trunk? (What's the sentiment regarding backporting to 4.7.1?)

Tobias

PS: The patch looks larger than it is: I converted some spaces into tabs.
2012-03-15  Tobias Burnus  bur...@net-b.de

	PR fortran/52585
	* trans-intrinsic.c (gfc_conv_associated): Fix handling of
	procpointer dummy arguments.

2012-03-15  Tobias Burnus  bur...@net-b.de

	PR fortran/52585
	* gfortran.dg/proc_ptr_36.f90: New.

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index ac9f507..2ec97c2 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -5761,10 +5787,14 @@ gfc_conv_associated (gfc_se *se, gfc_expr *expr)
   /* No optional target.  */
   if (ss1 == gfc_ss_terminator)
 {
-  /* A pointer to a scalar.  */
-  arg1se.want_pointer = 1;
-  gfc_conv_expr (arg1se, arg1-expr);
-  tmp2 = arg1se.expr;
+	  /* A pointer to a scalar.  */
+	  arg1se.want_pointer = 1;
+	  gfc_conv_expr (arg1se, arg1-expr);
+	  if (arg1-expr-symtree-n.sym-attr.proc_pointer
+	   arg1-expr-symtree-n.sym-attr.dummy)
+	arg1se.expr = build_fold_indirect_ref_loc (input_location,
+		   arg1se.expr);
+	  tmp2 = arg1se.expr;
 }
   else
 {
@@ -5794,12 +5824,21 @@ gfc_conv_associated (gfc_se *se, gfc_expr *expr)
 
   if (ss1 == gfc_ss_terminator)
 {
-  /* A pointer to a scalar.  */
-  gcc_assert (ss2 == gfc_ss_terminator);
-  arg1se.want_pointer = 1;
-  gfc_conv_expr (arg1se, arg1-expr);
-  arg2se.want_pointer = 1;
-  gfc_conv_expr (arg2se, arg2-expr);
+	  /* A pointer to a scalar.  */
+	  gcc_assert (ss2 == gfc_ss_terminator);
+	  arg1se.want_pointer = 1;
+	  gfc_conv_expr (arg1se, arg1-expr);
+	  if (arg1-expr-symtree-n.sym-attr.proc_pointer
+	   arg1-expr-symtree-n.sym-attr.dummy)
+	arg1se.expr = build_fold_indirect_ref_loc (input_location,
+		   arg1se.expr);
+
+	  arg2se.want_pointer = 1;
+	  gfc_conv_expr (arg2se, arg2-expr);
+	  if (arg2-expr-symtree-n.sym-attr.proc_pointer
+	   arg2-expr-symtree-n.sym-attr.dummy)
+	arg2se.expr = build_fold_indirect_ref_loc (input_location,
+		   arg2se.expr);
 	  gfc_add_block_to_block (se-pre, arg1se.pre);
 	  gfc_add_block_to_block (se-post, arg1se.post);
   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
--- /dev/null	2012-03-15 07:05:00.651809558 +0100
+++ /home/tob/projects/gcc-git/gcc/gcc/testsuite/gfortran.dg/proc_ptr_36.f90	2012-03-15 11:34:46.0 +0100
@@ -0,0 +1,48 @@
+! { dg-do run }
+!
+! PR fortran/52585
+!
+! Test proc-pointer dummies with ASSOCIATE
+!
+! Contributed by Mat Cross of NAG
+!
+module m0
+  abstract interface
+subroutine sub
+end subroutine sub
+  end interface
+  interface
+subroutine s(ss, isassoc)
+  import sub
+  logical :: isassoc
+  procedure(sub), pointer, intent(in) :: ss
+end subroutine s
+  end interface
+end module m0
+
+use m0, only : sub, s
+procedure(sub) :: sub2, pp
+pointer :: pp
+pp = sub2
+if (.not. associated(pp)) call abort ()
+if (.not. associated(pp,sub2)) call abort ()
+call s(pp, .true.)
+pp = null()
+if (associated(pp)) call abort ()
+if (associated(pp,sub2)) call abort ()
+call s(pp, .false.)
+end
+
+subroutine s(ss, isassoc)
+  use m0, only : sub
+  logical :: isassoc
+  procedure(sub), pointer, intent(in) :: ss
+  procedure(sub) :: sub2
+  if (isassoc .neqv. associated(ss)) call abort ()
+  if (isassoc .neqv. associated(ss,sub2)) call abort ()
+end subroutine s
+
+subroutine sub2
+end subroutine sub2
+
+! { dg-final { cleanup-modules m0 } }


Re: [PATCH] gfortran testsuite: implicitly cleanup-modules

2012-03-15 Thread Bernhard Reutner-Fischer
On Tue, Mar 13, 2012 at 01:30:29PM -0700, Mike Stump wrote:
On Mar 13, 2012, at 9:38 AM, Bernhard Reutner-Fischer wrote:
 Could some of the testsuite maintainers please eyeball?

I've eyed it, the only thing that stood out was:

-foreach testcase [lsort [glob -nocomplain $srcdir/$subdir/*.F]] {
-if ![runtest_file_p $runtests $testcase] then {
-  continue
-}
-fortran-torture $testcase
-}
-
-foreach testcase [lsort [glob -nocomplain $srcdir/$subdir/*.f90]] {
-if ![runtest_file_p $runtests $testcase] then {
-  continue
-}
-fortran-torture $testcase
-}

which, I hope does what you want.

It replaces a manually unrolled loop with a loop over the
testcase-extensions and works as expected. Or did you mean something
else?

Assuming you like those parts, Ok.

committed as r185430.

Since it touches non-fortran, please watch for and respond to any problems it 
might cause.

Of course, as always.

PS: I saw that the cleanup-tree-dump is also a bit redundant.
When looking at e.g. gcc/testsuite/gcc.dg/pr52578.c one would think that
scan-tree-dump-times might be able to automagically collect which
dumpfiles to cleanup as last step in dg-final.

One could go one step further and even implicitly add the corresponding
dg-options according to the expected scan-tree-dump files although this
might not be worth it iff there are passes that may produce dump-files
different to their pass name (did not look if this is possible). One
would have to strip the pass-number off the dump-file for passes that
are run more than once, too. Just a thought..

Thanks and cheers,


Re: [Patch/cfgexpand]: also consider assembler_name to call expand_main_function

2012-03-15 Thread Tristan Gingold

On Mar 15, 2012, at 10:37 AM, Richard Guenther wrote:

 On Wed, 14 Mar 2012, Tristan Gingold wrote:
 
 
 On Mar 14, 2012, at 5:08 PM, Richard Guenther wrote:
 
 On Wed, 14 Mar 2012, Tristan Gingold wrote:
 
 Hi,
 
 the code to call expand_main_function currently only checks DECL_NAME.  
 This leads
 to a hack in ada/gcc-interface/utils.c to handle the gnatbind generated 
 file that could
 declare:
 
 package ada_main is
 …
  function my_main
(argc : Integer;
 argv : System.Address;
 envp : System.Address)
 return Integer;
  pragma Export (C, my_main, main);
 …
 end ada_main;
 
 But expand_main_function is also called for function whose name is main 
 but assembly name isn't.  Eg:
 
 package pkg is
  procedure main;
 end pkg;
 
 So I think we should consider the assembler name is set, otherwise the 
 decl name.
 
 Manually tested on ia64-hp-openvms (where this issue was discovered).
 No C regressions for x86_64-darwin.
 
 Ok for trunk ?
 
 There are more checks for MAIN_NAME_P, so this certainly isn't enough.
 And if it is a good idea then the whole check, whether a FUNCTION_DECL
 is considered 'main' should be put into a function in tree.[ch] and
 used everywhere.  Note that what is 'main' is controlled by
 main_identifier_node, controlled by frontends.  So - why is that not
 enough to control for Ada?
 
 Indeed, I think we could handle this issue in gigi for Ada.  (I also think
 we don't want to handle crazy C code such as 'int my_main () asm (main)'.
 
 But, unless I missed something, doing this in gigi won't work with LTO.
 
 Well.  To make this work in LTO the main function (thus, the program
 entry point) should be marked at cgraph level and all users of
 MAIN_NAME_P should instead check a flag on the cgraph node.
 
 Will write a predicate in tree.[ch].
 
 Please instead transition main-ness to the graph.

Ok, I will explore this way.

Tristan.



Re: [PATCH] Change VECTOR_CST representation from TREE_LIST to TREE_VEC-like

2012-03-15 Thread Richard Guenther
On Thu, 15 Mar 2012, Richard Guenther wrote:

 
 This removes the use of TREE_LISTs for VECTOR_CSTs and instead employs
 a similar way of storing elements as TREE_VECs.  I copied the
 macro interface bits of the CONSTRUCTOR accesses and did a 1:1 transform
 at most places to not let refactoring errors creep in (well, where 
 possible).  I'm not sure if it's worth omitting the explicit length
 field in favor of using that of the type - at least we are getting
 consistency (no implicit zero elements) here for free.
 
 Bootstrap and regtest on x86_64-unknown-linux-gnu running.  I cannot
 test sparc apart from compiling a cc1, which works.
 
 Ok for the c-common and sparc bits?  Any other comments?

Bootstrapped ok on x86_64-unknown-linux-gnu.  Incremental patch to
fix issues revealed by testing below.

Richard.

Index: gcc/tree.c
===
--- gcc/tree.c.orig 2012-03-15 14:02:31.0 +0100
+++ gcc/tree.c  2012-03-15 13:51:27.0 +0100
@@ -1328,6 +1328,7 @@ build_vector_stat (tree type, tree *vals
   v = ggc_alloc_zone_cleared_tree_node_stat (tree_zone, length PASS_MEM_STAT);
 
   TREE_SET_CODE (v, VECTOR_CST);
+  TREE_CONSTANT (v) = 1;
   TREE_TYPE (v) = type;
 
   /* Iterate through elements and check for overflow.  */
Index: gcc/varasm.c
===
--- gcc/varasm.c.orig   2012-03-15 14:02:31.0 +0100
+++ gcc/varasm.c2012-03-15 13:59:37.0 +0100
@@ -4596,8 +4596,8 @@ output_constant (tree exp, unsigned HOST
 
elt_size = GET_MODE_SIZE (inner);
 
-   thissize = 0;
output_constant (VECTOR_CST_ELT (exp, 0), elt_size, align);
+   thissize = elt_size;
for (i = 1; i  VECTOR_CST_NELTS (exp); ++i)
  {
output_constant (VECTOR_CST_ELT (exp, i), elt_size, nalign);


[PATCH] Fix __builtin_ir{ound,int}{,f,l} expansion (PR middle-end/52592)

2012-03-15 Thread Jakub Jelinek
Hi!

If __builtin_ir{int,ound}{,f,l} expansion through optab fails,
we would end up generating a call to __builtin_ir{int,ound}{,f,l}
function (there is no ir{int,ound}{,f,l} in libm), which is wrong,
we should expand it as (int) lr{int,ound}{,f,l} in that case (similarly
to what we already do with __builtin_{i,l,ll}{ceil,floor}{,f,l}).

This has been reported as a failure to build mplayer on x86_64-linux
as well as a failure to build pulseaudio on s390x-linux.

Fixed thusly, bootstrapped/regtested on x86_64-linux and i686-linux,
ok for trunk and 4.7.0?

2012-03-15  Jakub Jelinek  ja...@redhat.com
Andrew Pinski  apin...@cavium.com

PR middle-end/52592
* builtins.c (expand_builtin_int_roundingfn_2): If expanding
BUILT_IN_IR{INT,OUND}* using optab fails, emit lr{int,ound}*
calls instead of __builtin_ir{int,ound}*.

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

--- gcc/builtins.c.jj   2012-02-12 15:46:32.0 +0100
+++ gcc/builtins.c  2012-03-15 10:20:59.335215596 +0100
@@ -2841,10 +2841,7 @@ expand_builtin_int_roundingfn_2 (tree ex
   tree fndecl = get_callee_fndecl (exp);
   tree arg;
   enum machine_mode mode;
-
-  /* There's no easy way to detect the case we need to set EDOM.  */
-  if (flag_errno_math)
-return NULL_RTX;
+  enum built_in_function fallback_fn = BUILT_IN_NONE;
 
   if (!validate_arglist (exp, REAL_TYPE, VOID_TYPE))
  gcc_unreachable ();
@@ -2854,47 +2851,79 @@ expand_builtin_int_roundingfn_2 (tree ex
   switch (DECL_FUNCTION_CODE (fndecl))
 {
 CASE_FLT_FN (BUILT_IN_IRINT):
+  fallback_fn = BUILT_IN_LRINT;
+  /* FALLTHRU */
 CASE_FLT_FN (BUILT_IN_LRINT):
 CASE_FLT_FN (BUILT_IN_LLRINT):
-  builtin_optab = lrint_optab; break;
+  builtin_optab = lrint_optab;
+  break;
 
 CASE_FLT_FN (BUILT_IN_IROUND):
+  fallback_fn = BUILT_IN_LROUND;
+  /* FALLTHRU */
 CASE_FLT_FN (BUILT_IN_LROUND):
 CASE_FLT_FN (BUILT_IN_LLROUND):
-  builtin_optab = lround_optab; break;
+  builtin_optab = lround_optab;
+  break;
 
 default:
   gcc_unreachable ();
 }
 
+  /* There's no easy way to detect the case we need to set EDOM.  */
+  if (flag_errno_math  fallback_fn == BUILT_IN_NONE)
+return NULL_RTX;
+
   /* Make a suitable register to place result in.  */
   mode = TYPE_MODE (TREE_TYPE (exp));
 
-  target = gen_reg_rtx (mode);
+  /* There's no easy way to detect the case we need to set EDOM.  */
+  if (!flag_errno_math)
+{
+  target = gen_reg_rtx (mode);
 
-  /* Wrap the computation of the argument in a SAVE_EXPR, as we may
- need to expand the argument again.  This way, we will not perform
- side-effects more the once.  */
-  CALL_EXPR_ARG (exp, 0) = arg = builtin_save_expr (arg);
+  /* Wrap the computation of the argument in a SAVE_EXPR, as we may
+need to expand the argument again.  This way, we will not perform
+side-effects more the once.  */
+  CALL_EXPR_ARG (exp, 0) = arg = builtin_save_expr (arg);
+
+  op0 = expand_expr (arg, NULL, VOIDmode, EXPAND_NORMAL);
+
+  start_sequence ();
+
+  if (expand_sfix_optab (target, op0, builtin_optab))
+   {
+ /* Output the entire sequence.  */
+ insns = get_insns ();
+ end_sequence ();
+ emit_insn (insns);
+ return target;
+   }
+
+  /* If we were unable to expand via the builtin, stop the sequence
+(without outputting the insns) and call to the library function
+with the stabilized argument list.  */
+  end_sequence ();
+}
 
-  op0 = expand_expr (arg, NULL, VOIDmode, EXPAND_NORMAL);
+  if (fallback_fn != BUILT_IN_NONE)
+{
+  /* Fall back to rounding to long int.  Use implicit_p 0 - for non-C99
+targets, (int) round (x) should never be transformed into
+BUILT_IN_IROUND and if __builtin_iround is called directly, emit
+a call to lround in the hope that the target provides at least some
+C99 functions.  This should result in the best user experience for
+not full C99 targets.  */
+  tree fallback_fndecl = mathfn_built_in_1 (TREE_TYPE (arg),
+   fallback_fn, 0);
 
-  start_sequence ();
+  exp = build_call_nofold_loc (EXPR_LOCATION (exp),
+  fallback_fndecl, 1, arg);
 
-  if (expand_sfix_optab (target, op0, builtin_optab))
-{
-  /* Output the entire sequence.  */
-  insns = get_insns ();
-  end_sequence ();
-  emit_insn (insns);
-  return target;
+  target = expand_call (exp, NULL_RTX, target == const0_rtx);
+  return convert_to_mode (mode, target, 0);
 }
 
-  /* If we were unable to expand via the builtin, stop the sequence
- (without outputting the insns) and call to the library function
- with the stabilized argument list.  */
-  end_sequence ();
-
   target = expand_call (exp, target, target == const0_rtx);
 
   return target;
--- 

[patch tree-optimization]: Fix for PR 45397 part 2 of 2

2012-03-15 Thread Kai Tietz
Hi,

this is the second part of the patch for this problem.  It adds some
basic simplifications for ==/!=
comparisons for eliminating redudant operands.

It adds the following patterns:
  -X ==/!= Z - X - Z ==/!= 0.
  ~X ==/!= Z ^ X - Z ==/!= ~0
  X ==/!= X - Y - Y == 0
  X ==/!= X + Y - Y == 0
  X ==/!= X ^ Y - Y == 0
  (X - Y) ==/!= (Z - Y) - X ==/!= Z
  (Y - X) ==/!= (Y - Z) - X ==/!= Z
  (X + Y) ==/!= (X + Z) - Y ==/!= Z
  (X + Y) ==/!= (Z + X) - Y ==/!= Z
  (X ^ Y) ==/!= (Z ^ X) - Y ==/!= Z

ChangeLog

2012-03-15  Kai Tietz  kti...@redhat.com

PR tree-optimization/45397
* tree-ssa-forwprop.c (compare_equal_optimized_1): Add
simplification patterns for ==/!= comparison.

2012-03-15  Kai Tietz  kti...@redhat.com

* gcc.dg/tree-ssa/pr45397-2.c: New test.

Regression tested for all languages (including Ada and Obj-C) on
x86_64-unknown-linux-gnu.  Ok for apply?

Regards,
Kai

Index: gcc-trunk/gcc/tree-ssa-forwprop.c
===
--- gcc-trunk.orig/gcc/tree-ssa-forwprop.c
+++ gcc-trunk/gcc/tree-ssa-forwprop.c
@@ -381,6 +381,99 @@ compare_equal_optimize_1 (gimple stmt, e
   || !INTEGRAL_TYPE_P (type_outer))
 return NULL_TREE;

+  /* Simplify -X ==/!= Z - X - Z ==/!= 0.  */
+  if (TREE_CODE (op0) == NEGATE_EXPR
+   !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0))
+   TREE_CODE (op1) == MINUS_EXPR
+   TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 1))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op1, 0),
+   build_zero_cst (TREE_TYPE (op1)));
+
+  /* Simplify X - Z ==/!= -X - Z ==/!= 0.  */
+  if (TREE_CODE (op1) == NEGATE_EXPR
+   !TREE_SIDE_EFFECTS (TREE_OPERAND (op1, 0))
+   TREE_CODE (op0) == MINUS_EXPR
+   TREE_OPERAND (op1, 0) == TREE_OPERAND (op0, 1))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op0, 0),
+   build_zero_cst (TREE_TYPE (op0)));
+
+  /* Simplify ~X ==/!= X ^ Y to Y ==/!= ~0.  */
+  if (TREE_CODE (op0) == BIT_NOT_EXPR
+   !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0))
+   TREE_CODE (op1) == BIT_XOR_EXPR)
+{
+  if (TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 1))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op1, 0),
+   fold_build1 (BIT_NOT_EXPR,
+TREE_TYPE (op1),
+build_zero_cst (TREE_TYPE (op1;
+  if (TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 0))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op1, 1),
+   fold_build1 (BIT_NOT_EXPR,
+TREE_TYPE (op1),
+build_zero_cst (TREE_TYPE (op1;
+}
+
+  /* Simplify X ^ Y ==/!= ~X to Y ==/!= ~0.  */
+  if (TREE_CODE (op1) == BIT_NOT_EXPR
+   !TREE_SIDE_EFFECTS (TREE_OPERAND (op1, 0))
+   TREE_CODE (op0) == BIT_XOR_EXPR)
+{
+  if (TREE_OPERAND (op1, 0) == TREE_OPERAND (op0, 1))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op0, 0),
+   fold_build1 (BIT_NOT_EXPR,
+TREE_TYPE (op0),
+build_zero_cst (TREE_TYPE (op0;
+  if (TREE_OPERAND (op1, 0) == TREE_OPERAND (op0, 0))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op0, 1),
+   fold_build1 (BIT_NOT_EXPR,
+TREE_TYPE (op0),
+build_zero_cst (TREE_TYPE (op0;
+}
+
+  /* For code being +, -, or ^-expression simplify (X code Y) ==/!= (Z code Y)
+ to (X ==/!= Z), and (X code Y) ==/!= (X code Z) to (Y ==/!= Z).  */
+  if (TREE_CODE (op0) == TREE_CODE (op1)
+   (TREE_CODE (op0) == PLUS_EXPR
+  || TREE_CODE (op0) == MINUS_EXPR
+  || TREE_CODE (op0) == BIT_XOR_EXPR))
+{
+  /* Simplify (X code Y) ==/!= (X code Z) to Y ==/!= Z.  */
+  if (TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 0)
+   !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0)))
+   return fold_build2_loc (gimple_location (stmt), code, type,
+   TREE_OPERAND (op0, 1),
+   TREE_OPERAND (op1, 1));
+  /* Simplify (X code Y) ==/!= (Z code X) to Y ==/!= Z, if code isn't
+minus operation.  */
+  if (TREE_CODE (op0) != MINUS_EXPR
+   TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 1)
+   !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0)))
+return fold_build2_loc 

Re: [PATCH] Fix __builtin_ir{ound,int}{,f,l} expansion (PR middle-end/52592)

2012-03-15 Thread Richard Guenther
On Thu, Mar 15, 2012 at 2:06 PM, Jakub Jelinek ja...@redhat.com wrote:
 Hi!

 If __builtin_ir{int,ound}{,f,l} expansion through optab fails,
 we would end up generating a call to __builtin_ir{int,ound}{,f,l}
 function (there is no ir{int,ound}{,f,l} in libm), which is wrong,
 we should expand it as (int) lr{int,ound}{,f,l} in that case (similarly
 to what we already do with __builtin_{i,l,ll}{ceil,floor}{,f,l}).

 This has been reported as a failure to build mplayer on x86_64-linux
 as well as a failure to build pulseaudio on s390x-linux.

 Fixed thusly, bootstrapped/regtested on x86_64-linux and i686-linux,
 ok for trunk and 4.7.0?

Yes.

Thanks,
Richard.

 2012-03-15  Jakub Jelinek  ja...@redhat.com
            Andrew Pinski  apin...@cavium.com

        PR middle-end/52592
        * builtins.c (expand_builtin_int_roundingfn_2): If expanding
        BUILT_IN_IR{INT,OUND}* using optab fails, emit lr{int,ound}*
        calls instead of __builtin_ir{int,ound}*.

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

 --- gcc/builtins.c.jj   2012-02-12 15:46:32.0 +0100
 +++ gcc/builtins.c      2012-03-15 10:20:59.335215596 +0100
 @@ -2841,10 +2841,7 @@ expand_builtin_int_roundingfn_2 (tree ex
   tree fndecl = get_callee_fndecl (exp);
   tree arg;
   enum machine_mode mode;
 -
 -  /* There's no easy way to detect the case we need to set EDOM.  */
 -  if (flag_errno_math)
 -    return NULL_RTX;
 +  enum built_in_function fallback_fn = BUILT_IN_NONE;

   if (!validate_arglist (exp, REAL_TYPE, VOID_TYPE))
      gcc_unreachable ();
 @@ -2854,47 +2851,79 @@ expand_builtin_int_roundingfn_2 (tree ex
   switch (DECL_FUNCTION_CODE (fndecl))
     {
     CASE_FLT_FN (BUILT_IN_IRINT):
 +      fallback_fn = BUILT_IN_LRINT;
 +      /* FALLTHRU */
     CASE_FLT_FN (BUILT_IN_LRINT):
     CASE_FLT_FN (BUILT_IN_LLRINT):
 -      builtin_optab = lrint_optab; break;
 +      builtin_optab = lrint_optab;
 +      break;

     CASE_FLT_FN (BUILT_IN_IROUND):
 +      fallback_fn = BUILT_IN_LROUND;
 +      /* FALLTHRU */
     CASE_FLT_FN (BUILT_IN_LROUND):
     CASE_FLT_FN (BUILT_IN_LLROUND):
 -      builtin_optab = lround_optab; break;
 +      builtin_optab = lround_optab;
 +      break;

     default:
       gcc_unreachable ();
     }

 +  /* There's no easy way to detect the case we need to set EDOM.  */
 +  if (flag_errno_math  fallback_fn == BUILT_IN_NONE)
 +    return NULL_RTX;
 +
   /* Make a suitable register to place result in.  */
   mode = TYPE_MODE (TREE_TYPE (exp));

 -  target = gen_reg_rtx (mode);
 +  /* There's no easy way to detect the case we need to set EDOM.  */
 +  if (!flag_errno_math)
 +    {
 +      target = gen_reg_rtx (mode);

 -  /* Wrap the computation of the argument in a SAVE_EXPR, as we may
 -     need to expand the argument again.  This way, we will not perform
 -     side-effects more the once.  */
 -  CALL_EXPR_ARG (exp, 0) = arg = builtin_save_expr (arg);
 +      /* Wrap the computation of the argument in a SAVE_EXPR, as we may
 +        need to expand the argument again.  This way, we will not perform
 +        side-effects more the once.  */
 +      CALL_EXPR_ARG (exp, 0) = arg = builtin_save_expr (arg);
 +
 +      op0 = expand_expr (arg, NULL, VOIDmode, EXPAND_NORMAL);
 +
 +      start_sequence ();
 +
 +      if (expand_sfix_optab (target, op0, builtin_optab))
 +       {
 +         /* Output the entire sequence.  */
 +         insns = get_insns ();
 +         end_sequence ();
 +         emit_insn (insns);
 +         return target;
 +       }
 +
 +      /* If we were unable to expand via the builtin, stop the sequence
 +        (without outputting the insns) and call to the library function
 +        with the stabilized argument list.  */
 +      end_sequence ();
 +    }

 -  op0 = expand_expr (arg, NULL, VOIDmode, EXPAND_NORMAL);
 +  if (fallback_fn != BUILT_IN_NONE)
 +    {
 +      /* Fall back to rounding to long int.  Use implicit_p 0 - for non-C99
 +        targets, (int) round (x) should never be transformed into
 +        BUILT_IN_IROUND and if __builtin_iround is called directly, emit
 +        a call to lround in the hope that the target provides at least some
 +        C99 functions.  This should result in the best user experience for
 +        not full C99 targets.  */
 +      tree fallback_fndecl = mathfn_built_in_1 (TREE_TYPE (arg),
 +                                               fallback_fn, 0);

 -  start_sequence ();
 +      exp = build_call_nofold_loc (EXPR_LOCATION (exp),
 +                                  fallback_fndecl, 1, arg);

 -  if (expand_sfix_optab (target, op0, builtin_optab))
 -    {
 -      /* Output the entire sequence.  */
 -      insns = get_insns ();
 -      end_sequence ();
 -      emit_insn (insns);
 -      return target;
 +      target = expand_call (exp, NULL_RTX, target == const0_rtx);
 +      return convert_to_mode (mode, target, 0);
     }

 -  /* If we were unable to expand via the builtin, stop the sequence
 -     (without outputting the insns) and call to the 

Re: [patch tree-optimization]: Fix for PR 45397 part 1 of 2

2012-03-15 Thread Richard Guenther
On Thu, Mar 15, 2012 at 2:08 PM, Kai Tietz ktiet...@googlemail.com wrote
 Hi,

 The solution for this PR is a mix out of different issues.  First is
 of course the type-hoisting, but also
 it shows some lacks in simplifications on integer-values, and on equal
 and none-equal
 comparisons.
 The first patch adds to forward-propagation the ability to do type-hoisting
 for some conversion operations and do simplification for inner binary
 operations on it.
 Most important part is here the adjustment of constant integer-values
 in statement-lists
 for a truncation.
 I limited that patch to handle in compare_equal_optimize_1 only
 bitwise-and operations
 inner a truncation-cast.  Of course for bitwise-xor/or operations some
 more simplifications
 are possible.
 This patch just does the type-hoisting part.  In a second patch I add
 to compare_equal_optimize_1
 the ability for further required simplifications for fixing this problem.

This looks like to match unbound pattern sizes and thus does not fit
into the forwprop machinery.  Instead it was suggested elsewhere
that promoting / demoting registers should be done in a separate pass
where you can compute a lattice of used bits and apply a transform
based on that lattice and target information (according to PROMOTE_MODE
for example).

Richard.

 ChangeLog

 2012-03-15  Kai Tietz  kti...@redhat.com

        PR tree-optimization/45397
        * tree-ssa-forwprop.c (compare_equal_optimize_1): New
        function.
        (combine_cond_expr_cond): Use compare_equal_optimize_1
        function.
        (truncate_integers): New function.
        (combine_inner_conversion): Likewise.
        (ssa_forward_propagate_and_combine): Use for conversions
        combine_inner_conversion function.

 2012-03-15  Kai Tietz  kti...@redhat.com

        * gcc.dg/tree-ssa/pr45397-1.c: New testcase.

 Regression tested for all languages (including Ada and Obj-C) on
 x86_64-unknown-linux-gnu.  Ok for apply?

 Regards,
 Kai

 Index: gcc-trunk/gcc/tree-ssa-forwprop.c
 ===
 --- gcc-trunk.orig/gcc/tree-ssa-forwprop.c
 +++ gcc-trunk/gcc/tree-ssa-forwprop.c
 @@ -362,6 +362,150 @@ rhs_to_tree (tree type, gimple stmt)
     gcc_unreachable ();
  }

 +/* This function does simplifications of comparison OP0 ==/!= OP1
 while integral
 +   typed operands
 +   On success new statement's TREE is returned, otherwise NULL_TREE.  */
 +
 +static tree
 +compare_equal_optimize_1 (gimple stmt, enum tree_code code, tree type,
 +                         tree op0, tree op1)
 +{
 +  gimple_stmt_iterator gsi;
 +  tree type_outer;
 +  tree type_inner, op_inner;
 +  tree op1_l, op1_r, tem;
 +  gimple newop;
 +
 +  type_outer = TREE_TYPE (op0);
 +  if ((code != EQ_EXPR  code != NE_EXPR)
 +      || !INTEGRAL_TYPE_P (type_outer))
 +    return NULL_TREE;
 +
 +  /* If OP0 isn't a conversion, then check if OP1 might be one.  If so
 +     swap arguments, otherwise return NULL_TREE.  */
 +  if (!CONVERT_EXPR_P (op0))
 +    {
 +      if (!CONVERT_EXPR_P (op1))
 +        return NULL_TREE;
 +      tem = op0;
 +      op0 = op1;
 +      op1 = tem;
 +    }
 +
 +  op_inner = TREE_OPERAND (op0, 0);
 +  type_inner = TREE_TYPE (op_inner);
 +
 +  /* Operations only apply to integral typed operands of cast.  */
 +  if (!INTEGRAL_TYPE_P (type_inner))
 +    return NULL_TREE;
 +
 +  /* If second operand is also a type-conversion, check that underlying 
 operand
 +     is integral typed.  */
 +  if (CONVERT_EXPR_P (op1)
 +       !INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (op1, 0
 +    return NULL_TREE;
 +
 +  /* Simplify ((type) X ==/!= (type) X) to true/false, if X has no 
 side-effects
 +     and is integral typed.  */
 +  if (CONVERT_EXPR_P (op1)
 +       TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 0)
 +       !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0)))
 +    return fold_convert (type, (code == EQ_EXPR ? boolean_true_node
 +                                               : boolean_false_node));
 +
 +  /* Simplify (type) X ==/!= (type) Y to X ==/!= Y, if types of X and Y are
 +     compatible and type-precision of X is smaller or equal to TYPE's.  */
 +  if (CONVERT_EXPR_P (op1)
 +       TYPE_PRECISION (type_inner) = TYPE_PRECISION (type_outer))
 +    {
 +      tem = TREE_OPERAND (op1, 0);
 +      if (!useless_type_conversion_p (type_inner, TREE_TYPE (tem)))
 +       return NULL_TREE;
 +      return fold_build2_loc (gimple_location (stmt), code, type,
 +                             op_inner, tem);
 +    }
 +
 +  /* Verify that for pattern 'OP0 = (type) X' the type of X is of
 integral kind,
 +     is unsigned, and has smaller or equal precision to type TYPE.  */
 +  if (TYPE_PRECISION (type_inner)  TYPE_PRECISION (type_outer)
 +      || !TYPE_UNSIGNED (type_inner))
 +    return NULL_TREE;
 +
 +  /* Simplify (type) X ==/!= CST to X ==/!= CST' with CST'=(type-of-X) CST.  
 */
 +  if (TREE_CODE (op1) == INTEGER_CST)
 +    {
 +      tree new_cst = fold_convert (type_inner, 

Re: [patch tree-optimization]: Fix for PR 45397 part 2 of 2

2012-03-15 Thread Richard Guenther
On Thu, Mar 15, 2012 at 2:09 PM, Kai Tietz ktiet...@googlemail.com wrote:
 Hi,

 this is the second part of the patch for this problem.  It adds some
 basic simplifications for ==/!=
 comparisons for eliminating redudant operands.

 It adds the following patterns:
  -X ==/!= Z - X - Z ==/!= 0.
  ~X ==/!= Z ^ X - Z ==/!= ~0
  X ==/!= X - Y - Y == 0
  X ==/!= X + Y - Y == 0
  X ==/!= X ^ Y - Y == 0
  (X - Y) ==/!= (Z - Y) - X ==/!= Z
  (Y - X) ==/!= (Y - Z) - X ==/!= Z
  (X + Y) ==/!= (X + Z) - Y ==/!= Z
  (X + Y) ==/!= (Z + X) - Y ==/!= Z
  (X ^ Y) ==/!= (Z ^ X) - Y ==/!= Z

Can you re-base this patch to work without the previous one?  Also
please coordinate with Andrew.  Note that all of these(?) simplifications
are already done by fold_comparison which we could share if you'd split
out the EXPR_P op0/op1 cases with separated operands/code.

Richard.

 ChangeLog

 2012-03-15  Kai Tietz  kti...@redhat.com

        PR tree-optimization/45397
        * tree-ssa-forwprop.c (compare_equal_optimized_1): Add
        simplification patterns for ==/!= comparison.

 2012-03-15  Kai Tietz  kti...@redhat.com

        * gcc.dg/tree-ssa/pr45397-2.c: New test.

 Regression tested for all languages (including Ada and Obj-C) on
 x86_64-unknown-linux-gnu.  Ok for apply?

 Regards,
 Kai

 Index: gcc-trunk/gcc/tree-ssa-forwprop.c
 ===
 --- gcc-trunk.orig/gcc/tree-ssa-forwprop.c
 +++ gcc-trunk/gcc/tree-ssa-forwprop.c
 @@ -381,6 +381,99 @@ compare_equal_optimize_1 (gimple stmt, e
       || !INTEGRAL_TYPE_P (type_outer))
     return NULL_TREE;

 +  /* Simplify -X ==/!= Z - X - Z ==/!= 0.  */
 +  if (TREE_CODE (op0) == NEGATE_EXPR
 +       !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0))
 +       TREE_CODE (op1) == MINUS_EXPR
 +       TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 1))
 +       return fold_build2_loc (gimple_location (stmt), code, type,
 +                               TREE_OPERAND (op1, 0),
 +                               build_zero_cst (TREE_TYPE (op1)));
 +
 +  /* Simplify X - Z ==/!= -X - Z ==/!= 0.  */
 +  if (TREE_CODE (op1) == NEGATE_EXPR
 +       !TREE_SIDE_EFFECTS (TREE_OPERAND (op1, 0))
 +       TREE_CODE (op0) == MINUS_EXPR
 +       TREE_OPERAND (op1, 0) == TREE_OPERAND (op0, 1))
 +       return fold_build2_loc (gimple_location (stmt), code, type,
 +                               TREE_OPERAND (op0, 0),
 +                               build_zero_cst (TREE_TYPE (op0)));
 +
 +  /* Simplify ~X ==/!= X ^ Y to Y ==/!= ~0.  */
 +  if (TREE_CODE (op0) == BIT_NOT_EXPR
 +       !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0))
 +       TREE_CODE (op1) == BIT_XOR_EXPR)
 +    {
 +      if (TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 1))
 +       return fold_build2_loc (gimple_location (stmt), code, type,
 +                               TREE_OPERAND (op1, 0),
 +                               fold_build1 (BIT_NOT_EXPR,
 +                                            TREE_TYPE (op1),
 +                                            build_zero_cst (TREE_TYPE 
 (op1;
 +      if (TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 0))
 +       return fold_build2_loc (gimple_location (stmt), code, type,
 +                               TREE_OPERAND (op1, 1),
 +                               fold_build1 (BIT_NOT_EXPR,
 +                                            TREE_TYPE (op1),
 +                                            build_zero_cst (TREE_TYPE 
 (op1;
 +    }
 +
 +  /* Simplify X ^ Y ==/!= ~X to Y ==/!= ~0.  */
 +  if (TREE_CODE (op1) == BIT_NOT_EXPR
 +       !TREE_SIDE_EFFECTS (TREE_OPERAND (op1, 0))
 +       TREE_CODE (op0) == BIT_XOR_EXPR)
 +    {
 +      if (TREE_OPERAND (op1, 0) == TREE_OPERAND (op0, 1))
 +       return fold_build2_loc (gimple_location (stmt), code, type,
 +                               TREE_OPERAND (op0, 0),
 +                               fold_build1 (BIT_NOT_EXPR,
 +                                            TREE_TYPE (op0),
 +                                            build_zero_cst (TREE_TYPE 
 (op0;
 +      if (TREE_OPERAND (op1, 0) == TREE_OPERAND (op0, 0))
 +       return fold_build2_loc (gimple_location (stmt), code, type,
 +                               TREE_OPERAND (op0, 1),
 +                               fold_build1 (BIT_NOT_EXPR,
 +                                            TREE_TYPE (op0),
 +                                            build_zero_cst (TREE_TYPE 
 (op0;
 +    }
 +
 +  /* For code being +, -, or ^-expression simplify (X code Y) ==/!= (Z code 
 Y)
 +     to (X ==/!= Z), and (X code Y) ==/!= (X code Z) to (Y ==/!= Z).  */
 +  if (TREE_CODE (op0) == TREE_CODE (op1)
 +       (TREE_CODE (op0) == PLUS_EXPR
 +          || TREE_CODE (op0) == MINUS_EXPR
 +          || TREE_CODE (op0) == BIT_XOR_EXPR))
 +    {
 +      /* Simplify (X code Y) ==/!= (X code Z) to Y ==/!= Z.  */
 +      if (TREE_OPERAND (op0, 0) == TREE_OPERAND (op1, 0)
 +           !TREE_SIDE_EFFECTS (TREE_OPERAND (op0, 0)))
 +       return 

Re: [patch tree-optimization]: Fix for PR 45397 part 2 of 2

2012-03-15 Thread Kai Tietz
2012/3/15 Richard Guenther richard.guent...@gmail.com:
 On Thu, Mar 15, 2012 at 2:09 PM, Kai Tietz ktiet...@googlemail.com wrote:
 Hi,

 this is the second part of the patch for this problem.  It adds some
 basic simplifications for ==/!=
 comparisons for eliminating redudant operands.

 It adds the following patterns:
  -X ==/!= Z - X - Z ==/!= 0.
  ~X ==/!= Z ^ X - Z ==/!= ~0
  X ==/!= X - Y - Y == 0
  X ==/!= X + Y - Y == 0
  X ==/!= X ^ Y - Y == 0
  (X - Y) ==/!= (Z - Y) - X ==/!= Z
  (Y - X) ==/!= (Y - Z) - X ==/!= Z
  (X + Y) ==/!= (X + Z) - Y ==/!= Z
  (X + Y) ==/!= (Z + X) - Y ==/!= Z
  (X ^ Y) ==/!= (Z ^ X) - Y ==/!= Z

 Can you re-base this patch to work without the previous one?  Also
 please coordinate with Andrew.  Note that all of these(?) simplifications
 are already done by fold_comparison which we could share if you'd split
 out the EXPR_P op0/op1 cases with separated operands/code.

 Richard.

Hmm, fold_comparison doesn't do the same thing as it checks for
possible overflow.  This is true for comparisons not being ==/!= or
having operands of none-integral-type.  But for ==/!= with integral
typed arguments  the overflow doesn't matter at all.  And exactly this
is what patch implements here.
This optimization of course is just desired in non-AST form, as we
otherwise loose information in FE.  Therefore I didn't added it to
fold_const.

I can rework the patch so that it works without the other one.

Regards,
Kai


Re: [patch tree-optimization]: Fix for PR 45397 part 1 of 2

2012-03-15 Thread Kai Tietz
2012/3/15 Richard Guenther richard.guent...@gmail.com:
 On Thu, Mar 15, 2012 at 2:08 PM, Kai Tietz ktiet...@googlemail.com wrote
 Hi,

 The solution for this PR is a mix out of different issues.  First is
 of course the type-hoisting, but also
 it shows some lacks in simplifications on integer-values, and on equal
 and none-equal
 comparisons.
 The first patch adds to forward-propagation the ability to do type-hoisting
 for some conversion operations and do simplification for inner binary
 operations on it.
 Most important part is here the adjustment of constant integer-values
 in statement-lists
 for a truncation.
 I limited that patch to handle in compare_equal_optimize_1 only
 bitwise-and operations
 inner a truncation-cast.  Of course for bitwise-xor/or operations some
 more simplifications
 are possible.
 This patch just does the type-hoisting part.  In a second patch I add
 to compare_equal_optimize_1
 the ability for further required simplifications for fixing this problem.

 This looks like to match unbound pattern sizes and thus does not fit
 into the forwprop machinery.  Instead it was suggested elsewhere
 that promoting / demoting registers should be done in a separate pass
 where you can compute a lattice of used bits and apply a transform
 based on that lattice and target information (according to PROMOTE_MODE
 for example).

 Richard.

Well, the integer truncation part might be something for a separate
pass.  It could then also take care that within single-use
gimple-statements the integral-constant is always on right-hand-side
of first statement of an +, -, |, ^, , and mul.

But the cast-hoisting code itself is not unbound AFAICS and has fixed
pattern size.

Regards,
Kai


Re: [patch tree-optimization]: Fix for PR 45397 part 1 of 2

2012-03-15 Thread Jakub Jelinek
On Thu, Mar 15, 2012 at 02:53:10PM +0100, Kai Tietz wrote:
  This looks like to match unbound pattern sizes and thus does not fit
  into the forwprop machinery.  Instead it was suggested elsewhere
  that promoting / demoting registers should be done in a separate pass
  where you can compute a lattice of used bits and apply a transform
  based on that lattice and target information (according to PROMOTE_MODE
  for example).
 
 Well, the integer truncation part might be something for a separate
 pass.  It could then also take care that within single-use
 gimple-statements the integral-constant is always on right-hand-side
 of first statement of an +, -, |, ^, , and mul.
 
 But the cast-hoisting code itself is not unbound AFAICS and has fixed
 pattern size.

The type demotion is PR45397/PR47477 among other PRs.
I'd just walk from the narrowing integer conversion stmts recursively
through the def stmts, see if they can be narrowed, note it, and finally if
everything or significant portion of the stmts can be demoted (if not all,
with some narrowing integer conversion stmt inserted), do it all together.

Jakub


Re: [patch tree-optimization]: Fix for PR 45397 part 1 of 2

2012-03-15 Thread Richard Guenther
On Thu, Mar 15, 2012 at 3:00 PM, Jakub Jelinek ja...@redhat.com wrote:
 On Thu, Mar 15, 2012 at 02:53:10PM +0100, Kai Tietz wrote:
  This looks like to match unbound pattern sizes and thus does not fit
  into the forwprop machinery.  Instead it was suggested elsewhere
  that promoting / demoting registers should be done in a separate pass
  where you can compute a lattice of used bits and apply a transform
  based on that lattice and target information (according to PROMOTE_MODE
  for example).

 Well, the integer truncation part might be something for a separate
 pass.  It could then also take care that within single-use
 gimple-statements the integral-constant is always on right-hand-side
 of first statement of an +, -, |, ^, , and mul.

 But the cast-hoisting code itself is not unbound AFAICS and has fixed
 pattern size.

Can you split that part out then please?

 The type demotion is PR45397/PR47477 among other PRs.
 I'd just walk from the narrowing integer conversion stmts recursively
 through the def stmts, see if they can be narrowed, note it, and finally if
 everything or significant portion of the stmts can be demoted (if not all,
 with some narrowing integer conversion stmt inserted), do it all together.

For PROMOTE_MODE targets you'd promote but properly mask out
constants (to make them cheaper to generate, for example).  You'd
also take advantate of targets that can do zero/sign-extending loads
without extra cost (ISTR that's quite important for some SPEC 2k6
benchmark on x86_64).

Richard.

        Jakub


Re: [patch tree-optimization]: Fix for PR 45397 part 2 of 2

2012-03-15 Thread Richard Guenther
On Thu, Mar 15, 2012 at 2:46 PM, Kai Tietz ktiet...@googlemail.com wrote:
 2012/3/15 Richard Guenther richard.guent...@gmail.com:
 On Thu, Mar 15, 2012 at 2:09 PM, Kai Tietz ktiet...@googlemail.com wrote:
 Hi,

 this is the second part of the patch for this problem.  It adds some
 basic simplifications for ==/!=
 comparisons for eliminating redudant operands.

 It adds the following patterns:
  -X ==/!= Z - X - Z ==/!= 0.
  ~X ==/!= Z ^ X - Z ==/!= ~0
  X ==/!= X - Y - Y == 0
  X ==/!= X + Y - Y == 0
  X ==/!= X ^ Y - Y == 0
  (X - Y) ==/!= (Z - Y) - X ==/!= Z
  (Y - X) ==/!= (Y - Z) - X ==/!= Z
  (X + Y) ==/!= (X + Z) - Y ==/!= Z
  (X + Y) ==/!= (Z + X) - Y ==/!= Z
  (X ^ Y) ==/!= (Z ^ X) - Y ==/!= Z

 Can you re-base this patch to work without the previous one?  Also
 please coordinate with Andrew.  Note that all of these(?) simplifications
 are already done by fold_comparison which we could share if you'd split
 out the EXPR_P op0/op1 cases with separated operands/code.

 Richard.

 Hmm, fold_comparison doesn't do the same thing as it checks for
 possible overflow.  This is true for comparisons not being ==/!= or
 having operands of none-integral-type.  But for ==/!= with integral
 typed arguments  the overflow doesn't matter at all.  And exactly this
 is what patch implements here.

fold_comparison does not check for overflow for ==/!=.

 This optimization of course is just desired in non-AST form, as we
 otherwise loose information in FE.  Therefore I didn't added it to
 fold_const.

Which pieces are not already in fold-const btw?  forwprop already
re-constructs trees for the defs of the lhs/rhs of a comparison.

Richard.


 I can rework the patch so that it works without the other one.

 Regards,
 Kai


Re: [PATCH] Change VECTOR_CST representation from TREE_LIST to TREE_VEC-like

2012-03-15 Thread Eric Botcazou
   * config/sparc/sparc.c (sparc_handle_vis_mul8x16): Adjust interface
   and implementation.
   (sparc_fold_builtin): Adjust.

OK modulo:

   /* Multiply the vector elements in ELTS0 to the elements in ELTS1 as
 specified by FNCODE.  All of the elements in ELTS0 and ELTS1 lists must be
 integer !constants.  A tree list with the results of the
 multiplications is stored !to the array *N_ELTS, and each element in
 the list is of INNER_TYPE.  */

 ! static void
 ! sparc_handle_vis_mul8x16 (tree *n_elts, int fncode, tree inner_type,
 !   tree elts0, tree elts1)
   {

The prototype and comment must be adjusted:

/* Multiply the VECTOR_CSTs CST0 and CST1 as specified by FNCODE and put
   the result into the array N_ELTS, whose elements are of INNER_TYPE.  */

static void
sparc_handle_vis_mul8x16 (tree *n_elts, int fncode, tree inner_type,
  tree cst0, tree cst1)

-- 
Eric Botcazou


Re: Remove obsolete IRIX 6.5 support

2012-03-15 Thread Rainer Orth
Ian Lance Taylor i...@google.com writes:

 Rainer Orth r...@cebitec.uni-bielefeld.de writes:

 * I'm removing IRIX-specific parts of libgo.  Given that libgo is
   imported from upstream (and supposed to work or made work on the 4.7
   branch), I don't know if this a good idea.

 Yeah, it's not.  Just send me the mainline patches to libgo rather than
 applying them yourself, I'll apply them to the upstream repository and
 commit to mainline.

Here's the libgo part of the patch.  Given that IRIX 6.5 Go support
remains on the 4.7 branch (and I hope to fix it up sufficiently to be
useful after 4.7.0 is released), I wonder if it's a good idea to apply
it upstream or better handle libgo like the other upstream libraries
(boehm-gc, libffi) which I didn't touch for the removal.

Thanks.
Rainer


2012-03-10  Rainer Orth  r...@cebitec.uni-bielefeld.de

libgo:
* configure.ac (is_irix): Remove.
(mips-sgi-irix6.5*): Don't set OSCFLAGS.
* configure: Regenerate.
* Makefile.am [LIBGO_IS_IRIX]: Remove.
* Makefile.in: Regenerate.
* mksysinfo.sh [__sgi__]: Remove.
(__timespec): Remove.

* go/net/http/cgi/host.go (osDefaultInheritEnv): Remove irix
handling.
* go/syscall/socket_irix.go: Remove.
* go/time/zoneinfo_unix.go (zoneDirs): Remove IRIX 6 support.

diff --git a/libgo/Makefile.am b/libgo/Makefile.am
--- a/libgo/Makefile.am
+++ b/libgo/Makefile.am
@@ -646,12 +646,6 @@ go_net_sock_file = go/net/sock_linux.go
 go_net_sockopt_file = go/net/sockopt_linux.go
 go_net_sockoptip_file = go/net/sockoptip_linux.go
 else
-if LIBGO_IS_IRIX
-go_net_cgo_file = go/net/cgo_linux.go
-go_net_sock_file = go/net/sock_linux.go
-go_net_sockopt_file = go/net/sockopt_linux.go
-go_net_sockoptip_file = go/net/sockoptip_linux.go
-else
 if LIBGO_IS_SOLARIS
 go_net_cgo_file = go/net/cgo_linux.go
 go_net_sock_file = go/net/sock_linux.go
@@ -671,7 +665,6 @@ go_net_sockoptip_file = go/net/sockoptip
 endif
 endif
 endif
-endif
 
 if LIBGO_IS_LINUX
 go_net_sendfile_file = go/net/sendfile_linux.go
@@ -754,9 +747,6 @@ else
 if LIBGO_IS_SOLARIS
 go_os_sys_file = go/os/sys_uname.go
 else
-if LIBGO_IS_IRIX
-go_os_sys_file = go/os/sys_uname.go
-else
 if LIBGO_IS_RTEMS
 go_os_sys_file = go/os/sys_uname.go
 else
@@ -764,7 +754,6 @@ go_os_sys_file = go/os/sys_bsd.go
 endif
 endif
 endif
-endif
 
 if LIBGO_IS_SOLARIS
 go_os_stat_file = go/os/stat_solaris.go
@@ -862,12 +851,8 @@ go_sync_files = \
 if LIBGO_IS_SOLARIS
 go_syslog_file = go/log/syslog/syslog_libc.go
 else
-if LIBGO_IS_IRIX
-go_syslog_file = go/log/syslog/syslog_libc.go
-else
 go_syslog_file = go/log/syslog/syslog_unix.go
 endif
-endif
 
 go_log_syslog_files = \
 	go/log/syslog/syslog.go \
@@ -1464,13 +1449,9 @@ else
 if LIBGO_IS_SOLARIS
 syscall_socket_file = go/syscall/socket_solaris.go
 else
-if LIBGO_IS_IRIX
-syscall_socket_file = go/syscall/socket_irix.go
-else
 syscall_socket_file = go/syscall/socket_bsd.go
 endif
 endif
-endif
 
 # Support for uname.
 if LIBGO_IS_SOLARIS
diff --git a/libgo/configure.ac b/libgo/configure.ac
--- a/libgo/configure.ac
+++ b/libgo/configure.ac
@@ -126,7 +126,6 @@ AC_SUBST(go_include)
 
 is_darwin=no
 is_freebsd=no
-is_irix=no
 is_linux=no
 is_netbsd=no
 is_rtems=no
@@ -135,7 +134,6 @@ GOOS=unknown
 case ${host} in
   *-*-darwin*)   is_darwin=yes;  GOOS=darwin ;;
   *-*-freebsd*)  is_freebsd=yes; GOOS=freebsd ;;
-  *-*-irix6*)is_irix=yes;GOOS=irix ;;
   *-*-linux*)is_linux=yes;   GOOS=linux ;;
   *-*-netbsd*)	 is_netbsd=yes;  GOOS=netbsd ;;
   *-*-rtems*)is_rtems=yes;   GOOS=rtems ;;
@@ -143,7 +141,6 @@ case ${host} in
 esac
 AM_CONDITIONAL(LIBGO_IS_DARWIN, test $is_darwin = yes)
 AM_CONDITIONAL(LIBGO_IS_FREEBSD, test $is_freebsd = yes)
-AM_CONDITIONAL(LIBGO_IS_IRIX, test $is_irix = yes)
 AM_CONDITIONAL(LIBGO_IS_LINUX, test $is_linux = yes)
 AM_CONDITIONAL(LIBGO_IS_NETBSD, test $is_netbsd = yes)
 AM_CONDITIONAL(LIBGO_IS_RTEMS, test $is_rtems = yes)
@@ -285,11 +282,6 @@ AC_SUBST(GO_SYSCALL_OS_ARCH_FILE)
 dnl Special flags used to generate sysinfo.go.
 OSCFLAGS=-D_GNU_SOURCE -D_LARGEFILE_SOURCE -D_FILE_OFFSET_BITS=64
 case $target in
-mips-sgi-irix6.5*)
-	# IRIX 6 needs _XOPEN_SOURCE=500 for the XPG5 version of struct
-	# msghdr in sys/socket.h.
-	OSCFLAGS=$OSCFLAGS -D_XOPEN_SOURCE=500
-	;;
 *-*-solaris2.[[89]])
 	# Solaris 8/9 need this so struct msghdr gets the msg_control
 	# etc. fields in sys/socket.h (_XPG4_2).
diff --git a/libgo/go/net/http/cgi/host.go b/libgo/go/net/http/cgi/host.go
--- a/libgo/go/net/http/cgi/host.go
+++ b/libgo/go/net/http/cgi/host.go
@@ -35,7 +35,6 @@ var osDefaultInheritEnv = map[string][]s
 	darwin:  {DYLD_LIBRARY_PATH},
 	freebsd: {LD_LIBRARY_PATH},
 	hpux:{LD_LIBRARY_PATH, SHLIB_PATH},
-	irix:{LD_LIBRARY_PATH, LD_LIBRARYN32_PATH, LD_LIBRARY64_PATH},
 	linux:   {LD_LIBRARY_PATH},
 	openbsd: {LD_LIBRARY_PATH},
 	solaris: {LD_LIBRARY_PATH, LD_LIBRARY_PATH_32, LD_LIBRARY_PATH_64},
diff --git 

Re: Remove obsolete Solaris 8 support

2012-03-15 Thread Rainer Orth
Ian Lance Taylor i...@google.com writes:

 Rainer Orth r...@cebitec.uni-bielefeld.de writes:

  libgo:
  * configure.ac (OSCFLAGS): Remove *-*-solaris2.8 handling.
  (libgo_cv_lib_makecontext_stack_top): Remove
  sparc*-*-solaris2.8* handling.
  * configure: Regenerate.

 As with the Irix 5 changes, just send the libgo patches to me rather
 than committing them directly to the repository.  Thanks.

Here it is, with the same caveat as for the IRIX 6.5 removal.

Rainer


diff --git a/libgo/configure.ac b/libgo/configure.ac
--- a/libgo/configure.ac
+++ b/libgo/configure.ac
@@ -282,8 +282,8 @@ AC_SUBST(GO_SYSCALL_OS_ARCH_FILE)
 dnl Special flags used to generate sysinfo.go.
 OSCFLAGS=-D_GNU_SOURCE -D_LARGEFILE_SOURCE -D_FILE_OFFSET_BITS=64
 case $target in
-*-*-solaris2.[[89]])
-	# Solaris 8/9 need this so struct msghdr gets the msg_control
+*-*-solaris2.9)
+	# Solaris 9 needs this so struct msghdr gets the msg_control
 	# etc. fields in sys/socket.h (_XPG4_2).
 	OSCFLAGS=$OSCFLAGS -D_XOPEN_SOURCE=500 -D_XOPEN_SOURCE_EXTENDED -D__EXTENSIONS__
 	;;
@@ -623,7 +623,7 @@ fi
 dnl Check if makecontext expects the uc_stack member of ucontext to point
 dnl to the top of the stack.
 case $target in
-  sparc*-*-solaris2.[[89]]*)
+  sparc*-*-solaris2.9*)
 libgo_cv_lib_makecontext_stack_top=yes
 ;;
   *)


-- 
-
Rainer Orth, Center for Biotechnology, Bielefeld University


Re: [patch tree-optimization]: Fix for PR 45397 part 2 of 2

2012-03-15 Thread Kai Tietz
2012/3/15 Richard Guenther richard.guent...@gmail.com:
 On Thu, Mar 15, 2012 at 2:46 PM, Kai Tietz ktiet...@googlemail.com wrote:
 2012/3/15 Richard Guenther richard.guent...@gmail.com:
 On Thu, Mar 15, 2012 at 2:09 PM, Kai Tietz ktiet...@googlemail.com wrote:
 Hi,

 this is the second part of the patch for this problem.  It adds some
 basic simplifications for ==/!=
 comparisons for eliminating redudant operands.

 It adds the following patterns:
  -X ==/!= Z - X - Z ==/!= 0.
  ~X ==/!= Z ^ X - Z ==/!= ~0
  X ==/!= X - Y - Y == 0
  X ==/!= X + Y - Y == 0
  X ==/!= X ^ Y - Y == 0
  (X - Y) ==/!= (Z - Y) - X ==/!= Z
  (Y - X) ==/!= (Y - Z) - X ==/!= Z
  (X + Y) ==/!= (X + Z) - Y ==/!= Z
  (X + Y) ==/!= (Z + X) - Y ==/!= Z
  (X ^ Y) ==/!= (Z ^ X) - Y ==/!= Z

 Can you re-base this patch to work without the previous one?  Also
 please coordinate with Andrew.  Note that all of these(?) simplifications
 are already done by fold_comparison which we could share if you'd split
 out the EXPR_P op0/op1 cases with separated operands/code.

 Richard.

 Hmm, fold_comparison doesn't do the same thing as it checks for
 possible overflow.  This is true for comparisons not being ==/!= or
 having operands of none-integral-type.  But for ==/!= with integral
 typed arguments  the overflow doesn't matter at all.  And exactly this
 is what patch implements here.

 fold_comparison does not check for overflow for ==/!=.

 This optimization of course is just desired in non-AST form, as we
 otherwise loose information in FE.  Therefore I didn't added it to
 fold_const.

 Which pieces are not already in fold-const btw?  forwprop already
 re-constructs trees for the defs of the lhs/rhs of a comparison.

 Richard.

I have tried to use here instead a call to fold_build2 instead, and I
had to notice that it didn't optimized a single case (beside the - and
~ case on both sides).

I see in fold const for example in the pattern 'X +- C1 CMP Y +- C2'
to 'X CMP Y +- C2 +- C1' explicit the check for it.

...
/* Transform comparisons of the form X +- C1 CMP Y +- C2 to
   X CMP Y +- C2 +- C1 for signed X, Y.  This is valid if
   the resulting offset is smaller in absolute value than the
   original one.  */
if (TYPE_OVERFLOW_UNDEFINED (TREE_TYPE (arg0))
 (TREE_CODE (arg0) == PLUS_EXPR || TREE_CODE (arg0) == MINUS_EXPR)
...

The same for pattern X +- C1 CMP C2 to X CMP C2 +- C1.

The cases for '(X + Y) ==/!= (Z + X)' and co have the same issue or
are simply not present.

Sorry fold_const doesn't cover this at all.

Kai


Re: The state of glibc libm

2012-03-15 Thread Uros Bizjak
Hello!

 SSE ABI entries for i?86 in glibc were rejected. ?I proposed them like
 4-5 years ago to make -mfpmath=sse not suck.

 With the new libm hopefully this can be revisited.

 But there's the ABI and there's the internal implementation.

 My point was just that relying on x87 fully again does not really make
 sense anymore in 2012.

 That's true, the return value shuffle to/from the x87 stack might not be
 too bad for performance, nor argument passing on the stack.

Can this issue be solved with alternative function entry points, in
the same way ICC does? This way, we can pass values in SSE, not on the
stack.

Uros.


Re: Remove obsolete Solaris 8 support

2012-03-15 Thread Eric Botcazou
 If we are, we'll never learn if this code is needed on anything beyond
 Solaris 8 and keep this cruft around basically forever.

So what?  This file is a big kludge and there is no value whatsoever in it 
being elegant or particularly readable or even efficient.

 I'll at least try a bootstrap with the nframes = 2 code ripped out with
 Solaris 9 FCS libc and libthread (and of course the whole rest: latest
 Solaris 9, 10 and 11) and see if anything breaks.

To make things clear upfront: I'll oppose any change that removes something.

-- 
Eric Botcazou


struct siginfo vs. siginfo_t (was: GNU C Library master sources branch, master, updated. glibc-2.15-229-g4efeffc)

2012-03-15 Thread Thomas Schwinge
Hi!

On 26 Feb 2012 18:17:52 -, drep...@sourceware.org wrote:
 http://sources.redhat.com/git/gitweb.cgi?p=glibc.git;a=commitdiff;h=4efeffc1d583597e4f52985b9747269e47b754e2
 
 commit 4efeffc1d583597e4f52985b9747269e47b754e2
 Author: Ulrich Drepper drep...@gmail.com
 Date:   Sun Feb 26 13:17:27 2012 -0500
 
 Fix up POSIX testing in conformtest

 [...]
 + * sysdeps/unix/sysv/linux/bits/siginfo.h: Don't name siginfo_t
 + struct.  [...]
 [...]

 diff --git a/sysdeps/unix/sysv/linux/bits/siginfo.h 
 b/sysdeps/unix/sysv/linux/bits/siginfo.h
 index ecef39d..0635e2f 100644
 --- a/sysdeps/unix/sysv/linux/bits/siginfo.h
 +++ b/sysdeps/unix/sysv/linux/bits/siginfo.h
 [...]
 @@ -47,7 +47,7 @@ typedef union sigval
  #  define __SI_PAD_SIZE ((__SI_MAX_SIZE / sizeof (int)) - 3)
  # endif
  
 -typedef struct siginfo
 +typedef struct
{
  int si_signo;/* Signal number.  */
  int si_errno;/* If non-zero, an errno value associated with
 [...]

This change breaks GCC:

In file included from 
/scratch/tschwing/FM_sh-linux-gnu-mk2/src/gcc-mainline/libgcc/unwind-dw2.c:377:0:
./md-unwind-support.h: In function 'sh_fallback_frame_state':
./md-unwind-support.h:182:17: error: field 'info' has incomplete type

In my case, this is really libgcc/config/sh/linux-unwind.h:

[...]
   181struct rt_sigframe {
   182  struct siginfo info;
   183  struct ucontext uc;
   184} *rt_ = context-cfa;
[...]

There are more such cases:

boehm-gc/os_dep.c:#   define SIGINFO_T struct siginfo
libgcc/config/alpha/linux-unwind.h:   struct siginfo info;
libgcc/config/bfin/linux-unwind.h:struct siginfo *pinfo;
libgcc/config/bfin/linux-unwind.h:struct siginfo info;
libgcc/config/i386/linux-unwind.h:struct siginfo *pinfo;
libgcc/config/i386/linux-unwind.h:struct siginfo info;
libgcc/config/ia64/linux-unwind.h:struct siginfo *info;
libgcc/config/ia64/linux-unwind.h:struct siginfo *info;
libgcc/config/mips/linux-unwind.h:struct siginfo info;
libgcc/config/pa/linux-unwind.h:struct siginfo info;
libgcc/config/sh/linux-unwind.h:  struct siginfo *pinfo;
libgcc/config/sh/linux-unwind.h:  struct siginfo info;
libgcc/config/sh/linux-unwind.h:  struct siginfo info;
libgcc/config/tilepro/linux-unwind.h:struct siginfo info;
libgcc/config/xtensa/linux-unwind.h:struct siginfo info;

(Is there really nobody doing nightly testing of GCC against glibc master
branch on x86, which would have shown this earlier?)

Replacing struct siginfo with siginfo_t in sh/linux-unwind.h makes the
build pass.  Is this the desired approach; shall we apply this for all
cases listed above (and submit to Boehm GC upstream)?  I wonder -- if GCC
breaks, how much software out in the wild is going to break once this
glibc change ripples through?


Grüße,
 Thomas


pgpkHs9szr65i.pgp
Description: PGP signature


Re: [google] Add -gfission support to GCC (issue5754090)

2012-03-15 Thread Eric Botcazou
  I wasn't trying to be pompous! It's just our project name, but I
  thought fission to be quite appropriate for what it does. How does
  -gsplit or -gsplit-dwarf work for you?

 Or -gsplit-debug?

-g is already supposed to convey the debug, so I think that -gsplit-dwarf is 
the best proposal (and we already have -gstrict-dwarf for example).  Thanks.

-- 
Eric Botcazou


Re: [Patch, libfortran] RFC: Shared vtables, constification

2012-03-15 Thread Janne Blomqvist
PING! (At this point, obviously for trunk only)

On Mon, Feb 13, 2012 at 20:20, Janne Blomqvist
blomqvist.ja...@gmail.com wrote:
 Hi,

 the attached patch changes the low-level libgfortran IO dispatching
 mechanism to use shared vtables for each stream type, instead of all
 the function pointers being replicated for each unit. This is similar
 to e.g. how the C++ frontend implements vtables. The benefits are:

 - Slightly smaller heap memory overhead for each unit as only the
 vtable pointer needs to be stored, and slightly faster unit
 initialization as only the vtable pointer needs to be setup instead of
 all the function pointers in the stream struct.

 - Looking at unix.o with readelf, one sees

 Relocation section '.rela.data.rel.ro.local.mem_vtable' at offset
 0x15550 contains 8 entries:

 and similarly for the other vtables; according to
 http://www.airs.com/blog/archives/189 this means that after relocation
 the page where this data resides may be marked read-only.

 The downside is that the sizes of the .text and .data sections are
 increased. Before:

   text    data     bss     dec     hex filename
 1116991    6664     592 1124247  112797
 ./x86_64-unknown-linux-gnu/libgfortran/.libs/libgfortran.so

 After:

   text    data     bss     dec     hex filename
 1117487    6936     592 1125015  112a97
 ./x86_64-unknown-linux-gnu/libgfortran/.libs/libgfortran.so


 The data section increase is due to the vtables, the text increase is,
 I guess, due to the extra pointer dereference when calling the IO
 functions.

 Regtested on x86_64-unknown-linux-gnu, Ok for trunk, or 4.8?

 2012-02-13  Janne Blomqvist  j...@gcc.gnu.org

        * io/unix.h (struct stream): Rename to stream_vtable.
        (struct stream): New struct definition.
        (sread): Dereference vtable pointer.
        (swrite): Likewise.
        (sseek): Likewise.
        (struncate): Likewise.
        (sflush): Likewise.
        (sclose): Likewise.
        * io/unix.c (raw_vtable): New variable.
        (buf_vtable): Likewise.
        (mem_vtable): Likewise.
        (mem4_vtable): Likewise.
        (raw_init): Assign vtable pointer.
        (buf_init): Likewise.
        (open_internal): Likewise.
        (open_internal4): Likewise.



 --
 Janne Blomqvist



-- 
Janne Blomqvist


Re: struct siginfo vs. siginfo_t (was: GNU C Library master sources branch, master, updated. glibc-2.15-229-g4efeffc)

2012-03-15 Thread Carlos O'Donell
On Thu, Mar 15, 2012 at 11:05 AM, Thomas Schwinge
tho...@codesourcery.com wrote:
 Hi!

 On 26 Feb 2012 18:17:52 -, drep...@sourceware.org wrote:
 http://sources.redhat.com/git/gitweb.cgi?p=glibc.git;a=commitdiff;h=4efeffc1d583597e4f52985b9747269e47b754e2

 commit 4efeffc1d583597e4f52985b9747269e47b754e2
 Author: Ulrich Drepper drep...@gmail.com
 Date:   Sun Feb 26 13:17:27 2012 -0500

     Fix up POSIX testing in conformtest

 [...]
 +     * sysdeps/unix/sysv/linux/bits/siginfo.h: Don't name siginfo_t
 +     struct.  [...]
 [...]

 diff --git a/sysdeps/unix/sysv/linux/bits/siginfo.h 
 b/sysdeps/unix/sysv/linux/bits/siginfo.h
 index ecef39d..0635e2f 100644
 --- a/sysdeps/unix/sysv/linux/bits/siginfo.h
 +++ b/sysdeps/unix/sysv/linux/bits/siginfo.h
 [...]
 @@ -47,7 +47,7 @@ typedef union sigval
  #  define __SI_PAD_SIZE     ((__SI_MAX_SIZE / sizeof (int)) - 3)
  # endif

 -typedef struct siginfo
 +typedef struct
    {
      int si_signo;            /* Signal number.  */
      int si_errno;            /* If non-zero, an errno value associated with
 [...]

 This change breaks GCC:

    In file included from 
 /scratch/tschwing/FM_sh-linux-gnu-mk2/src/gcc-mainline/libgcc/unwind-dw2.c:377:0:
    ./md-unwind-support.h: In function 'sh_fallback_frame_state':
    ./md-unwind-support.h:182:17: error: field 'info' has incomplete type

 In my case, this is really libgcc/config/sh/linux-unwind.h:

    [...]
       181            struct rt_sigframe {
       182              struct siginfo info;
       183              struct ucontext uc;
       184            } *rt_ = context-cfa;
    [...]

POSIX says you get siginto_t *not* struct siginfo, please fix the code.

 (Is there really nobody doing nightly testing of GCC against glibc master
 branch on x86, which would have shown this earlier?)

I don't test building GCC against glibc master unless I'm making a
potentially ABI breaking change.

We should be rebuilding *all* of userspace when glibc changes. It
would be nice if we setup an OpenEmbedded system to rebuild as much of
x86-64 userspace as possible against a new glibc and check for
regressions.

 Replacing struct siginfo with siginfo_t in sh/linux-unwind.h makes the
 build pass.  Is this the desired approach; shall we apply this for all
 cases listed above (and submit to Boehm GC upstream)?  I wonder -- if GCC
 breaks, how much software out in the wild is going to break once this
 glibc change ripples through?

You can't know until you try building a full distribution.

Cheers,
Carlos.


Re: [PATCH] gfortran testsuite: implicitly cleanup-modules

2012-03-15 Thread Richard Guenther
On Thu, Mar 15, 2012 at 1:39 PM, Bernhard Reutner-Fischer
rep.dot@gmail.com wrote:
 On Tue, Mar 13, 2012 at 01:30:29PM -0700, Mike Stump wrote:
On Mar 13, 2012, at 9:38 AM, Bernhard Reutner-Fischer wrote:
 Could some of the testsuite maintainers please eyeball?

I've eyed it, the only thing that stood out was:

-foreach testcase [lsort [glob -nocomplain $srcdir/$subdir/*.F]] {
-    if ![runtest_file_p $runtests $testcase] then {
-      continue
-    }
-    fortran-torture $testcase
-}
-
-foreach testcase [lsort [glob -nocomplain $srcdir/$subdir/*.f90]] {
-    if ![runtest_file_p $runtests $testcase] then {
-      continue
-    }
-    fortran-torture $testcase
-}

which, I hope does what you want.

 It replaces a manually unrolled loop with a loop over the
 testcase-extensions and works as expected. Or did you mean something
 else?

Assuming you like those parts, Ok.

 committed as r185430.

You forgot to add fortran-modules.exp :(

That breaks final testing result it seems (at least).

Richard.


Since it touches non-fortran, please watch for and respond to any problems it 
might cause.

 Of course, as always.

 PS: I saw that the cleanup-tree-dump is also a bit redundant.
 When looking at e.g. gcc/testsuite/gcc.dg/pr52578.c one would think that
 scan-tree-dump-times might be able to automagically collect which
 dumpfiles to cleanup as last step in dg-final.

 One could go one step further and even implicitly add the corresponding
 dg-options according to the expected scan-tree-dump files although this
 might not be worth it iff there are passes that may produce dump-files
 different to their pass name (did not look if this is possible). One
 would have to strip the pass-number off the dump-file for passes that
 are run more than once, too. Just a thought..

 Thanks and cheers,


Re: The state of glibc libm

2012-03-15 Thread Andi Kleen
Uros Bizjak ubiz...@gmail.com writes:

 Hello!

 SSE ABI entries for i?86 in glibc were rejected. ?I proposed them like
 4-5 years ago to make -mfpmath=sse not suck.

 With the new libm hopefully this can be revisited.

 But there's the ABI and there's the internal implementation.

 My point was just that relying on x87 fully again does not really make
 sense anymore in 2012.

 That's true, the return value shuffle to/from the x87 stack might not be
 too bad for performance, nor argument passing on the stack.

 Can this issue be solved with alternative function entry points, in
 the same way ICC does? This way, we can pass values in SSE, not on the
 stack.

Passing values in SSE is a big win, especially on some CPUs like Atom.

You can just annotate math.h (possibly with different entry names, so that
someone not including it doesn't get totally bogus results)

-Andi

-- 
a...@linux.intel.com -- Speaking for myself only


Re: [doc] GCC 4.7 Solaris updates to install.texi

2012-03-15 Thread Rainer Orth
Gerald Pfeifer ger...@pfeifer.com writes:

 On Mon, 12 Mar 2012, Rainer Orth wrote:
 Tested with make doc/gccinstall.info doc/gccinstall.pdf, ok for mainline
 and 4.7 branch?

 +Sun does not ship a C compiler with Solaris 2 before Solaris 10, though
 +you can download the Sun Studio compilers for free.  In Solaris 10 and
 +11, GCC 3.4.3 is available in @command{/usr/sfw/bin/gcc}.  Solaris 11
 +also provides GCC 4.5.2 in @command{/usr/gcc/4.5/bin/gcc}.  Alternatively,

 I see Richi has approved, just wonder whether as @command would
 be more appropriate than in @command, twice?

I think so.  Ok for mainline and 4.7 branch?

Rainer


2012-03-15  Rainer Orth  r...@cebitec.uni-bielefeld.de

* doc/install.texi (Specific, *-*-solaris2*): Improve wording.

# HG changeset patch
# Parent a1e4c800ecf4ef89c2393b7471ebdf9bbcad40e1
Improve wording in GCC 4.7 Solaris update to install.texi

diff --git a/gcc/doc/install.texi b/gcc/doc/install.texi
--- a/gcc/doc/install.texi
+++ b/gcc/doc/install.texi
@@ -4071,8 +4071,8 @@ been removed in GCC 4.6.
 
 Sun does not ship a C compiler with Solaris 2 before Solaris 10, though
 you can download the Sun Studio compilers for free.  In Solaris 10 and
-11, GCC 3.4.3 is available in @command{/usr/sfw/bin/gcc}.  Solaris 11
-also provides GCC 4.5.2 in @command{/usr/gcc/4.5/bin/gcc}.  Alternatively,
+11, GCC 3.4.3 is available as @command{/usr/sfw/bin/gcc}.  Solaris 11
+also provides GCC 4.5.2 as @command{/usr/gcc/4.5/bin/gcc}.  Alternatively,
 you can install a pre-built GCC to bootstrap and install GCC.  See the
 @uref{binaries.html,,binaries page} for details.
 


-- 
-
Rainer Orth, Center for Biotechnology, Bielefeld University


Re: [PATCH] Fix PRs 52080, 52097 and 48124, rewrite bitfield expansion, enable the C++ memory model wrt bitfields everywhere

2012-03-15 Thread Eric Botcazou
 1. is easy, see patch below.  2. is much harder - we need to
 compute the bit-offset relative to the bitfield group start,
 thus in get_bit_range we do

   /* Compute the adjustment to bitpos from the offset of the field
  relative to the representative.  */
   offset = size_diffop (DECL_FIELD_OFFSET (field),
 DECL_FIELD_OFFSET (repr));
   bitoffset = (tree_low_cst (offset, 1) * BITS_PER_UNIT
+ tree_low_cst (DECL_FIELD_BIT_OFFSET (field), 1)
- tree_low_cst (DECL_FIELD_BIT_OFFSET (repr), 1));

 and we cannot generally assume offset is zero (well, maybe we could
 arrange that though, at least we could assert that for all fields
 in a bitfield group DECL_FIELD_OFFSET is the same?).

I'm skeptical.

 Any suggestion?  Apart from trying to make sure that offset will
 be zero by construction?  Or by simply not handling bitfields
 properly that start at a variable offset?

Computing the offset in stor-layout.c and storing it in DECL_INITIAL?

 The finish_bitfield_representative hunk implements the fix for 1.,
 the rest the proposed zero-by-construction solution for 2.

Thanks!

-- 
Eric Botcazou


Re: struct siginfo vs. siginfo_t (was: GNU C Library master sources branch, master, updated. glibc-2.15-229-g4efeffc)

2012-03-15 Thread H.J. Lu
On Thu, Mar 15, 2012 at 8:57 AM, Carlos O'Donell
car...@systemhalted.org wrote:
 On Thu, Mar 15, 2012 at 11:05 AM, Thomas Schwinge
 tho...@codesourcery.com wrote:
 Hi!

 On 26 Feb 2012 18:17:52 -, drep...@sourceware.org wrote:
 http://sources.redhat.com/git/gitweb.cgi?p=glibc.git;a=commitdiff;h=4efeffc1d583597e4f52985b9747269e47b754e2

 commit 4efeffc1d583597e4f52985b9747269e47b754e2
 Author: Ulrich Drepper drep...@gmail.com
 Date:   Sun Feb 26 13:17:27 2012 -0500

     Fix up POSIX testing in conformtest

 [...]
 +     * sysdeps/unix/sysv/linux/bits/siginfo.h: Don't name siginfo_t
 +     struct.  [...]
 [...]

 diff --git a/sysdeps/unix/sysv/linux/bits/siginfo.h 
 b/sysdeps/unix/sysv/linux/bits/siginfo.h
 index ecef39d..0635e2f 100644
 --- a/sysdeps/unix/sysv/linux/bits/siginfo.h
 +++ b/sysdeps/unix/sysv/linux/bits/siginfo.h
 [...]
 @@ -47,7 +47,7 @@ typedef union sigval
  #  define __SI_PAD_SIZE     ((__SI_MAX_SIZE / sizeof (int)) - 3)
  # endif

 -typedef struct siginfo
 +typedef struct
    {
      int si_signo;            /* Signal number.  */
      int si_errno;            /* If non-zero, an errno value associated with
 [...]

 This change breaks GCC:

    In file included from 
 /scratch/tschwing/FM_sh-linux-gnu-mk2/src/gcc-mainline/libgcc/unwind-dw2.c:377:0:
    ./md-unwind-support.h: In function 'sh_fallback_frame_state':
    ./md-unwind-support.h:182:17: error: field 'info' has incomplete type

 In my case, this is really libgcc/config/sh/linux-unwind.h:

    [...]
       181            struct rt_sigframe {
       182              struct siginfo info;
       183              struct ucontext uc;
       184            } *rt_ = context-cfa;
    [...]

 POSIX says you get siginto_t *not* struct siginfo, please fix the code.


struct siginfo may not work correctly for Linux/x32
and siginfo_t does since siginfo_t has an alignment
attribute, which isn't applied to struct siginfo.


-- 
H.J.


Re: [patch tree-optimization]: Fix for PR 45397 part 1 of 2

2012-03-15 Thread Michael Matz
Hi,

On Thu, 15 Mar 2012, Richard Guenther wrote:

  The type demotion is PR45397/PR47477 among other PRs. I'd just walk 
  from the narrowing integer conversion stmts recursively through the 
  def stmts, see if they can be narrowed, note it, and finally if 
  everything or significant portion of the stmts can be demoted (if not 
  all, with some narrowing integer conversion stmt inserted), do it all 
  together.
 
 For PROMOTE_MODE targets you'd promote but properly mask out
 constants (to make them cheaper to generate, for example).  You'd
 also take advantate of targets that can do zero/sign-extending loads
 without extra cost (ISTR that's quite important for some SPEC 2k6
 benchmark on x86_64).

gamess.  I still have an old proof of concept patch doing type promotion.  
Probably doesn't apply anymore, and it's using too broad predicates (it 
simple-mindedly extends to the largest type see in an expression tree).
But I think that basic idea of it is sound.


Ciao,
Michael.

Index: passes.c
===
--- passes.c(revision 159226)
+++ passes.c(working copy)
@@ -831,6 +831,7 @@ init_optimization_passes (void)
   NEXT_PASS (pass_all_optimizations);
 {
   struct opt_pass **p = pass_all_optimizations.pass.sub;
+  extern struct gimple_opt_pass pass_bprop_extends;
   NEXT_PASS (pass_remove_cgraph_callee_edges);
   /* Initial scalar cleanups before alias computation.
 They ensure memory accesses are not indirect wherever possible.  */
@@ -838,6 +839,7 @@ init_optimization_passes (void)
   NEXT_PASS (pass_update_address_taken);
   NEXT_PASS (pass_rename_ssa_copies);
   NEXT_PASS (pass_complete_unrolli);
+  NEXT_PASS (pass_bprop_extends);
   NEXT_PASS (pass_ccp);
   NEXT_PASS (pass_forwprop);
   NEXT_PASS (pass_call_cdce);
Index: tree-ssa-ccp.c
===
--- tree-ssa-ccp.c  (revision 159226)
+++ tree-ssa-ccp.c  (working copy)
@@ -1999,3 +1999,263 @@ struct gimple_opt_pass pass_fold_builtin
 | TODO_update_ssa  /* todo_flags_finish */
  }
 };
+
+#if 1
+static bool
+promote_through_insn_p (gimple def, tree *prhs1, tree *prhs2)
+{
+  tree lhs, rhs1, rhs2;
+  if (!is_gimple_assign (def))
+return false;
+  lhs = gimple_assign_lhs (def);
+  rhs1 = rhs2 = NULL;
+  switch (gimple_assign_rhs_class (def))
+{
+  case GIMPLE_SINGLE_RHS:
+   rhs1 = gimple_assign_rhs1 (def);
+   if (TREE_CODE (rhs1) != SSA_NAME)
+ return false;
+   break;
+  case GIMPLE_UNARY_RHS:
+   rhs1 = gimple_assign_rhs1 (def);
+   if (TREE_TYPE (gimple_expr_type (def)) != TREE_TYPE (rhs1))
+ return false;
+   break;
+  case GIMPLE_BINARY_RHS:
+   rhs1 = gimple_assign_rhs1 (def);
+   rhs2 = gimple_assign_rhs2 (def);
+
+   switch (gimple_assign_rhs_code (def))
+ {
+   case LSHIFT_EXPR: case RSHIFT_EXPR:
+   case LROTATE_EXPR: case RROTATE_EXPR:
+ rhs2 = NULL;
+ if (TREE_TYPE (lhs) != TREE_TYPE (rhs1))
+   return false;
+ break;
+   case PLUS_EXPR: case MINUS_EXPR:
+   case MULT_EXPR: case EXACT_DIV_EXPR:
+   case TRUNC_DIV_EXPR: case CEIL_DIV_EXPR:
+   case FLOOR_DIV_EXPR: case ROUND_DIV_EXPR:
+   case TRUNC_MOD_EXPR: case CEIL_MOD_EXPR:
+   case FLOOR_MOD_EXPR: case ROUND_MOD_EXPR:
+   case RDIV_EXPR:
+   case MIN_EXPR: case MAX_EXPR:
+   case BIT_IOR_EXPR: case BIT_XOR_EXPR: case BIT_AND_EXPR:
+ if (TREE_TYPE (lhs) != TREE_TYPE (rhs1)
+ || TREE_TYPE (lhs) != TREE_TYPE (rhs2))
+   return false;
+ break;
+   default:
+ return false;
+ }
+   break;
+  default:
+   return false;
+}
+  if (rhs1  TREE_CODE (rhs1) != SSA_NAME)
+rhs1 = NULL;
+  if (prhs1)
+*prhs1 = rhs1;
+  if (rhs2  TREE_CODE (rhs2) != SSA_NAME)
+rhs2 = NULL;
+  if (prhs2)
+*prhs2 = rhs2;
+  return true;
+}
+
+static tree
+get_extended_version (tree newtype, tree name, bool force)
+{
+  tree ret = TREE_CHAIN (name);
+  tree rhs1, rhs2;
+  gimple def;
+  /* If we already have a version of NAME, try to use it.  If it
+ doesn't match in type, fail.  */
+  if (ret)
+{
+  if (TREE_TYPE (ret) == newtype)
+   return ret;
+  else
+   return NULL_TREE;
+}
+  def = SSA_NAME_DEF_STMT (name);
+  /* If we can propagate through our defining insn, try to do that.  */
+  if (promote_through_insn_p (def, rhs1, rhs2))
+{
+  gimple stmt;
+  tree extrhs1, extrhs2;
+  gimple_stmt_iterator gsi;
+  enum tree_code code;
+  if (rhs1)
+   {
+ extrhs1 = get_extended_version (newtype, rhs1, true);
+ if (!extrhs1)
+   /* ??? We could force here.  */
+   return NULL_TREE;
+   }
+  else
+   extrhs1 = 

Re: [ping] Vectorizer patches for 4.8

2012-03-15 Thread Ulrich Weigand
Richard Guenther wrote:
 On Thu, Mar 8, 2012 at 3:56 PM, Ulrich Weigand uweig...@de.ibm.com wrote:
  Ira Rosen posted a couple of vectorizer patches intended for 4.8:
 
  =A0 http://gcc.gnu.org/ml/gcc-patches/2012-02/msg00191.html
  =A0 http://gcc.gnu.org/ml/gcc-patches/2012-02/msg00223.html

  OK to commit the two patches to mainline?
 
 Ok.

I've checked them in now, thanks!

 Who will be able to help with problems with those patches?

I'll do my best to address any issues that may come up ...


Bye,
Ulrich

-- 
  Dr. Ulrich Weigand
  GNU Toolchain for Linux on System z and Cell BE
  ulrich.weig...@de.ibm.com



Re: [PATCH] Fix PRs 52080, 52097 and 48124, rewrite bitfield expansion, enable the C++ memory model wrt bitfields everywhere

2012-03-15 Thread Eric Botcazou
 Computing the offset in stor-layout.c and storing it in DECL_INITIAL?

Ugh.  I just realized that the DECL_BIT_FIELD_REPRESENTATIVE is built during 
layout... but is overloaded with DECL_QUALIFIER.  That's probably the source 
of the miscompilation I talked about earlier.

Can we delay it until after gimplification ?  Then we could use DECL_INITIAL.

-- 
Eric Botcazou


Re: [PATCH] Change VECTOR_CST representation from TREE_LIST to TREE_VEC-like

2012-03-15 Thread Joseph S. Myers
On Thu, 15 Mar 2012, Richard Guenther wrote:

   c-family/
   * c-pretty-print.c (pp_c_initializer_list): Adjust.

The c-family changes are OK.

-- 
Joseph S. Myers
jos...@codesourcery.com


Re: [patch, gcc RFA] dg-extract-results.sh: Handle KFAILs.

2012-03-15 Thread Pedro Alves
On 03/14/2012 08:15 PM, Mike Stump wrote:

 On Mar 14, 2012, at 10:21 AM, Doug Evans wrote:
 The results of running the testsuite in parallel should match the
 results when run serially.  This patch adds KFAIL counts so that happens.
 [There's still a nit that the order of the results don't precisely match,
 but that's a separate issue.]

 I will check this into the gdb tree if there are no objections.
 Any reason not to apply it to the gcc tree as well?
 
 I don't know that the gcc tree has any of the known stuff, though, that's not 
 on purpose or by design, just no one has done it, I think.


Still, kfail is standard DejaGnu, not a GDB invention.  It'd be nice not to
need to fork the script for this.

-- 
Pedro Alves


Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread DJ Delorie

Sigh, libiberty is supposed to be a portability library, not a
kitchen-sink for common stuff.  Should I give up that premise?  Or
should we consider a common dwarf2 helper library, and move even more
of the dwarf2 code into it?

 First, you'll notice that the first constant for a given enum is
 defined using a separate macro name.  I couldn't think of a better
 way to avoid the trailing ',' in an enum warning -- one element
 must be distinguished, so I chose the first.

I typically terminate the list with a FOO_MAX enum, which is going
to need to be handled differently anyway.

 Also, you'll see that the names passed to the macros start with an _.

Beware you're not violating (or causing to violate) some ISO namespace
requirement for identifiers starting with underscores.


Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread Tom Tromey
 DJ == DJ Delorie d...@redhat.com writes:

DJ Sigh, libiberty is supposed to be a portability library, not a
DJ kitchen-sink for common stuff.  Should I give up that premise?  Or
DJ should we consider a common dwarf2 helper library, and move even more
DJ of the dwarf2 code into it?

My reasoning was:

I would have put it somewhere else, but there is nowhere else to put it.
Making a new library for this one file seemed like overkill.
Finally, there is already stuff in libiberty not related to
portability.  E.g., hashtab or the demangler.

Tom First, you'll notice that the first constant for a given enum is
Tom defined using a separate macro name.  I couldn't think of a better
Tom way to avoid the trailing ',' in an enum warning -- one element
Tom must be distinguished, so I chose the first.

DJ I typically terminate the list with a FOO_MAX enum, which is going
DJ to need to be handled differently anyway.

I usually do that to, but I wanted this change not to affect the
contents of the defined enums.

Tom Also, you'll see that the names passed to the macros start with an _.

DJ Beware you're not violating (or causing to violate) some ISO namespace
DJ requirement for identifiers starting with underscores.

Yeah, I didn't consider that.

I guess I can just put the whole DW_TAG_ prefix in there.
That isn't a big deal.  Or if you have some other suggestion, I can
implement it.

Tom


Re: [patch, libffi] Sync merge libffi

2012-03-15 Thread Dominique Dhumieres
Iain,

I have posted at http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg01799.html
the regtests on powerpc-apple-darwin9 with the patch. I still get the following
failures

FAIL: libffi.call/err_bad_abi.c -O0 -W -Wall execution test
FAIL: libffi.call/err_bad_abi.c -O2 execution test
FAIL: libffi.call/err_bad_abi.c -O3 execution test
FAIL: libffi.call/err_bad_abi.c -Os execution test
FAIL: libffi.call/err_bad_abi.c -O2 -fomit-frame-pointer execution test

TIA

Dominique


Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread DJ Delorie

 Finally, there is already stuff in libiberty not related to
 portability.  E.g., hashtab or the demangler.

Yeah, I know, hence my Should I give up that premise?

 I guess I can just put the whole DW_TAG_ prefix in there.  That
 isn't a big deal.  Or if you have some other suggestion, I can
 implement it.

If the macros always prepend something to it, it should be safe
enough, despite technically violating the spirit of the rule.  I have
no other suggestions.

But given you've already had the issue with and, you're already
seeing problems anyway, so maybe that's a sign that it's not actually
safe enough ?


Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread Pedro Alves
On 03/15/2012 06:48 PM, DJ Delorie wrote:

 Finally, there is already stuff in libiberty not related to
  portability.  E.g., hashtab or the demangler.
 Yeah, I know, hence my Should I give up that premise?

Wouldn't it make sense to eventually switch everything to gnulib
for portability instead?  With that in mind, I predict we'll end
up with libiberty composed of only the odd stuff.  :-)

-- 
Pedro Alves


Re: [patch, gcc RFA] dg-extract-results.sh: Handle KFAILs.

2012-03-15 Thread Mike Stump
On Mar 15, 2012, at 11:09 AM, Pedro Alves wrote:
 Still, kfail is standard DejaGnu, not a GDB invention.  It'd be nice not to
 need to fork the script for this.

The change is fine for the gcc tree.


Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread Jakub Jelinek
On Thu, Mar 15, 2012 at 12:41:54PM -0600, Tom Tromey wrote:
 I guess I can just put the whole DW_TAG_ prefix in there.
 That isn't a big deal.  Or if you have some other suggestion, I can
 implement it.

Yeah, I think the either the whole OP_TAG (DW_TAG_foobar, ...), or
OP_TAG (TAG_foobar, ...) would be safer and nicer.

Jakub


[Patch, fortran] Use BUILT_IN_IROUND

2012-03-15 Thread Janne Blomqvist
Hi,

since some time GCC has BUILT_IN_IROUND{F,,L}, similar to lround() and
llround() but the result is returned as an integer. As there is no
corresponding libc function, this builtin is expanded to lround{f,l}
except when -ffast-math is used, in which case it enables slightly
shorter and faster code to be generated inline. Attached patch enables
this builtin in the gfortran frontend. For the testcase

function my_nint(x)
  implicit none
  real :: x
  integer :: my_nint
  my_nint = nint(x)
end function my_nint

compiled with -O2 -ffast-math on x86-64, the difference between the
assembler output of trunk and trunk+patch:

--- iround.trunk.O2fastmath.s   2012-03-15 20:12:40.045069324 +0200
+++ iround.s2012-03-15 20:24:19.501320278 +0200
@@ -12,7 +12,7 @@ my_nint_:
movss   .LC0(%rip), %xmm0
orps%xmm1, %xmm0
addss   %xmm2, %xmm0
-   cvttss2siq  %xmm0, %rax
+   cvttss2si   %xmm0, %eax
ret
.cfi_endproc
 .LFE0:

Comparing the size of the object files, in the patched version the
text section is one byte shorter.

Regtested on x86_64-unknown-linux-gnu, Ok for trunk?

(As an aside, there were some recent problems with __builtin_iround(),
see PR 52592, but they seem to be fixed now so I think this should be
safe)

2012-03-15  Janne Blomqvist  j...@gcc.gnu.org

* f95-lang.c (gfc_init_builtin_functions): Initialize
BUILT_IN_IROUND.
* mathbuiltins.def: Add IROUND.
* trans-intrinsic.c (build_round_expr): Use BUILT_IN_IROUND if
type size matches.
(gfc_build_intrinsic_lib_fndecls): Build iround functions.


-- 
Janne Blomqvist
diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c
index 05b598f..3f28e67 100644
--- a/gcc/fortran/f95-lang.c
+++ b/gcc/fortran/f95-lang.c
@@ -773,7 +773,11 @@ gfc_init_builtin_functions (void)
   gfc_define_builtin (__builtin_fmodf, mfunc_float[1], 
 		  BUILT_IN_FMODF, fmodf, ATTR_CONST_NOTHROW_LEAF_LIST);
 
-  /* lround{f,,l} and llround{f,,l} */
+  /* iround{f,,l}, lround{f,,l} and llround{f,,l} */
+  ftype = build_function_type_list (integer_type_node,
+float_type_node, NULL_TREE); 
+  gfc_define_builtin(__builtin_iroundf, ftype, BUILT_IN_IROUNDF,
+		 iroundf, ATTR_CONST_NOTHROW_LEAF_LIST);
   ftype = build_function_type_list (long_integer_type_node,
 float_type_node, NULL_TREE); 
   gfc_define_builtin (__builtin_lroundf, ftype, BUILT_IN_LROUNDF,
@@ -783,6 +787,10 @@ gfc_init_builtin_functions (void)
   gfc_define_builtin (__builtin_llroundf, ftype, BUILT_IN_LLROUNDF,
 		  llroundf, ATTR_CONST_NOTHROW_LEAF_LIST);
 
+  ftype = build_function_type_list (integer_type_node,
+double_type_node, NULL_TREE); 
+  gfc_define_builtin(__builtin_iround, ftype, BUILT_IN_IROUND,
+		 iround, ATTR_CONST_NOTHROW_LEAF_LIST);
   ftype = build_function_type_list (long_integer_type_node,
 double_type_node, NULL_TREE); 
   gfc_define_builtin (__builtin_lround, ftype, BUILT_IN_LROUND,
@@ -792,6 +800,10 @@ gfc_init_builtin_functions (void)
   gfc_define_builtin (__builtin_llround, ftype, BUILT_IN_LLROUND,
 		  llround, ATTR_CONST_NOTHROW_LEAF_LIST);
 
+  ftype = build_function_type_list (integer_type_node,
+long_double_type_node, NULL_TREE); 
+  gfc_define_builtin(__builtin_iroundl, ftype, BUILT_IN_IROUNDL,
+		 iroundl, ATTR_CONST_NOTHROW_LEAF_LIST);
   ftype = build_function_type_list (long_integer_type_node,
 long_double_type_node, NULL_TREE); 
   gfc_define_builtin (__builtin_lroundl, ftype, BUILT_IN_LROUNDL,
diff --git a/gcc/fortran/mathbuiltins.def b/gcc/fortran/mathbuiltins.def
index b0bcc1f..f6d9586 100644
--- a/gcc/fortran/mathbuiltins.def
+++ b/gcc/fortran/mathbuiltins.def
@@ -64,6 +64,7 @@ OTHER_BUILTIN (FMOD,  fmod,  2,   true)
 OTHER_BUILTIN (FREXP, frexp, frexp,   false)
 OTHER_BUILTIN (LLROUND,   llround,   llround, true)
 OTHER_BUILTIN (LROUND,lround,lround,  true)
+OTHER_BUILTIN (IROUND,	  iround,iround,	true)
 OTHER_BUILTIN (NEXTAFTER, nextafter, 2,   true)
 OTHER_BUILTIN (POW,   pow,   1,   true)
 OTHER_BUILTIN (ROUND, round, 1,   true)
diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index ac9f507..5e54d8e 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -376,28 +376,24 @@ build_round_expr (tree arg, tree restype)
 {
   tree argtype;
   tree fn;
-  bool longlong;
   int argprec, resprec;
 
   argtype = TREE_TYPE (arg);
   argprec = TYPE_PRECISION (argtype);
   resprec = TYPE_PRECISION (restype);
 
-  /* Depending on the type of the result, choose the long int intrinsic
- (lround family) or long long intrinsic (llround).  We might also
- need to convert the result afterwards.  */
-  if (resprec = LONG_TYPE_SIZE)
-

Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread Tom Tromey
 DJ == DJ Delorie d...@redhat.com writes:

Tom Finally, there is already stuff in libiberty not related to
Tom portability.  E.g., hashtab or the demangler.

DJ Yeah, I know, hence my Should I give up that premise?

Yeah.

I am not sure there will ever be enough shared code to warrant a new
library, particularly because adding a new library is so expensive --
not just the configury stuff but also adding it to the link lines in the
Makefiles of all the tools that might need it.

I suppose if I had my wish list implemented here, it would be to remove
the portability stuff from libiberty in favor of gnulib, and keep
libiberty as a higher-level library.

Tom I guess I can just put the whole DW_TAG_ prefix in there.  That
Tom isn't a big deal.  Or if you have some other suggestion, I can
Tom implement it.

DJ If the macros always prepend something to it, it should be safe
DJ enough, despite technically violating the spirit of the rule.  I have
DJ no other suggestions.

DJ But given you've already had the issue with and, you're already
DJ seeing problems anyway, so maybe that's a sign that it's not actually
DJ safe enough ?

I think this arises from a bug in cpp, since it issues the -Wc++-compat
warning even if the token in question is only used as an argument to
stringizing.  This seems mistaken -- but it seemed advisable to work
around it.

Tom


Re: RFA: consolidate DWARF strings into libiberty

2012-03-15 Thread Tom Tromey
 Jakub == Jakub Jelinek ja...@redhat.com writes:

Jakub On Thu, Mar 15, 2012 at 12:41:54PM -0600, Tom Tromey wrote:
 I guess I can just put the whole DW_TAG_ prefix in there.
 That isn't a big deal.  Or if you have some other suggestion, I can
 implement it.

Jakub Yeah, I think the either the whole OP_TAG (DW_TAG_foobar, ...), or
Jakub OP_TAG (TAG_foobar, ...) would be safer and nicer.

Ok, no problem.  I will make that change.

Tom


Re: [patch, libffi] Sync merge libffi

2012-03-15 Thread Iain Sandoe

Hi Dominique,

On 15 Mar 2012, at 18:46, Dominique Dhumieres wrote:

I have posted at http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg01799.html
the regtests on powerpc-apple-darwin9 with the patch. I still get  
the following

failures


thanks - I think the priority is to get this (unwind) patch sorted  
out ...


(Note that I've confirmed with David that the unwind patch is local to  
Darwin, so I will ping that in due course).


---

... I was aware that these (new) tests failed:

FAIL: libffi.call/err_bad_abi.c -O0 -W -Wall execution test
FAIL: libffi.call/err_bad_abi.c -O2 execution test
FAIL: libffi.call/err_bad_abi.c -O3 execution test
FAIL: libffi.call/err_bad_abi.c -Os execution test
FAIL: libffi.call/err_bad_abi.c -O2 -fomit-frame-pointer execution  
test



David Edelsohn was kind enough to point out that a patch for this has  
been posted to libffi-discuss,


http://sourceware.org/ml/libffi-discuss/2012/msg00070.html

unfortunately my schedule is a little hectic right now, and I've not  
had time to try it.


cheers
Iain



Preserve pointer types in ivopts

2012-03-15 Thread Bernd Schmidt
Currently, tree-ssa-loop-ivopts assumes that pointers and integers can
be used interchangeably. It prefers to compute everything in unsigned
integer types rather than pointer types.
On a new target that I'm working on, this assumption is problematic;
casting a pointer to an integer and doing arithmetic on the integer
would be much too expensive to be useful. I came up with the patch
below, which makes ivopts try harder to preserve pointer types.
tree-affine is changed to keep track of base pointers, and do arithmetic
(in particular subtraction) properly if base pointers are involved.

Bootstrapped and regression tested with all languages on i686-linux. I
get FAILs in:

* gcc.dg/guality/pr43051-1.c
  A somewhat contrived testcase; gdb now produces optimized out
  messages which I think is acceptable? In any case I remain to be
  convinced that this testcase demonstrates any real problem.
* gcc.dg/tree-ssa/reassoc-19.c scan-tree-dump-times reassoc2  \+  0
  This seems to fail because we do POINTER_PLUS (ptr, NEG offset))
  rather than (char *)((int)ptr - offset). As far as I can tell this
  is also not a real problem, but I don't know how to adjust the
  testcase.

Comments? Ok?


Bernd
* tree-affine.c (aff_combination_zero): Initialize baseptr.
(aff_combination_add): Handle baseptrs.  Abort if both are set.
(aff_combination_diff): New function.
(tree_to_aff_combination_1): Renamed from tree_to_aff_combination.
Remove code to handle pointers; changed to call itself recursively.
(tree_to_aff_combination): New function.  Handle the pointer cases
formerly found in the function of the same name, and use
tree_to_aff_combination_1 to compute the offsets.
(aff_combination_to_tree): Build a POINTER_PLUS_EXPR around the
offset if the baseptr is nonnull.
* tree-affine.h (struct affine_tree_combination): New member baseptr.
(aff_combination_diff): Declare.
* tree-predcom.c (determine_offset, valid_initialier_p): Use
aff_combination_diff and return false if it fails.
* tree-ssa-loop-ivopts.c (determine_base_object): If an non-pointer
is cast to a pointer, return the cast.
(add_candidate_1): Use sizetype for steps of a pointer-type iv.
(add_old_iv_candidates): Only add a zero-base pointer candidate if
the precision of pointers and sizetype is equal.
(get_computation_aff): Don't convert steps to pointer types.
Ensure pointers are not scaled. Use aff_combination_diff for
subtraction.
(ptr_difference_cost, difference_cost): Use aff_combination_diff and
return infinite_cost if it fails.
(get_loop_invariant_expr_id): Likewise, returning -1 on failure.
(get_computation_cost_at): Fail if bad pointer expressions would be
generated.
(rewrite_use_nonlinear_expr): Use POINTER_PLUS_EXPR if necessary.
* tree-ssa-address.c (addr_to_parts): Look for a baseptr in the
aff_tree.
* tree-ssa-loop-im.c (mem_refs_may_alias_p): Use aff_combination_diff.

testsuite/
* gcc.dg/tree-ssa/loop-4.c: Scan only for real MEMs, not addresses of
them.

Index: gcc/tree-ssa-loop-im.c
===
--- gcc/tree-ssa-loop-im.c  (revision 184938)
+++ gcc/tree-ssa-loop-im.c  (working copy)
@@ -1772,8 +1772,8 @@ mem_refs_may_alias_p (tree mem1, tree me
   get_inner_reference_aff (mem2, off2, size2);
   aff_combination_expand (off1, ttae_cache);
   aff_combination_expand (off2, ttae_cache);
-  aff_combination_scale (off1, double_int_minus_one);
-  aff_combination_add (off2, off1);
+  if (!aff_combination_diff (off2, off1))
+return true;
 
   if (aff_comb_cannot_overlap_p (off2, size1, size2))
 return false;
Index: gcc/testsuite/gcc.dg/tree-ssa/loop-4.c
===
--- gcc/testsuite/gcc.dg/tree-ssa/loop-4.c  (revision 184938)
+++ gcc/testsuite/gcc.dg/tree-ssa/loop-4.c  (working copy)
@@ -37,7 +37,7 @@ void xxx(void)
 
 /* { dg-final { scan-tree-dump-times  \\* \[^\\n\\r\]*= 0 optimized } } */
 /* { dg-final { scan-tree-dump-times \[^\\n\\r\]*= \\*  0 optimized } } */
-/* { dg-final { scan-tree-dump-times MEM 1 optimized } } */
+/* { dg-final { scan-tree-dump-times \[^\]MEM 1 optimized } } */
 
 /* And the original induction variable should be eliminated.  */
 
Index: gcc/tree-ssa-loop-ivopts.c
===
--- gcc/tree-ssa-loop-ivopts.c  (revision 184938)
+++ gcc/tree-ssa-loop-ivopts.c  (working copy)
@@ -879,15 +879,21 @@ static tree
 determine_base_object (tree expr)
 {
   enum tree_code code = TREE_CODE (expr);
+  tree type = TREE_TYPE (expr);
   tree base, obj;
 
   /* If this is a pointer casted to any type, we need to determine
  the base object for the pointer; so handle conversions before
  throwing away 

Re: [PATCH] gfortran testsuite: implicitly cleanup-modules

2012-03-15 Thread Jakub Jelinek
On Thu, Mar 15, 2012 at 05:56:32PM +0100, Bernhard Reutner-Fischer wrote:
 On Thu, Mar 15, 2012 at 04:57:12PM +0100, Richard Guenther wrote:
 On Thu, Mar 15, 2012 at 1:39 PM, Bernhard Reutner-Fischer
 rep.dot@gmail.com wrote:
 
  committed as r185430.
 
 You forgot to add fortran-modules.exp :(
 
 committed as r185439.
 I am very sorry for that..

Even with that file in, libgomp and libitm make check still fail,
can't find fortran-modules.exp.

Jakub


Re: libgo patch RFA: Export {enter,exit}syscall

2012-03-15 Thread Ian Lance Taylor
On Tue, Mar 13, 2012 at 4:01 PM, Ian Lance Taylor i...@google.com wrote:
 The cooperative threading model used by Go works by calling entersyscall
 whenever we are about to make a call to a C function that may block.
 That was not being done for a call to getaddrinfo used when doing a DNS
 lookup.  This patch fixes that problem by exporting the entersyscall and
 exitsyscall functions from the syscall package.  Exporting a function in
 Go is done by naming it with a capital letter, so this patch simply
 consistently renames the entersyscall and exitsyscall functions and all
 their uses.  This will also be useful for SWIG, which faces a similar
 issue.

 Bootstrapped and ran Go testsuite on x86_64-unknown-linux-gnu.
 Committed to mainline.

 OK for 4.7 branch?

Approved for 4.7 by Jakub offline.  Committed to 4.7 branch.

Ian


[PATCH] Use vpermpd instead of vpermq for V4DF AVX2 permutations (PR target/52568)

2012-03-15 Thread Jakub Jelinek
Hi!

This patch let's -mavx2 use vpermpd instead of vpermq for
V4DFmode __builtin_shuffle (e.g. {1, 2, 3, 0}).
Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?

2012-03-15  Jakub Jelinek  ja...@redhat.com

PR target/52568
* config/i386/sse.md (UNSPEC_VPERMDF): Remove.
(avx2_permv4df): Remove.
(avx2_permv4di): Macroize into...
(avx2_permmode): ... this using VI8F_256 iterator.
(avx2_permv4di_1): Macroize into...
(avx2_permmode_1): ... this using VI8F_256 iterator.

--- gcc/config/i386/sse.md.jj   2012-03-14 09:39:41.0 +0100
+++ gcc/config/i386/sse.md  2012-03-15 12:47:56.649703448 +0100
@@ -80,7 +80,6 @@ (define_c_enum unspec [
 
   ;; For AVX2 support
   UNSPEC_VPERMSI
-  UNSPEC_VPERMDF
   UNSPEC_VPERMSF
   UNSPEC_VPERMTI
   UNSPEC_GATHER
@@ -11889,19 +11888,6 @@ (define_insn avx2_permvarv8si
(set_attr prefix vex)
(set_attr mode OI)])
 
-(define_insn avx2_permv4df
-  [(set (match_operand:V4DF 0 register_operand =x)
-   (unspec:V4DF
- [(match_operand:V4DF 1 register_operand xm)
-  (match_operand:SI 2 const_0_to_255_operand n)]
- UNSPEC_VPERMDF))]
-  TARGET_AVX2
-  vpermpd\t{%2, %1, %0|%0, %1, %2}
-  [(set_attr type sselog)
-   (set_attr prefix_extra 1)
-   (set_attr prefix vex)
-   (set_attr mode OI)])
-
 (define_insn avx2_permvarv8sf
   [(set (match_operand:V8SF 0 register_operand =x)
(unspec:V8SF
@@ -11914,25 +11900,25 @@ (define_insn avx2_permvarv8sf
(set_attr prefix vex)
(set_attr mode OI)])
 
-(define_expand avx2_permv4di
-  [(match_operand:V4DI 0 register_operand )
-   (match_operand:V4DI 1 nonimmediate_operand )
+(define_expand avx2_permmode
+  [(match_operand:VI8F_256 0 register_operand )
+   (match_operand:VI8F_256 1 nonimmediate_operand )
(match_operand:SI 2 const_0_to_255_operand )]
   TARGET_AVX2
 {
   int mask = INTVAL (operands[2]);
-  emit_insn (gen_avx2_permv4di_1 (operands[0], operands[1],
- GEN_INT ((mask  0)  3),
- GEN_INT ((mask  2)  3),
- GEN_INT ((mask  4)  3),
- GEN_INT ((mask  6)  3)));
+  emit_insn (gen_avx2_permmode_1 (operands[0], operands[1],
+   GEN_INT ((mask  0)  3),
+   GEN_INT ((mask  2)  3),
+   GEN_INT ((mask  4)  3),
+   GEN_INT ((mask  6)  3)));
   DONE;
 })
 
-(define_insn avx2_permv4di_1
-  [(set (match_operand:V4DI 0 register_operand =x)
-   (vec_select:V4DI
- (match_operand:V4DI 1 nonimmediate_operand xm)
+(define_insn avx2_permmode_1
+  [(set (match_operand:VI8F_256 0 register_operand =x)
+   (vec_select:VI8F_256
+ (match_operand:VI8F_256 1 nonimmediate_operand xm)
  (parallel [(match_operand 2 const_0_to_3_operand )
 (match_operand 3 const_0_to_3_operand )
 (match_operand 4 const_0_to_3_operand )
@@ -11945,11 +11931,11 @@ (define_insn avx2_permv4di_1
   mask |= INTVAL (operands[4])  4;
   mask |= INTVAL (operands[5])  6;
   operands[2] = GEN_INT (mask);
-  return vpermq\t{%2, %1, %0|%0, %1, %2};
+  return vpermssemodesuffix\t{%2, %1, %0|%0, %1, %2};
 }
   [(set_attr type sselog)
(set_attr prefix vex)
-   (set_attr mode OI)])
+   (set_attr mode sseinsnmode)])
 
 (define_insn avx2_permv2ti
   [(set (match_operand:V4DI 0 register_operand =x)

Jakub


[PATCH] Improve AVX V4DF and V8SF permutations (PR target/52568)

2012-03-15 Thread Jakub Jelinek
Hi!

As noted in the PR, we can vectorize e.g. V4DFmode
__builtin_shuffle (, {1, 2, 3, 0}) in 3 insns, some intra-lane
permutation, followed by swapping of the lanes (vperm2f128) and
finally vblend{pd,ps} that merges in the registers with non-swapped
and swapped lanes.

Bootstrapped/regtested on x86_64-linux and i686-linux, tested
additionally with
GCC_TEST_RUN_EXPENSIVE=1 make check-gcc 
RUNTESTFLAGS='--target_board=unix\{-m32/-mavx,-m64/-mavx\} 
dg-torture.exp=vshuf*'
Ok for trunk?

2012-03-15  Jakub Jelinek  ja...@redhat.com

PR target/52568
* config/i386/i386.c (expand_vec_perm_vperm2f128_vblend): New
function.
(ix86_expand_vec_perm_const_1): Use it.

* gcc.dg/torture/vshuf-4.inc: Add two new tests.
* gcc.dg/torture/vshuf-8.inc: Likewise.
* gcc.dg/torture/vshuf-16.inc: Likewise.
* gcc.dg/torture/vshuf-32.inc: Likewise.

--- gcc/config/i386/i386.c.jj   2012-03-14 09:39:41.0 +0100
+++ gcc/config/i386/i386.c  2012-03-15 16:29:05.091015505 +0100
@@ -36627,6 +36627,73 @@ expand_vec_perm_interleave3 (struct expa
   return true;
 }
 
+/* A subroutine of ix86_expand_vec_perm_builtin_1.  Try to implement
+   a single vector permutation using a single intra-lane vector
+   permutation, vperm2f128 swapping the lanes and vblend* insn blending
+   the non-swapped and swapped vectors together.  */
+
+static bool
+expand_vec_perm_vperm2f128_vblend (struct expand_vec_perm_d *d)
+{
+  struct expand_vec_perm_d dfirst, dsecond;
+  unsigned i, j, msk, nelt = d-nelt, nelt2 = nelt / 2;
+  rtx seq;
+  bool ok;
+  rtx (*blend) (rtx, rtx, rtx, rtx) = NULL;
+
+  if (!TARGET_AVX
+  || TARGET_AVX2
+  || (d-vmode != V8SFmode  d-vmode != V4DFmode)
+  || d-op0 != d-op1)
+return false;
+
+  dfirst = *d;
+  for (i = 0; i  nelt; i++)
+dfirst.perm[i] = 0xff;
+  for (i = 0, msk = 0; i  nelt; i++)
+{
+  j = (d-perm[i]  nelt2) ? i | nelt2 : i  ~nelt2;
+  if (dfirst.perm[j] != 0xff  dfirst.perm[j] != d-perm[i])
+   return false;
+  dfirst.perm[j] = d-perm[i];
+  if (j != i)
+   msk |= (1  i);
+}
+  for (i = 0; i  nelt; i++)
+if (dfirst.perm[i] == 0xff)
+  dfirst.perm[i] = i;
+
+  if (!d-testing_p)
+dfirst.target = gen_reg_rtx (dfirst.vmode);
+
+  start_sequence ();
+  ok = expand_vec_perm_1 (dfirst);
+  seq = get_insns ();
+  end_sequence ();
+
+  if (!ok)
+return false;
+
+  if (d-testing_p)
+return true;
+
+  emit_insn (seq);
+
+  dsecond = *d;
+  dsecond.op0 = dfirst.target;
+  dsecond.op1 = dfirst.target;
+  dsecond.target = gen_reg_rtx (dsecond.vmode);
+  for (i = 0; i  nelt; i++)
+dsecond.perm[i] = i ^ nelt2;
+
+  ok = expand_vec_perm_1 (dsecond);
+  gcc_assert (ok);
+
+  blend = d-vmode == V8SFmode ? gen_avx_blendps256 : gen_avx_blendpd256;
+  emit_insn (blend (d-target, dfirst.target, dsecond.target, GEN_INT (msk)));
+  return true;
+}
+
 /* A subroutine of expand_vec_perm_even_odd_1.  Implement the double-word
permutation with two pshufb insns and an ior.  We should have already
failed all two instruction sequences.  */
@@ -37278,6 +37345,9 @@ ix86_expand_vec_perm_const_1 (struct exp
   if (expand_vec_perm_interleave3 (d))
 return true;
 
+  if (expand_vec_perm_vperm2f128_vblend (d))
+return true;
+
   /* Try sequences of four instructions.  */
 
   if (expand_vec_perm_vpshufb2_vpermq (d))
--- gcc/testsuite/gcc.dg/torture/vshuf-4.inc.jj 2011-11-10 18:08:58.0 
+0100
+++ gcc/testsuite/gcc.dg/torture/vshuf-4.inc2012-03-15 16:49:17.796455812 
+0100
@@ -21,7 +21,9 @@ T (17,1, 3, 5, 7) \
 T (18, 3, 3, 3, 3) \
 T (19, 3, 2, 1, 0) \
 T (20, 0, 4, 1, 5) \
-T (21, 2, 6, 3, 7)
+T (21, 2, 6, 3, 7) \
+T (22, 1, 2, 3, 0) \
+T (23, 2, 1, 0, 3)
 #define EXPTESTS \
 T (116,1, 2, 4, 3) \
 T (117,7, 3, 3, 0) \
--- gcc/testsuite/gcc.dg/torture/vshuf-8.inc.jj 2011-11-10 18:08:58.0 
+0100
+++ gcc/testsuite/gcc.dg/torture/vshuf-8.inc2012-03-15 16:50:25.313099258 
+0100
@@ -21,7 +21,9 @@ T (17,1, 3, 5, 7, 9, 11, 13, 15) \
 T (18, 3, 3, 3, 3, 3, 3, 3, 3) \
 T (19, 7, 6, 5, 4, 3, 2, 1, 0) \
 T (20, 0, 8, 1, 9, 2, 10, 3, 11) \
-T (21, 4, 12, 5, 13, 6, 14, 7, 15)
+T (21, 4, 12, 5, 13, 6, 14, 7, 15) \
+T (22, 1, 2, 3, 4, 5, 6, 7, 0) \
+T (23, 6, 5, 4, 3, 2, 1, 0, 7)
 #define EXPTESTS \
 T (116,9, 3, 9, 4, 7, 0, 0, 6) \
 T (117,4, 14, 12, 8, 9, 6, 0, 10) \
--- gcc/testsuite/gcc.dg/torture/vshuf-16.inc.jj2011-11-10 
18:08:58.0 +0100
+++ gcc/testsuite/gcc.dg/torture/vshuf-16.inc   2012-03-15 16:51:15.383835439 
+0100
@@ -21,7 +21,9 @@ T (17,1, 3, 5, 7, 9, 11, 13, 15, 17, 19
 T (18, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3) \
 T (19, 15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0) \
 T (20, 0, 16, 1, 17, 2, 18, 3, 19, 4, 20, 5, 21, 6, 22, 7, 23) \
-T (21, 8, 24, 9, 25, 10, 26, 11, 27, 12, 28, 13, 29, 14, 30, 15, 31)
+T (21, 8, 24, 9, 25, 10, 26, 11, 27, 12, 28, 13, 29, 14, 30, 15, 31) \
+T 

Re: [Patch, fortran] Use BUILT_IN_IROUND

2012-03-15 Thread Tobias Burnus

Janne Blomqvist wrote:

since some time GCC has BUILT_IN_IROUND{F,,L}, similar to lround() and
llround() but the result is returned as an integer.

Regtested on x86_64-unknown-linux-gnu, Ok for trunk?


OK. Thanks for the patch! Nit: Could you check mathbuiltins.def - at 
least in the diff, iround seems to be misaligned (one   missing).


Tobias


2012-03-15  Janne Blomqvistj...@gcc.gnu.org

 * f95-lang.c (gfc_init_builtin_functions): Initialize
 BUILT_IN_IROUND.
 * mathbuiltins.def: Add IROUND.
 * trans-intrinsic.c (build_round_expr): Use BUILT_IN_IROUND if
 type size matches.
 (gfc_build_intrinsic_lib_fndecls): Build iround functions.




Re: [Patch, fortran] Use BUILT_IN_IROUND

2012-03-15 Thread Janne Blomqvist
On Thu, Mar 15, 2012 at 22:14, Tobias Burnus bur...@net-b.de wrote:
 Janne Blomqvist wrote:

 since some time GCC has BUILT_IN_IROUND{F,,L}, similar to lround() and
 llround() but the result is returned as an integer.

 Regtested on x86_64-unknown-linux-gnu, Ok for trunk?


 OK. Thanks for the patch! Nit: Could you check mathbuiltins.def - at least
 in the diff, iround seems to be misaligned (one   missing).

Ah, a tab had sneaked in, fixed. Committed the fixed patch as r185442.
Thanks for the quick review!

-- 
Janne Blomqvist


[wwwdocs] Buildstat update for 4.6

2012-03-15 Thread Tom G. Christensen
Latest results for 4.6.x

-tgc

Testresults for 4.6.2:
  hppa2.0w-hp-hpux11.11
  i386-pc-solaris2.8
  i686-pc-linux-gnu
  powerpc-apple-darwin8.11.0
  sparc-sun-solaris2.8 (2)
  x86_64-apple-darwin10.8.0
  x86_64-apple-darwin11.3.0
  x86_64-unknown-linux-gnu

Testresults for 4.6.2:
  powerpc-ibm-aix5.3.0.0 (2)
  x86_64-unknown-linux-gnu

Index: buildstat.html
===
RCS file: /cvs/gcc/wwwdocs/htdocs/gcc-4.6/buildstat.html,v
retrieving revision 1.9
diff -u -r1.9 buildstat.html
--- buildstat.html  14 Dec 2011 10:57:49 -  1.9
+++ buildstat.html  15 Mar 2012 21:11:11 -
@@ -78,6 +78,7 @@
 tdhppa2.0w-hp-hpux11.11/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg00172.html;4.6.3/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg03199.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-06/msg03306.html;4.6.1/a,
 a href=http://gcc.gnu.org/ml/gcc-testresults/2011-03/msg02630.html;4.6.0/a
@@ -107,6 +108,7 @@
 tdi386-pc-solaris2.8/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg01757.html;4.6.3/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg03286.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-07/msg00139.html;4.6.1/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-04/msg00175.html;4.6.0/a,
@@ -165,6 +167,7 @@
 tdi686-pc-linux-gnu/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg00163.html;4.6.3/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg03395.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg03062.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg00899.html;4.6.1/a,
@@ -203,6 +206,7 @@
 tdpowerpc-apple-darwin8.11.0/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg00497.html;4.6.3/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg03272.html;4.6.2/a,
 a href=http://gcc.gnu.org/ml/gcc-testresults/2011-07/msg01092.html;4.6.1/a
 /td
@@ -218,6 +222,15 @@
 /tr
 
 tr
+tdpowerpc-ibm-aix5.3.0.0/td
+tdnbsp;/td
+tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-02/msg00142.html;4.6.2/a,
+a href=http://gcc.gnu.org/ml/gcc-testresults/2012-02/msg00436.html;4.6.2/a
+/td
+/tr
+
+tr
 tdpowerpc-ibm-aix6.1.0.0/td
 tdnbsp;/td
 tdTest results:
@@ -260,6 +273,8 @@
 tdsparc-sun-solaris2.8/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg01811.html;4.6.3/a,
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg00337.html;4.6.3/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-11/msg01044.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-11/msg00683.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg03536.html;4.6.2/a,
@@ -325,6 +340,7 @@
 tdx86_64-apple-darwin10.8.0/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg01724.html;4.6.3/a,
 a href=http://gcc.gnu.org/ml/gcc-testresults/2011-10/msg02994.html;4.6.2/a
 /td
 /tr
@@ -338,9 +354,19 @@
 /tr
 
 tr
+tdx86_64-apple-darwin11.3.0/td
+tdnbsp;/td
+tdTest results:
+a href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg00118.html;4.6.3/a
+/td
+/tr
+
+tr
 tdx86_64-unknown-linux-gnu/td
 tdnbsp;/td
 tdTest results:
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2012-03/msg01688.html;4.6.3/a,
+a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-12/msg00968.html;4.6.2/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-06/msg03135.html;4.6.1/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-06/msg01380.html;4.6.0/a,
 a 
href=http://gcc.gnu.org/ml/gcc-testresults/2011-05/msg03091.html;4.6.0/a,


C++ PATCH for c++/52582 (ICE with devirtualization on PPC)

2012-03-15 Thread Jason Merrill
jakub and richi analyzed this bug; normally we set DECL_EXTERNAL on all 
functions with vague linkage, but we were failing to do so for the 
synthesized destructor, which caused problems with devirtualization. 
Fixed thus.


Jakub tested the patch.  Applying to trunk; will apply to 4.7 branch 
after 4.7.0.
commit a5e3b73aaee13ed672641faee53989785cffed83
Author: Jason Merrill ja...@redhat.com
Date:   Wed Mar 14 14:24:22 2012 -0400

	PR c++/52582
	* method.c (implicitly_declare_fn): Set DECL_EXTERNAL.

diff --git a/gcc/cp/method.c b/gcc/cp/method.c
index 0718916..0d4793e 100644
--- a/gcc/cp/method.c
+++ b/gcc/cp/method.c
@@ -1593,6 +1593,7 @@ implicitly_declare_fn (special_function_kind kind, tree type, bool const_p)
   DECL_DELETED_FN (fn) = deleted_p;
   DECL_DECLARED_CONSTEXPR_P (fn) = constexpr_p;
 }
+  DECL_EXTERNAL (fn) = true;
   DECL_NOT_REALLY_EXTERN (fn) = 1;
   DECL_DECLARED_INLINE_P (fn) = 1;
   gcc_assert (!TREE_USED (fn));
diff --git a/gcc/testsuite/g++.dg/torture/pr52582.C b/gcc/testsuite/g++.dg/torture/pr52582.C
new file mode 100644
index 000..1b93fc4
--- /dev/null
+++ b/gcc/testsuite/g++.dg/torture/pr52582.C
@@ -0,0 +1,23 @@
+// PR c++/52582
+
+inline void *operator new (__SIZE_TYPE__, void *p) throw ()
+{
+  return p;
+}
+struct B
+{
+  virtual ~B ();
+  B ();
+};
+struct A : B
+{
+  A () : B () {}
+  virtual void bar ();
+};
+void
+foo ()
+{
+  char a[64];
+  B *b = new (a) A ();
+  b-~B ();
+}


[pph] add tests and -fpph-check (issue5820069)

2012-03-15 Thread Lawrence Crowl
This patch mostly adds several test cases reduced from full-scale attempts to
use PPH.

  c?anonymous* -- problems handling anonymous/tagless types
  c?features* -- problems with benign macro redefinitions
  x?tmpldfltparm* -- inappropriately merging default template arguments

It also add an option -fpph-check to refine our check for headers compatible
with PPH.  It implies -fprimary-system-header-okay and checks for the main
source file missing a guard.  Generating a pph file implies the same check.

Tested on x64.


Index: gcc/c-family/ChangeLog.pph

2012-03-15   Lawrence Crowl  cr...@google.com

* c.opt (-fpph-check): New.
* c-opts.c (c_common_handle_option): Add OPT_fpph_check.
(case OPT__output_pph_): Also imply -fpph-check.
* c-common.h (bool pph_check_main_missing_guard): New.
* c-common.c (bool pph_check_main_missing_guard): New.
(const char *pph_out_file): Explicitly initialize to NULL.

Index: gcc/testsuite/ChangeLog.pph

2012-03-15   Lawrence Crowl  cr...@google.com

* g++.dg/pph/c0anonymous.h: New.
* g++.dg/pph/c1anonymous1.h: New.
* g++.dg/pph/c1anonymous2.h: New.
* g++.dg/pph/c5features1.h: New.
* g++.dg/pph/c5features2.h: New.
* g++.dg/pph/c7features.cc: New.
* g++.dg/pph/d8dupguard.cc: Add xfail-if comment.
* g++.dg/pph/x0tmpldfltparm.h: New.
* g++.dg/pph/x1tmpldfltparm.cc: New.
* g++.dg/pph/y9overload.cc: Add xfail-if comment.

Index: gcc/cp/ChangeLog.pph

2012-03-15   Lawrence Crowl  cr...@google.com

* pph.h (pph_check_main_guarded): New.
* pph-core.c (pph_check_main_guarded): New.
* pph-out.c (pph_writer_finish): Factor out guard check into
pph_check_main_guarded.
* parser.c (c_parse_file): Add guard check for non-pph compiles.


Index: gcc/c-family/c.opt
===
--- gcc/c-family/c.opt  (revision 185442)
+++ gcc/c-family/c.opt  (working copy)
@@ -981,6 +981,10 @@ fplan9-extensions
 C ObjC Var(flag_plan9_extensions)
 Enable Plan 9 language extensions
 
+fpph-check
+C++
+-fpph-checkCheck a header for minimal compatibility with PPH.
+
 fpph-debug=
 C++ Joined RejectNegative UInteger Var(flag_pph_debug)
 -fpph-debug=N   Enable debugging output at level N from PPH support
Index: gcc/c-family/c-opts.c
===
--- gcc/c-family/c-opts.c   (revision 185442)
+++ gcc/c-family/c-opts.c   (working copy)
@@ -404,6 +404,7 @@ c_common_handle_option (size_t scode, co
 case OPT__output_pph_:
   pph_out_file = arg;
   cpp_opts-primary_system_header_okay = true;
+  pph_check_main_missing_guard = true;
   break;
 
 case OPT_A:
@@ -814,6 +815,11 @@ c_common_handle_option (size_t scode, co
   set_struct_debug_option (global_options, loc, arg);
   break;
 
+case OPT_fpph_check:
+  cpp_opts-primary_system_header_okay = true;
+  pph_check_main_missing_guard = true;
+  break;
+
 case OPT_fpph_hdr_:
   add_pph_header_map (arg);
   break;
Index: gcc/c-family/c-common.c
===
--- gcc/c-family/c-common.c (revision 185442)
+++ gcc/c-family/c-common.c (working copy)
@@ -194,7 +194,11 @@ const char *pch_file;
 /* The file name to which we should write a preparsed header, or
NULL if no header will be written in this compile.  */
 
-const char *pph_out_file;
+const char *pph_out_file = NULL;
+
+/* Whether or not we should check for a guard on the main input file.  */
+
+bool pph_check_main_missing_guard = false;
 
 /* Nonzero if an ISO standard was selected.  It rejects macros in the
user's namespace.  */
Index: gcc/c-family/c-common.h
===
--- gcc/c-family/c-common.h (revision 185442)
+++ gcc/c-family/c-common.h (working copy)
@@ -585,6 +585,10 @@ extern const char *pch_file;
 
 extern const char *pph_out_file;
 
+/* Whether or not we should check for a guard on the main input file.  */
+
+extern bool pph_check_main_missing_guard;
+
 /* Return true if we have any map from INCLUDE to PPH file.  */
 
 extern bool
Index: gcc/testsuite/g++.dg/pph/c1anonymous1.h
===
--- gcc/testsuite/g++.dg/pph/c1anonymous1.h (revision 0)
+++ gcc/testsuite/g++.dg/pph/c1anonymous1.h (revision 0)
@@ -0,0 +1,11 @@
+// {xfail-if ANONYMOUS MERGING { *-*-* } { -fpph-map=pph.map } }
+// { dg-bogus c0anonymous.h:4:16: error: 'anon_t' has a previous declaration 
here  { xfail *-*-* } 0 }
+
+#ifndefC1ANONYMOUS
+#defineC1ANONYMOUS
+
+#include c0anonymous.h
+
+enum { first, second }; // { dg-bogus 'anon_t' referred to as enum  { 
xfail *-*-* } }
+
+#endif
Index: gcc/testsuite/g++.dg/pph/c1anonymous2.h

Re: Preserve pointer types in ivopts

2012-03-15 Thread Zdenek Dvorak
Hi,

 Currently, tree-ssa-loop-ivopts assumes that pointers and integers can
 be used interchangeably. It prefers to compute everything in unsigned
 integer types rather than pointer types.
 On a new target that I'm working on, this assumption is problematic;
 casting a pointer to an integer and doing arithmetic on the integer
 would be much too expensive to be useful. I came up with the patch
 below, which makes ivopts try harder to preserve pointer types.
 tree-affine is changed to keep track of base pointers, and do arithmetic
 (in particular subtraction) properly if base pointers are involved.
 
 Bootstrapped and regression tested with all languages on i686-linux. I
 get FAILs in:
 
 * gcc.dg/guality/pr43051-1.c
   A somewhat contrived testcase; gdb now produces optimized out
   messages which I think is acceptable? In any case I remain to be
   convinced that this testcase demonstrates any real problem.
 * gcc.dg/tree-ssa/reassoc-19.c scan-tree-dump-times reassoc2  \+  0
   This seems to fail because we do POINTER_PLUS (ptr, NEG offset))
   rather than (char *)((int)ptr - offset). As far as I can tell this
   is also not a real problem, but I don't know how to adjust the
   testcase.
 
 Comments? Ok?

the reason unsigned integer types are prefered is that possible overflows
during the computation have defined semantics.  With pointer types, the
intermediate steps of the computations could have undefined behavior, possibly
confusing further optimizations.  Is the patch with this regard?

Zdenek


Re: [Patch, libfortran] RFC: Shared vtables, constification

2012-03-15 Thread Jerry DeLisle

On 03/15/2012 11:42 AM, Janne Blomqvist wrote:

PING! (At this point, obviously for trunk only)



Yes, OK for trunk.


On Mon, Feb 13, 2012 at 20:20, Janne Blomqvist
blomqvist.ja...@gmail.com  wrote:

Hi,

the attached patch changes the low-level libgfortran IO dispatching
mechanism to use shared vtables for each stream type, instead of all
the function pointers being replicated for each unit. This is similar
to e.g. how the C++ frontend implements vtables. The benefits are:

- Slightly smaller heap memory overhead for each unit as only the
vtable pointer needs to be stored, and slightly faster unit
initialization as only the vtable pointer needs to be setup instead of
all the function pointers in the stream struct.

- Looking at unix.o with readelf, one sees

Relocation section '.rela.data.rel.ro.local.mem_vtable' at offset
0x15550 contains 8 entries:

and similarly for the other vtables; according to
http://www.airs.com/blog/archives/189 this means that after relocation
the page where this data resides may be marked read-only.

The downside is that the sizes of the .text and .data sections are
increased. Before:

   textdata bss dec hex filename
11169916664 592 1124247  112797
./x86_64-unknown-linux-gnu/libgfortran/.libs/libgfortran.so

After:

   textdata bss dec hex filename
11174876936 592 1125015  112a97
./x86_64-unknown-linux-gnu/libgfortran/.libs/libgfortran.so


The data section increase is due to the vtables, the text increase is,
I guess, due to the extra pointer dereference when calling the IO
functions.

Regtested on x86_64-unknown-linux-gnu, Ok for trunk, or 4.8?

2012-02-13  Janne Blomqvistj...@gcc.gnu.org

* io/unix.h (struct stream): Rename to stream_vtable.
(struct stream): New struct definition.
(sread): Dereference vtable pointer.
(swrite): Likewise.
(sseek): Likewise.
(struncate): Likewise.
(sflush): Likewise.
(sclose): Likewise.
* io/unix.c (raw_vtable): New variable.
(buf_vtable): Likewise.
(mem_vtable): Likewise.
(mem4_vtable): Likewise.
(raw_init): Assign vtable pointer.
(buf_init): Likewise.
(open_internal): Likewise.
(open_internal4): Likewise.



--
Janne Blomqvist






Re: struct siginfo vs. siginfo_t (was: GNU C Library master sources branch, master, updated. glibc-2.15-229-g4efeffc)

2012-03-15 Thread Mike Frysinger
On Thursday 15 March 2012 11:57:00 Carlos O'Donell wrote:
 We should be rebuilding *all* of userspace when glibc changes. It
 would be nice if we setup an OpenEmbedded system to rebuild as much of
 x86-64 userspace as possible against a new glibc and check for
 regressions.

emerge -e world
-mike


signature.asc
Description: This is a digitally signed message part.


Re: [PATCH] Use vpermpd instead of vpermq for V4DF AVX2 permutations (PR target/52568)

2012-03-15 Thread Richard Henderson
On 03/15/12 13:05, Jakub Jelinek wrote:
 Hi!
 
 This patch let's -mavx2 use vpermpd instead of vpermq for
 V4DFmode __builtin_shuffle (e.g. {1, 2, 3, 0}).
 Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?
 
 2012-03-15  Jakub Jelinek  ja...@redhat.com
 
   PR target/52568
   * config/i386/sse.md (UNSPEC_VPERMDF): Remove.
   (avx2_permv4df): Remove.
   (avx2_permv4di): Macroize into...
   (avx2_permmode): ... this using VI8F_256 iterator.
   (avx2_permv4di_1): Macroize into...
   (avx2_permmode_1): ... this using VI8F_256 iterator.

Ok.


r~


Re: [PATCH] Improve AVX V4DF and V8SF permutations (PR target/52568)

2012-03-15 Thread Richard Henderson
On 03/15/12 13:09, Jakub Jelinek wrote:
 Hi!
 
 As noted in the PR, we can vectorize e.g. V4DFmode
 __builtin_shuffle (, {1, 2, 3, 0}) in 3 insns, some intra-lane
 permutation, followed by swapping of the lanes (vperm2f128) and
 finally vblend{pd,ps} that merges in the registers with non-swapped
 and swapped lanes.
 
 Bootstrapped/regtested on x86_64-linux and i686-linux, tested
 additionally with
 GCC_TEST_RUN_EXPENSIVE=1 make check-gcc 
 RUNTESTFLAGS='--target_board=unix\{-m32/-mavx,-m64/-mavx\} 
 dg-torture.exp=vshuf*'
 Ok for trunk?
 
 2012-03-15  Jakub Jelinek  ja...@redhat.com
 
   PR target/52568
   * config/i386/i386.c (expand_vec_perm_vperm2f128_vblend): New
   function.
   (ix86_expand_vec_perm_const_1): Use it.
 
   * gcc.dg/torture/vshuf-4.inc: Add two new tests.
   * gcc.dg/torture/vshuf-8.inc: Likewise.
   * gcc.dg/torture/vshuf-16.inc: Likewise.
   * gcc.dg/torture/vshuf-32.inc: Likewise.


Ok.


r~


Re: Preserve pointer types in ivopts

2012-03-15 Thread Jakub Jelinek
On Fri, Mar 16, 2012 at 12:20:44AM +0100, Bernd Schmidt wrote:
 On 03/16/2012 12:16 AM, Jakub Jelinek wrote:
  On Fri, Mar 16, 2012 at 12:03:08AM +0100, Bernd Schmidt wrote:
  On 03/15/2012 11:12 PM, Zdenek Dvorak wrote:
 
  the reason unsigned integer types are prefered is that possible overflows
  during the computation have defined semantics.  With pointer types, the
  intermediate steps of the computations could have undefined behavior, 
  possibly
  confusing further optimizations.  Is the patch with this regard?
 
  It's trying to use sizetype for pointer offset computations. As far as I
  can tell that's supposed to be an unsigned type, so it should be OK. I
  think the final POINTER_PLUS_EXPRs we make can't overflow in valid 
  programs.
  
  In the IL before ivopts it shouldn't for valid programs, but what ivopts
  makes out of it often would, that is why it uses unsigned integers instead.
 
 Well, what are our rules for whether overflow on POINTER_PLUS_EXPR is
 defined or not? A quick search through the headers and docs doesn't turn
 up anything. Would there be a downside to defining it as wrapping?
 
 Can you show an example where a POINTER_PLUS_EXPR produced by ivopts
 would overflow?

Don't have a testcase right now, I've just seen IVOPTS many times in the
past initialize an IV with start of array minus some constant, end of array
plus some constant or similar (which is fine if the IV is unsigned integer
of the size of a pointer, but certainly wouldn't be fine if the IV had
pointer type).  For pointer arithmetics in the IL we assume the C
requirements, pointer arithmetics can be performed only within the same
object, so for
int a[10];
both of the following are invalid, even in the IL:
int *p = a - 1;
int *q = a + 11;

Jakub


Re: Preserve pointer types in ivopts

2012-03-15 Thread Zdenek Dvorak
Hi,

  Well, what are our rules for whether overflow on POINTER_PLUS_EXPR is
  defined or not? A quick search through the headers and docs doesn't turn
  up anything. Would there be a downside to defining it as wrapping?
  
  Can you show an example where a POINTER_PLUS_EXPR produced by ivopts
  would overflow?
 
 Don't have a testcase right now, I've just seen IVOPTS many times in the
 past initialize an IV with start of array minus some constant, end of array
 plus some constant or similar (which is fine if the IV is unsigned integer
 of the size of a pointer, but certainly wouldn't be fine if the IV had
 pointer type).  For pointer arithmetics in the IL we assume the C
 requirements, pointer arithmetics can be performed only within the same
 object, so for
 int a[10];
 both of the following are invalid, even in the IL:
 int *p = a - 1;
 int *q = a + 11;

for example, something like this:

int a[1000];

void foo(int n)
{
  int i, *p = a;

  for (i = 8; i  n; i++)
*p++ = 10;
}

ivopts may decide to change this to:

int a[1000];

void foo(int n)
{
  int i, *p = a - 8;

  for (i = 8; i  n; i++)
p[i] = 10;
}

which may require one less adition, depending on the available addressing modes.
Of course, as written above this has undefined behavior; hence, the casts to
unsigned integer,

Zdenek


Re: Preserve pointer types in ivopts

2012-03-15 Thread Bernd Schmidt
On 03/16/2012 12:44 AM, Jakub Jelinek wrote:
 For pointer arithmetics in the IL we assume the C
 requirements, pointer arithmetics can be performed only within the same
 object, so for
 int a[10];
 both of the following are invalid, even in the IL:
 int *p = a - 1;
 int *q = a + 11;

Ok, so what's the solution? Add a second POINTER_PLUS_EXPR code with
defined overflow behaviour, or add a flag to it?


Bernd


Re: Preserve pointer types in ivopts

2012-03-15 Thread Andrew Pinski
On Thu, Mar 15, 2012 at 5:09 PM, Bernd Schmidt ber...@codesourcery.com wrote:
 On 03/16/2012 12:44 AM, Jakub Jelinek wrote:
 For pointer arithmetics in the IL we assume the C
 requirements, pointer arithmetics can be performed only within the same
 object, so for
 int a[10];
 both of the following are invalid, even in the IL:
 int *p = a - 1;
 int *q = a + 11;

 Ok, so what's the solution? Add a second POINTER_PLUS_EXPR code with
 defined overflow behaviour, or add a flag to it?

We should have one for PLUS_EXPR also.  There was some movement on
that on a branch that Richard Guenther did but I don't know if he is
going to work on it further.  I have been noticing more and more the
need for this feature while working on my tree combiner branch, that I
might try to see if Richard's branch can be revisited.

Thanks,
Andrew Pinski


Re: Ping: Re: [patch middle-end]: Fix PR/48814 - [4.4/4.5/4.6/4.7 Regression] Incorrect scalar increment result

2012-03-15 Thread Jonathan Wakely
On 15 March 2012 15:40, Richard Guenther wrote:
 On Thu, Mar 15, 2012 at 4:22 PM, Kai Tietz ktiet...@googlemail.com wrote:
 Richard,

 ping.  I think now could be a good time for applying the patch you
 have for this issue as we are in stage 1.

 It will still regress the two libstdc++ testcases (well, I guess so at least).

 Jonathan - you didn't answer my reply to your question?  Would it be ok
 to apply this patch with leaving the regressions in-place, to be investigated
 by libstdc++ folks?

Sorry, I've either forgotten or missed the reply - but if you think
the problem is in libstdc++ then certainly go ahead and apply it, I'll
investigate the libstdc++ problems (and ask for help if they defeat
me!)


[PATCH, ARM, 4.6] backport PR pch/45979

2012-03-15 Thread Michael Hope

Hi there.

This patch backports my PCH on ARM EABI fix[1] for pch/PR45979 to the 4.6 
branch.  This
fixes PCH support on ARM and tidies up the random pch testsuite failures that 
are seen
between runs.

OK for 4.6?

-- Michael
[1] http://gcc.gnu.org/ml/gcc-patches/2011-05/msg00017.html

gcc/

2012-03-16  Michael Hope  michael.h...@linaro.org

Backport from mainline
2011-05-05  Michael Hope  michael.h...@linaro.org

PR pch/45979
* config/host-linux.c (TRY_EMPTY_VM_SPACE): Define for
__ARM_EABI__ hosts.

diff --git a/gcc/config/host-linux.c b/gcc/config/host-linux.c
index 47ce3ea..ec61055 100644
--- a/gcc/config/host-linux.c
+++ b/gcc/config/host-linux.c
@@ -84,6 +84,8 @@
 # define TRY_EMPTY_VM_SPACE0x6000
 #elif defined(__mc68000__)
 # define TRY_EMPTY_VM_SPACE0x4000
+#elif defined(__ARM_EABI__)
+# define TRY_EMPTY_VM_SPACE 0x6000
 #else
 # define TRY_EMPTY_VM_SPACE0
 #endif


[google/4.6] Fix problems with -gfission (issue5844043)

2012-03-15 Thread Cary Coutant
For google/gcc-4_6 branch.

This patch fixes several problems with -gfission:
 - Bad index for range list in the compile unit DIE.
 - DW_AT_ranges attribute for compile unit in the wrong file.
 - Incorrect size for skeleton type unit DIEs.
 - Wrote location expression using DW_OP_addr to DWO file.
 - Emitted skeleton debug section even when there is no debug info.

Tested: bootstrap, gcc regression tests, hand testing on -gfission
test cases.


include/

2012-03-15   Sterling Augustine  saugust...@google.com
 Cary Coutant  ccout...@google.com

* dwarf2.h (enum dwarf_location_atom): Add
DW_OP_GNU_addr_index.

gcc/

2012-03-15   Sterling Augustine  saugust...@google.com
 Cary Coutant  ccout...@google.com

* dwarf2out.c (dwarf_stack_op_name): Add DW_OP_GNU_addr_index.
(size_of_loc_descr): Likewise.
(output_loc_operands): Likewise.
(output_loc_operands_raw): Likewise.
(new_addr_loc_descr): New function.
(add_AT_range_list): Store index in AT_index.
(size_of_die): For range_list, use AT_index for index value.
(add_top_level_skeleton_die_attrs): Don't add DW_AT_stmt_list here.
(get_skeleton_type_unit): New function.
(output_skeleton_debug_sections): Add comp_unit parameter; adjust
caller.  Don't allocate new comp unit DIE here.  Move allocation
of debug_skeleton_info_section_label and
debug_skeleton_abbrev_section_label to dwarf2out_init.  Call
get_skeleton_type_unit.
(output_comdat_type_unit): Remove assert; call get_skeleton_type_unit.
(mem_loc_descriptor): Call new_addr_loc_desc.
(loc_descriptor): Likewise.
(loc_list_from_tree): Likewise.
(add_const_value_attribute): Likewise.
(dwarf2out_init): Allocate debug_skeleton_info_section_label and
debug_skeleton_abbrev_section_label.
(output_indirect_string): Check for DW_FORM_strp instead of label
and refcount.
(output_addr_table): Add case for dw_val_class_loc.
(resolve_addr_in_expr): Handle DW_OP_addr_index.
(hash_loc_operands): Likewise.
(compare_loc_operands): Likewise.
(dwarf2out_finish): Allocate skeleton compile unit DIE here; add
range lists, DW_AT_stmt_list, and DW_AT_macro_info to it instead
of dwo compile unit DIE.  Output skeleton debug info section only
if there is debug info.


Index: include/dwarf2.h
===
--- include/dwarf2.h(revision 185451)
+++ include/dwarf2.h(working copy)
@@ -547,6 +547,8 @@ enum dwarf_location_atom
 DW_OP_GNU_uninit = 0xf0,
 DW_OP_GNU_encoded_addr = 0xf1,
 DW_OP_GNU_implicit_pointer = 0xf2,
+/* Extension for Fission.  See http://gcc.gnu.org/wiki/DebugFission.  */
+DW_OP_GNU_addr_index = 0xfb,
 /* HP extensions.  */
 DW_OP_HP_unknown = 0xe0, /* Ouch, the same as GNU_push_tls_address.  */
 DW_OP_HP_is_value= 0xe1,
Index: gcc/dwarf2out.c
===
--- gcc/dwarf2out.c (revision 185451)
+++ gcc/dwarf2out.c (working copy)
@@ -4779,6 +4779,8 @@ dwarf_stack_op_name (unsigned int op)
   return DW_OP_GNU_encoded_addr;
 case DW_OP_GNU_implicit_pointer:
   return DW_OP_GNU_implicit_pointer;
+case DW_OP_GNU_addr_index:
+  return DW_OP_GNU_addr_index;
 
 default:
   return OP_unknown;
@@ -4897,6 +4899,9 @@ size_of_loc_descr (dw_loc_descr_ref loc)
 case DW_OP_addr:
   size += DWARF2_ADDR_SIZE;
   break;
+case DW_OP_GNU_addr_index:
+  size += size_of_uleb128 (loc-dw_loc_oprnd1.v.val_unsigned);
+  break;
 case DW_OP_const1u:
 case DW_OP_const1s:
   size += 1;
@@ -5275,6 +5280,11 @@ output_loc_operands (dw_loc_descr_ref lo
}
   break;
 
+case DW_OP_GNU_addr_index:
+  dw2_asm_output_data_uleb128 (loc-dw_loc_oprnd1.v.val_unsigned,
+   (address index));
+  break;
+
 case DW_OP_GNU_implicit_pointer:
   {
char label[MAX_ARTIFICIAL_LABEL_BYTES
@@ -5343,6 +5353,7 @@ output_loc_operands_raw (dw_loc_descr_re
   switch (loc-dw_loc_opc)
 {
 case DW_OP_addr:
+case DW_OP_GNU_addr_index:
 case DW_OP_implicit_value:
   /* We cannot output addresses in .cfi_escape, only bytes.  */
   gcc_unreachable ();
@@ -6314,6 +6325,7 @@ static inline dw_loc_descr_ref AT_loc (d
 static void add_AT_loc_list (dw_die_ref, enum dwarf_attribute,
 dw_loc_list_ref);
 static inline dw_loc_list_ref AT_loc_list (dw_attr_ref);
+static unsigned int add_addr_table_entry (dw_attr_node *);
 static void add_AT_addr (dw_die_ref, enum dwarf_attribute, rtx);
 static inline rtx AT_addr (dw_attr_ref);
 static void add_AT_lbl_id (dw_die_ref, enum dwarf_attribute, const char *);
@@ -6571,6 +6583,31 @@ static bool generic_type_p (tree);
 static void 

Re: [patch] Fix non-standard Ada bootstrap failure on IA-64

2012-03-15 Thread Alexandre Oliva
On Mar  9, 2012, Eric Botcazou ebotca...@adacore.com wrote:

 It does that only in case the -g0 build would add the same locs to the
 table.  Only the DEBUG_INSN_P setting_insn locs are there just in -g builds
 and not in -g0 ones.

 If that's really supposed to work like so, then this is the bug, because the 
 non-legitimate expression is present only with -g and its location promoted.

It could be the case that an alternate, legitimate representation of the
same expression is used elsewhere, and at the point that goes into
cselib, the previously debug-only entry should become a regular entry in
the cselib table.

Is this what you observe?  If that's it, maybe we need to somehow mark
debug-only locs in loc lists, and get some code other than VTA to skip
the debug-only locs, or somethink like that.

-- 
Alexandre Oliva, freedom fighterhttp://FSFLA.org/~lxoliva/
You must be the change you wish to see in the world. -- Gandhi
Be Free! -- http://FSFLA.org/   FSF Latin America board member
Free Software Evangelist  Red Hat Brazil Compiler Engineer