platform/upstream/gcc.git
5 years ago[Ada] Usage of signed type in array bounds in CCG
Javier Miranda [Mon, 22 Jul 2019 13:57:46 +0000 (13:57 +0000)]
[Ada] Usage of signed type in array bounds in CCG

2019-07-22  Javier Miranda  <miranda@adacore.com>

gcc/ada/

* exp_ch4.adb (Size_In_Storage_Elements): Improve the expansion
to handle array indexes that are modular type.
(Expand_N_Allocator): For 32-bit targets improve the generation
of the runtime check associated with large arrays supporting
arrays initialized with a qualified expression.
* libgnat/s-imenne.adb (Image_Enumeration_8,
Image_Enumeration_16, Image_Enumeration_32): Define the index of
Index_Table with range Natural'First .. Names'Length since in
the worst case all the literals of the enumeration type would be
single letter literals and the Table built by the frontend would
have as many components as the length of the names string. As a
result of this enhancement, the internal tables declared using
Index_Table have a length closer to the real needs, thus
avoiding the declaration of large arrays on 32-bit CCG targets.

From-SVN: r273685

5 years ago[Ada] Issue warning or error message on ignored typing constraint
Yannick Moy [Mon, 22 Jul 2019 13:57:42 +0000 (13:57 +0000)]
[Ada] Issue warning or error message on ignored typing constraint

GNAT ignores the discriminant constraint on a component when it applies
to the type of the record being analyzed. Now issue a warning on Ada
code when ignoring this constraint, or an error on SPARK code.

2019-07-22  Yannick Moy  <moy@adacore.com>

gcc/ada/

* sem_ch3.adb (Constrain_Access): Issue a message about ignored
constraint.

gcc/testsuite/

* gnat.dg/warn24.adb: New testcase.

From-SVN: r273684

5 years ago[Ada] Fix spurious visibility error for tagged type with inlining
Eric Botcazou [Mon, 22 Jul 2019 13:57:37 +0000 (13:57 +0000)]
[Ada] Fix spurious visibility error for tagged type with inlining

This fixes a spurious visibility error for the very peculiar case where
an operator that operates on the class-wide type of a tagged type is
declared in a package, the operator is renamed in another package where
a subtype of the tagged type is declared, and both packages end up in
the transititive closure of a unit compiled with optimization and
inter-inlining (-gnatn).

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* sem_ch8.adb (End_Use_Type): Reset the In_Use flag on the
class-wide type if the type is tagged.
(Use_One_Type): Add commentary on the handling of the class-wide
type.

gcc/testsuite/

* gnat.dg/inline17.adb, gnat.dg/inline17_pkg1.adb,
gnat.dg/inline17_pkg1.ads, gnat.dg/inline17_pkg2.ads,
gnat.dg/inline17_pkg3.adb, gnat.dg/inline17_pkg3.ads: New
testcase.

From-SVN: r273683

5 years ago[Ada] Remove obsolete Is_For_Access_Subtype machinery
Eric Botcazou [Mon, 22 Jul 2019 13:57:31 +0000 (13:57 +0000)]
[Ada] Remove obsolete Is_For_Access_Subtype machinery

This change removes the Is_For_Access_Subtype machinery from the
compiler.  This machinery was devised a long time ago to deal with a
peculiarity of the freezing for access-to-record subtypes but has been
degenerate for quite some time now and does not seem to serve any useful
purpose at this point.

Morever it has an annoying side effect whereby it causes Underlying_Type
to return the (unconstrained) base record type when invoked on the
designated record subtype, which is very problematic for GNATprove.

There should be no functional changes.

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* einfo.ads (Is_For_Access_Subtype): Delete.
(Set_Is_For_Access_Subtype): Likewise.
* einfo.adb (Is_For_Access_Subtype): Likewise.
(Set_Is_For_Access_Subtype): Likewise.
(Write_Entity_Flags): Do not write Is_For_Access_Subtype.
* exp_ch4.adb (Expand_N_Selected_Component): Do not deal with
it.
* exp_spark.adb (Expand_SPARK_N_Selected_Component): Likewise.
* sem_ch4.adb (Analyze_Explicit_Dereference): Likewise.
* sem_ch3.adb (Build_Discriminated_Subtype): Do not build a
special private subtype for access-to-record subtypes.

From-SVN: r273682

5 years ago[Ada] Spurious error on private subtype of derived access type
Eric Botcazou [Mon, 22 Jul 2019 13:57:26 +0000 (13:57 +0000)]
[Ada] Spurious error on private subtype of derived access type

This patch fixes a spurious type error on a dynamic predicate on a
subtype of a private type whose full view is a derived access type.
Prior to it, the base type of the subtype would appear to be the parent
type of the derived type instead of the derived type itself, leading to
problems downstream.

The following package must now compile quietly:

with S;

package T is
   type B_Pointer is private;
   Null_B_Pointer : constant B_Pointer;
   function OK (B : B_Pointer) return Boolean is (B /= Null_B_Pointer);
   subtype Valid_B_Pointer is B_Pointer
     with Dynamic_Predicate => OK (Valid_B_Pointer);
private
   type B_Pointer is new S.A_Pointer;
   Null_B_Pointer : constant B_Pointer := B_Pointer (S.Null_A_Pointer);
end;

package S is
   type A_Type is new Integer;
   type A_Pointer is access A_Type;
   Null_A_Pointer : constant A_Pointer := null;
end;

Moreover, it also plugs a loophole in the compiler whereby an
instantiation of a generic with a formal subprogram declaration nested
in an enclosing generic package would be done even if there was a
mismatch between an original and a derived types involved in the
instantiation.

The compiler must now gives the following error:
p.adb:11:43: no visible subprogram matches the specification for "Action"
on

with Q;
with R;
with G;

procedure P is

  package My_G is new G (Q.T);

  procedure Proc (Value : R.T) is null;

  procedure Iter is new My_G.Iteration_G (Proc);

begin
  null;
end;

with R;

package Q is

  type T is new R.T;

end Q;

package R is

  type T is private;

private

  type T is access Integer;

end R;

generic

  type Value_T is private;

package G is

  generic
    with procedure Action (Value : Value_T);
  procedure Iteration_G;

end G;

package body G is

  procedure Iteration_G is null;

end G;

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* sem_ch3.adb (Complete_Private_Subtype): Rework the setting of
the Etype of the full view for full base types that cannot
contain any discriminant.  Remove code and comment about it in
the main path.

From-SVN: r273681

5 years ago[Ada] Type inconsistency in floating_point type declarations
Ed Schonberg [Mon, 22 Jul 2019 13:57:22 +0000 (13:57 +0000)]
[Ada] Type inconsistency in floating_point type declarations

This patch fixes an inconsistency in the typing of the bounds of a
floting point type declaration, when some bound is given by a dtatic
constant of an explicit type, instead of a real literal, Previous to
this patch the bound of the type retained the given type, leading to
spurious errors in Codepeer.

2019-07-22  Ed Schonberg  <schonberg@adacore.com>

gcc/ada/

* sem_ch3.adb (Convert_Bound): Subsidiary of
Floating_Point_Type_Declaration, to handle properly range
specifications with bounds that may include static constants of
a given type rather than real literals.

From-SVN: r273680

5 years ago[Ada] Further fix non-stored discriminant in aggregate for GNATprove
Eric Botcazou [Mon, 22 Jul 2019 13:57:18 +0000 (13:57 +0000)]
[Ada] Further fix non-stored discriminant in aggregate for GNATprove

GNATprove expects discriminants appearing in aggregates and their types
to be resolved to stored discriminants.  This extends the machinery that
makes sure this is the case for default initialization expressions so as
to also handle component associations in these expressions.

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* sem_aggr.adb (Rewrite_Bound): Be prepared for discriminals
too.
(Rewrite_Range;): Minor tweak.
(Resolve_Record_Aggregate): For a component with default
initialization whose expression is an array aggregate, also
rewrite the bounds of the component associations, if any.

From-SVN: r273679

5 years ago[Ada] Premature finalization of controlled temporaries in case expressions
Gary Dismukes [Mon, 22 Jul 2019 13:57:13 +0000 (13:57 +0000)]
[Ada] Premature finalization of controlled temporaries in case expressions

The compiler was generating finalization of temporary objects used in
evaluating case expressions for controlled types in cases where the case
statement created by Expand_N_Expression_With_Actions is rewritten as an
if statement. This is fixed by inheriting the From_Condition_Expression
flag from the rewritten case statement.

The test below must generate the following output when executed:

$ main
Xs(1): 1

----

package Test is

   type E is (E1, E2);
   procedure Test (A : in E);

end Test;

----

with Ada.Text_IO;
with Ada.Finalization;

package body Test is

   type T is new Ada.Finalization.Controlled with
      record
         N : Natural := 0;
      end record;

   overriding procedure Finalize (X : in out T) is
   begin
      X.N := 42;
   end Finalize;

   type T_Array is array (Positive range <>) of T;

   function Make_T (N : Natural) return T is
   begin
      return (Ada.Finalization.Controlled with N => N);
   end Make_T;

   X1 : constant T := Make_T (1);
   X2 : constant T := Make_T (2);

   procedure Test (A : in E)
   is
      Xs : constant T_Array := (case A is
                                   when E1 => (1 => X1),
                                   when E2 => (1 => X2));
   begin
      Ada.Text_IO.Put_Line ("Xs(1):" & Natural'Image (Xs (1).N));
   end Test;

end Test;

----

with Test;

procedure Main is
begin
   Test.Test (Test.E1);
end Main;

2019-07-22  Gary Dismukes  <dismukes@adacore.com>

gcc/ada/

* exp_ch5.adb (Expand_N_Case_Statement): In the case where a
case statement is rewritten as an equivalent if statement,
inherit the From_Condition_Expression flag from the case
statement.

From-SVN: r273678

5 years ago[Ada] Internal error on iterator for limited private discriminated type
Eric Botcazou [Mon, 22 Jul 2019 13:57:09 +0000 (13:57 +0000)]
[Ada] Internal error on iterator for limited private discriminated type

This patch further extends the short-circuit, aka optimization, present
in the Check_Constrained_Object procedure used for renaming declarations
to all limited types, so as to prevent type mismatches downstream in
more cases.

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* sem_ch8.adb (Check_Constrained_Object): Further extend the
special optimization to all limited types.

gcc/testsuite/

* gnat.dg/iter5.adb, gnat.dg/iter5_pkg.ads: New testcase.

From-SVN: r273677

5 years ago[Ada] Fix missing Constraint_Error for Enum_Val attribute
Eric Botcazou [Mon, 22 Jul 2019 13:57:04 +0000 (13:57 +0000)]
[Ada] Fix missing Constraint_Error for Enum_Val attribute

This fixes an old issue involving the Enum_Val attribute: it does not
always raise a Constraint_Error exception when the specified value is
not valid for the enumeration type (instead a modulo computation is
applied to the value).

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* exp_attr.adb (Expand_N_Attribute_Reference)
<Attribute_Enum_Val>: Set No_Truncation on the
N_Unchecked_Type_Conversion built around the argument passed to
the attribute.

gcc/testsuite/

* gnat.dg/enum_val1.adb: New testcase.

From-SVN: r273676

5 years ago[Ada] Ensure meaningless digits in a string are discarded
Nicolas Roche [Mon, 22 Jul 2019 13:56:59 +0000 (13:56 +0000)]
[Ada] Ensure meaningless digits in a string are discarded

2019-07-22  Nicolas Roche  <roche@adacore.com>

gcc/ada/

* libgnat/s-valrea.adb (Scan_Real): Ignore non significative
digits to avoid converging to infinity in some cases.

gcc/testsuite/

* gnat.dg/float_value1.adb: New testcase.

From-SVN: r273675

5 years ago[Ada] Fix wrong assumption on bounds in GNAT.Encode_String
Eric Botcazou [Mon, 22 Jul 2019 13:56:55 +0000 (13:56 +0000)]
[Ada] Fix wrong assumption on bounds in GNAT.Encode_String

This fixes a couple of oversights in the GNAT.Encode_String package,
whose effect is to assume that all the strings have a lower bound of 1.

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* libgnat/g-encstr.adb (Encode_Wide_String): Fix oversight.
(Encode_Wide_Wide_String): Likewise.

gcc/testsuite/

* gnat.dg/encode_string1.adb, gnat.dg/encode_string1_pkg.adb,
gnat.dg/encode_string1_pkg.ads: New testcase.

From-SVN: r273674

5 years ago[Ada] Fix spurious loop warning for function with Out parameter
Eric Botcazou [Mon, 22 Jul 2019 13:56:50 +0000 (13:56 +0000)]
[Ada] Fix spurious loop warning for function with Out parameter

The compiler gives a spurious warning about a possible infinite while
loop whose condition contains a call to a function that takes an Out or
In/Out parameter and whose actual is a variable that is not modified in
the loop, because it still thinks that functions can only have In
parameters.

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* sem_warn.adb (Find_Var): Bail out for a function call with an
Out or In/Out parameter.

gcc/testsuite/

* gnat.dg/warn23.adb: New testcase.

From-SVN: r273673

5 years ago[Ada] Ensure Ctrl-C is not emited on terminated processes
Nicolas Roche [Mon, 22 Jul 2019 13:56:45 +0000 (13:56 +0000)]
[Ada] Ensure Ctrl-C is not emited on terminated processes

Due to the reuse policy of PID on Windows. Sending a Ctrl-C to a dead
process might result in a Ctrl-C sent to the wrong process. The check is
also implemented on Unix platforms and avoid unecessary waits.

2019-07-22  Nicolas Roche  <roche@adacore.com>

gcc/ada/

* terminals.c (__gnat_tty_waitpid): Support both blocking and
not blocking mode.
* libgnat/g-exptty.ads (Is_Process_Running): New function.
* libgnat/g-exptty.adb (Close): Don't try to interrupt/terminate
a process if it is already dead.

From-SVN: r273672

5 years ago[Ada] Incorrect values in conversion from fixed-point subtype with 'Small
Ed Schonberg [Mon, 22 Jul 2019 13:56:40 +0000 (13:56 +0000)]
[Ada] Incorrect values in conversion from fixed-point subtype with 'Small

This patch fixes incorrect computations involving a fixed-point subtype
whose parent type has an aspect specification for 'Small.

Executing the following:

   gnatmake -q conv
   ./conv

must yield:

   9000.000000
    9.00000000000000E+03
    9000.000000
    9.00000000000000E+03
    9.00000000000000E+03
    9.00000000000000E+03
    9.00000000000000E+03
    9.00000000000000E+03

----
with Text_IO; use Text_IO;
procedure Conv is
  V_P : constant := 10.0 ** (-6);
  M_V : constant := 9000.0;
  N_V : constant := -9000.0;
  type V_T is delta V_P range N_V .. M_V  with Small => V_P;
  subtype S_T is V_T range 0.0 .. M_V;

  function Convert (Input : in S_T) return Long_Float is
  begin
    Put_Line (Input'Img);
    Put_Line (Long_Float'Image (Long_Float (Input)));
    return Long_Float (Input);
  end Convert;

begin

  declare
    Var_S : constant S_T := S_T'Last;
    Output : constant Long_Float := Convert (Var_S);
  begin
    Put_Line (Long_Float'Image (Convert (Var_S)));
    Put_Line (Long_Float'Image (Long_Float (Var_S)));
    Put_Line (Output'Img);
  end;

  Put_Line (Long_Float'Image (Long_Float (S_T'Last)));

end Conv;

2019-07-22  Ed Schonberg  <schonberg@adacore.com>

gcc/ada/

* freeze.adb (Freeze_Fixed_Point_Type):  When freezing a
fixed-point subtype, check whether the parent type declarastion
includes an aspect specification for the 'Small type attribute,
and inherit the specified value.

From-SVN: r273671

5 years ago[Ada] Crash in C++ constructor without external and link name
Javier Miranda [Mon, 22 Jul 2019 13:56:36 +0000 (13:56 +0000)]
[Ada] Crash in C++ constructor without external and link name

The compiler blows up processing the declaration of a tagged type
variable that has a C++ constructor without external or link name. After
this patch the frontend reports an error.

2019-07-22  Javier Miranda  <miranda@adacore.com>

gcc/ada/

* freeze.adb (Freeze_Subprogram): Check that C++ constructors
must have external or link name.

gcc/testsuite/

* gnat.dg/cpp_constructor2.adb: New testcase.

From-SVN: r273670

5 years ago[Ada] Spurious warning about a useless assignment
Ed Schonberg [Mon, 22 Jul 2019 13:56:31 +0000 (13:56 +0000)]
[Ada] Spurious warning about a useless assignment

This patch removes a spurious warning about a useless assignment, when a
composite object is the target of an assignment and is an actual for an
out parameter in a subsewuent call, and there is an intervening use of
the object as the prefix of a selected component in an intervening
operation.

2019-07-22  Ed Schonberg  <schonberg@adacore.com>

gcc/ada/

* sem_res.adb (Resolve_Selected_Component): If the prefix has a
deferred reference, generate the correct reference now, to
indicate that the previous assignment is used.  This prevents
spurious warnings on useless assignments when compiling with all
warnings enabled. when there is a subsequent call in the same
stqtement list, in which the prefix of the selected component is
the actual for an out parameter.

gcc/testsuite/

* gnat.dg/warn22.adb: New testcase.

From-SVN: r273669

5 years ago[Ada] Fix internal error on array slice in loop and Loop_Invariant
Eric Botcazou [Mon, 22 Jul 2019 13:56:26 +0000 (13:56 +0000)]
[Ada] Fix internal error on array slice in loop and Loop_Invariant

This fixes an internal error caused by the presence of an Itype in a
wrong scope.  This Itype is created for an array slice present in the
condition of a while loop whose body also contains a pragma
Loop_Invariant, initially in the correct scope but then relocated into a
function created for the pragma.

2019-07-22  Eric Botcazou  <ebotcazou@adacore.com>

gcc/ada/

* exp_attr.adb (Expand_Loop_Entry_Attribute): Copy the condition
of a while loop instead of simply relocating it.

gcc/testsuite/

* gnat.dg/loop_invariant1.adb, gnat.dg/loop_invariant1.ads: New
testcase.

From-SVN: r273668

5 years agore PR tree-optimization/91221 (ICE in get_int_cst_ext_nunits, at tree.c:1299 since...
Richard Biener [Mon, 22 Jul 2019 11:18:55 +0000 (11:18 +0000)]
re PR tree-optimization/91221 (ICE in get_int_cst_ext_nunits, at tree.c:1299 since r273548)

2019-07-22  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91221
* tree-ssa-sccvn.c (vn_reference_lookup_3): Appropriately
restrict partial-def handling of empty constructors and
memset to refs with known offset.

* g++.dg/pr91221.C: New testcase.

From-SVN: r273667

5 years agox86/AVX512: improve generated code for bit-wise negation of vectors of integers
Jan Beulich [Mon, 22 Jul 2019 08:07:29 +0000 (08:07 +0000)]
x86/AVX512: improve generated code for bit-wise negation of vectors of integers

NOT on vectors of integers does not require loading a constant vector of
all ones into a register - VPTERNLOG can be used here (and could/should
be further used to carry out other binary and ternary logical operations
which don't have a special purpose instruction).

gcc/
2019-07-22  Jan Beulich  <jbeulich@suse.com>

* config/i386/sse.md (ternlogsuffix): New.
(one_cmpl<mode>2): Don't force CONSTM1_RTX into a register when
AVX512F is in use.
(<mask_codefor>one_cmpl<mode>2<mask_name>): New.

From-SVN: r273663

5 years agoDo not emit __gnu_lto_v1 symbol.
Martin Liska [Mon, 22 Jul 2019 07:34:47 +0000 (09:34 +0200)]
Do not emit __gnu_lto_v1 symbol.

2019-07-22  Martin Liska  <mliska@suse.cz>

* config/avr/avr.c (avr_asm_output_aligned_decl_common): Update
comment.
* toplev.c (compile_file): Do not emit __gnu_lto_v1 symbol.
2019-07-22  Martin Liska  <mliska@suse.cz>

* config/pa/stublib.c: Remove stub symbol __gnu_lto_v1.
* config/pa/t-stublib: Likewise.
2019-07-22  Martin Liska  <mliska@suse.cz>

* simple-object-elf.c (simple_object_elf_copy_lto_debug_sections):
Do not search for gnu_lto_v1, but search for first '\0'.

From-SVN: r273662

5 years agoSimplify LTO section format.
Martin Liska [Mon, 22 Jul 2019 07:34:32 +0000 (09:34 +0200)]
Simplify LTO section format.

2019-07-22  Martin Liska  <mliska@suse.cz>

* lto-section-in.c (lto_get_section_data):
Use new function get_compression.
* lto-streamer-out.c (produce_lto_section): Use
set_compression to encode compression algorithm.
* lto-streamer.h (struct lto_section): Do not
use bitfields in the format.

From-SVN: r273661

5 years agoMake a warning for -Werror=wrong-language (PR driver/91172).
Martin Liska [Mon, 22 Jul 2019 07:34:10 +0000 (09:34 +0200)]
Make a warning for -Werror=wrong-language (PR driver/91172).

2019-07-22  Martin Liska  <mliska@suse.cz>

PR driver/91172
* opts-common.c (decode_cmdline_option): Decode
argument of -Werror and check it for a wrong language.
* opts-global.c (complain_wrong_lang): Remove such case.
2019-07-22  Martin Liska  <mliska@suse.cz>

PR driver/91172
* gcc.dg/pr91172.c: New test.

From-SVN: r273660

5 years ago[ARC] Fix emitting TLS symbols.
Claudiu Zissulescu [Mon, 22 Jul 2019 07:06:37 +0000 (09:06 +0200)]
[ARC] Fix emitting TLS symbols.

When storing a TLS symbol to memory, always use an intermediate register to load it.

gcc/
xxxx-xx-xx  Claudiu Zissulescu  <claziss@synopsys.com>

* config/arc/arc.c (prepare_move_operands): Always use an
intermediate register when storing a TLS symbols.

gcc/
xxxx-xx-xx  Claudiu Zissulescu  <claziss@synopsys.com>

* gcc/testsuite/gcc.target/arc/tls-2.c: New test.
* gcc/testsuite/gcc.target/arc/tls-3.c: Likewise.

From-SVN: r273657

5 years agoDaily bump.
GCC Administrator [Mon, 22 Jul 2019 00:16:23 +0000 (00:16 +0000)]
Daily bump.

From-SVN: r273656

5 years agore PR c++/67853 (decltype of parenthesized xvalue does not correctly yield rvalue...
Marek Polacek [Sun, 21 Jul 2019 21:20:27 +0000 (21:20 +0000)]
re PR c++/67853 (decltype of parenthesized xvalue does not correctly yield rvalue-reference)

PR c++/67853
* g++.dg/cpp0x/decltype72.C: New test.

From-SVN: r273652

5 years agoor1k: only force reg for immediates
Stafford Horne [Sun, 21 Jul 2019 21:02:54 +0000 (21:02 +0000)]
or1k: only force reg for immediates

The force_reg in or1k_expand_compare is hard coded for SImode, which is fine as
this used to only be used on SI expands.  However, with FP support this will
cause issues.  In general we should only force the right hand operand to a
register if its an immediate.  This patch adds an condition to check for that.

gcc/ChangeLog:

* config/or1k/or1k.c (or1k_expand_compare): Check for int before
force_reg.

From-SVN: r273651

5 years agoor1k: Initial support for FPU
Stafford Horne [Sun, 21 Jul 2019 21:01:59 +0000 (21:01 +0000)]
or1k: Initial support for FPU

This adds support for OpenRISC hardware floating point instructions.
This is enabled with the -mhard-float option.

Double-prevision floating point operations work using register pairing as
specified in: https://openrisc.io/proposals/orfpx64a32.  This has just been
added in the OpenRISC architecture specification 1.3.
This is enabled with the -mdouble-float option.

Not all architectures support unordered comparisons so an option,
-munordered-float is added.

Currently OpenRISC does not support sf/df or df/sf conversions, but this has
also just been added in architecture specification 1.3.

gcc/ChangeLog:

* config.gcc (or1k*-*-*): Add mhard-float, mdouble-float, msoft-float
and munordered-float validations.
* config/or1k/constraints.md (d): New register constraint.
* config/or1k/predicates.md (fp_comparison_operator): New.
* config/or1k/or1k.c (or1k_print_operand): Add support for printing 'd'
operands.
(or1k_expand_compare): Normalize unordered comparisons.
* config/or1k/or1k.h (reg_class): Define DOUBLE_REGS.
(REG_CLASS_NAMES): Add "DOUBLE_REGS".
(REG_CLASS_CONTENTS): Add contents for DOUBLE_REGS.
* config/or1k/or1k.md (type): Add fpu.
(fpu): New instruction reservation.
(F, f, fr, fi, FI, FOP, fop): New.
(<fop><F:mode>3): New ALU instruction definition.
(float<fi><F:mode>2): New conversion instruction definition.
(fix_trunc<F:mode><fi>2): New conversion instruction definition.
(fpcmpcc): New code iterator.
(*sf_fp_insn): New instruction definition.
(cstore<F:mode>4): New expand definition.
(cbranch<F:mode>4): New expand definition.
* config/or1k/or1k.opt (msoft-float, mhard-float, mdouble-float,
munordered-float): New options.
* doc/invoke.texi: Document msoft-float, mhard-float, mdouble-float and
munordered-float.

From-SVN: r273650

5 years agoor1k: Add mrori option, fix option docs
Stafford Horne [Sun, 21 Jul 2019 21:00:47 +0000 (21:00 +0000)]
or1k: Add mrori option, fix option docs

gcc/ChangeLog:

* config.gcc (or1k*-*-*): Add mrori and mror to validation.
* doc/invoke.texi (OpenRISC Options): Add mrori option, rewrite all
documenation to be more clear.
* config/or1k/elf.opt (mboard=, mnewlib): Rewrite documentation to be
more clear.
* config/or1k/or1k.opt (mrori): New option.
(mhard-div, msoft-div, mhard-mul, msoft-mul, mcmov, mror, msext,
msfimm, mshftimm): Rewrite documentation to be more clear.
* config/or1k/or1k.md (insn_support): Add ror and rori.
(enabled): Add conditions for ror and rori.
(rotrsi3): Replace condition for shftimm with ror and rori.

gcc/testsuite/ChangeLog:

* gcc.target/or1k/ror-4.c: New file.
* gcc.target/or1k/shftimm-1.c: Update test from rotate to shift
as the shftimm option no longer controls rotate.

From-SVN: r273649

5 years agoor1k: Fix issues with msoft-div
Stafford Horne [Sun, 21 Jul 2019 20:59:50 +0000 (20:59 +0000)]
or1k: Fix issues with msoft-div

Fixes bad assembly logic with software divide as reported by Richard Selvaggi.
Also, add a basic test to verify the soft math works when enabled.

gcc/testsuite/ChangeLog:

PR target/90362
* gcc.target/or1k/div-mul-3.c: New test.

libgcc/ChangeLog:

PR target/90362
* config/or1k/lib1funcs.S (__udivsi3): Change l.sfeqi
to l.sfeq and l.sfltsi to l.sflts equivalents as the immediate
instructions are not available on every processor.  Change a
l.bnf to l.bf to fix logic issue.

From-SVN: r273648

5 years agoor1k: Fix code quality for volatile memory loads
Stafford Horne [Sun, 21 Jul 2019 20:58:54 +0000 (20:58 +0000)]
or1k: Fix code quality for volatile memory loads

Volatile memory does not match the memory_operand predicate.  This
causes extra extend/mask instructions instructions when reading
from volatile memory.  On OpenRISC loading volatile memory can be
treated the same as regular memory loads which supports combined
sign/zero extends.  Fixing this eliminates the need for extra
extend/mask instructions.

This also adds a test provided by Richard Selvaggi which uncovered the
issue while we were looking into another issue.

gcc/ChangeLog:

PR target/90363
* config/or1k/or1k.md (zero_extend<mode>si2): Update predicate.
(extend<mode>si2): Update predicate.
* gcc/config/or1k/predicates.md (volatile_mem_operand): New.
(reg_or_mem_operand): New.

gcc/testsuite/ChangeLog:

PR target/90363
* gcc.target/or1k/swap-1.c: New test.
* gcc.target/or1k/swap-2.c: New test.

From-SVN: r273647

5 years ago[PPC] Fix bootstrap for non-SVR4 targets.
Iain Sandoe [Sun, 21 Jul 2019 20:15:00 +0000 (20:15 +0000)]
[PPC] Fix bootstrap for non-SVR4 targets.

The recent change to move code into the new rs6000-call.c file is missing a
default value for the TARGET_NO_PROTOTYPE value (which only affects targets
that don’t include svr4.h).  Fixed by moving the fallback setting from
rs6000.c (which has no uses now) to rs6000-call.c.

2019-07-21  Iain Sandoe  <iain@sandoe.co.uk>

* config/rs6000/rs6000.c (TARGET_NO_PROTOTYPE): Move from here...
* config/rs6000/rs6000-call.c: ... to here.

From-SVN: r273646

5 years agore PR libfortran/91030 (Poor performance of I/O -fconvert=big-endian)
Thomas Koenig [Sun, 21 Jul 2019 15:55:49 +0000 (15:55 +0000)]
re PR libfortran/91030 (Poor performance of I/O -fconvert=big-endian)

2019-07-21  Thomas König  <tkoenig@gcc.gnu.org>

PR libfortran/91030
* gfortran.texi (GFORTRAN_FORMATTED_BUFFER_SIZE): Document
(GFORTRAN_UNFORMATTED_BUFFER_SIZE): Likewise.

2019-07-21  Thomas König  <tkoenig@gcc.gnu.org>

PR libfortran/91030
* io/unix.c (BUFFER_SIZE): Delete.
(BUFFER_FORMATTED_SIZE_DEFAULT): New variable.
(BUFFER_UNFORMATTED_SIZE_DEFAULT): New variable.
(unix_stream): Add buffer_size.
(buf_read): Use s->buffer_size instead of BUFFER_SIZE.
(buf_write): Likewise.
(buf_init): Add argument unformatted.  Handle block sizes
for unformatted vs. formatted, using defaults if provided.
(fd_to_stream): Add argument unformatted in call to buf_init.
* libgfortran.h (options_t): Add buffer_size_formatted and
buffer_size_unformatted.
* runtime/environ.c (variable_table): Add
GFORTRAN_UNFORMATTED_BUFFER_SIZE and
GFORTRAN_FORMATTED_BUFFER_SIZE.

From-SVN: r273643

5 years agoDaily bump.
GCC Administrator [Sun, 21 Jul 2019 00:16:16 +0000 (00:16 +0000)]
Daily bump.

From-SVN: r273640

5 years agors6000: Make offsettable_mem_operand use any_memory_operand
Segher Boessenkool [Sat, 20 Jul 2019 17:37:07 +0000 (19:37 +0200)]
rs6000: Make offsettable_mem_operand use any_memory_operand

* config/rs6000/predicates.md (offsettable_mem_operand): Allow volatile
memory.

From-SVN: r273633

5 years agors6000: Make input_operand use any_memory_operand
Segher Boessenkool [Sat, 20 Jul 2019 17:35:04 +0000 (19:35 +0200)]
rs6000: Make input_operand use any_memory_operand

* config/rs6000/predicates.md (input_operand): Allow volatile memory.

From-SVN: r273632

5 years agors6000: Make lwa_operand use any_memory_operand
Segher Boessenkool [Sat, 20 Jul 2019 17:34:06 +0000 (19:34 +0200)]
rs6000: Make lwa_operand use any_memory_operand

Testcase from comex, see https://lwn.net/Articles/793932/ .

* config/rs6000/predicates.md (lwa_operand): Allow volatile memory.

gcc/testsuite/
* gcc.target/powerpc/volatile-mem.c: New testcase.

From-SVN: r273631

5 years agors6000: New predicate any_memory_operand
Segher Boessenkool [Sat, 20 Jul 2019 17:28:37 +0000 (19:28 +0200)]
rs6000: New predicate any_memory_operand

The new predicate accepts both memory_operand and volatile_mem_operand.

* config/rs6000/predicates.md (volatile_mem_operand): Modernize syntax.
(any_memory_operand): New predicate.
(reg_or_mem_operand): Use it.

From-SVN: r273630

5 years agore PR target/91204 (ICE in expand_expr_real_2, at expr.c:9215 with -O3)
Jakub Jelinek [Sat, 20 Jul 2019 17:13:00 +0000 (19:13 +0200)]
re PR target/91204 (ICE in expand_expr_real_2, at expr.c:9215 with -O3)

PR target/91204
* optabs.c (expand_unop): As fallback, expand ~op0 as op0 ^ -1.

* gcc.c-torture/compile/pr91204.c: New test.

From-SVN: r273629

5 years agopa.h (hppa_profile_hook): Delete declaration.
John David Anglin [Sat, 20 Jul 2019 16:47:25 +0000 (16:47 +0000)]
pa.h (hppa_profile_hook): Delete declaration.

* config/pa/pa.h (hppa_profile_hook): Delete declaration.
* config/pa/pa-protos.h (hppa_profile_hook): Add declaration.

From-SVN: r273628

5 years agoFix ICE on class template argument deduction with inherited ctor.
Jason Merrill [Sat, 20 Jul 2019 14:43:49 +0000 (10:43 -0400)]
Fix ICE on class template argument deduction with inherited ctor.

In general, when we see a dependent using-declaration we don't know whether
it names a function or not, so it doesn't get an OVERLOAD unless we see
overloads of the same name in the current class.  In the case of an
inherited constructor we could figure that out from the name, but it's
simpler to handle USING_DECL properly.

* cp-tree.h (ovl_iterator::using_p): A USING_DECL by itself was also
introduced by a using-declaration.

From-SVN: r273623

5 years agoReduce memory consumption for push/pop_access_scope.
Jason Merrill [Sat, 20 Jul 2019 13:48:38 +0000 (09:48 -0400)]
Reduce memory consumption for push/pop_access_scope.

I was seeing memory consumption issues on the concepts-cxx2a
branch. push_scope was, surprisingly, at the top of -fmem-report, and
push_access_scope was pretty high.  Fixing them was pretty simple.

* name-lookup.c (leave_scope): Do add class levels other than
previous_class_level to free_binding_level.
(invalidate_class_lookup_cache): Move from class.c, add to
free_binding_level.
* pt.c (saved_access_scope): Change from list to vec.

From-SVN: r273622

5 years agotree.def (OMP_LOOP): New tree code.
Jakub Jelinek [Sat, 20 Jul 2019 11:21:42 +0000 (13:21 +0200)]
tree.def (OMP_LOOP): New tree code.

* tree.def (OMP_LOOP): New tree code.
* tree-core.h (enum omp_clause_code): Add OMP_CLAUSE_BIND.
(enum omp_clause_bind_kind): New enum.
(struct tree_omp_clause): Add subcode.bind_kind.
* tree.h (OMP_LOOP_CHECK): Rename to ...
(OMP_LOOPING_CHECK): ... this.
(OMP_FOR_BODY, OMP_FOR_CLAUSES, OMP_FOR_INIT, OMP_FOR_COND,
OMP_FOR_INCR, OMP_FOR_PRE_BODY, OMP_FOR_ORIG_DECLS): Use
OMP_LOOPING_CHECK instead of OMP_LOOP_CHECK.
(OMP_CLAUSE_BIND_KIND): Define.
* tree.c (omp_clause_num_ops, omp_clause_code_name): Add
bind clause entries.
(walk_tree_1): Handle OMP_CLAUSE_BIND.
* tree-pretty-print.c (dump_omp_clause): Likewise.
(dump_generic_node): Handle OMP_LOOP.
* gimplify.c (enum omp_region_type): Add ORT_IMPLICIT_TARGET.
(in_omp_construct): New variable.
(is_gimple_stmt): Handle OMP_LOOP.
(gimplify_scan_omp_clauses): For lastprivate don't set
check_non_private if code == OMP_LOOP.  For reduction clause
on OMP_LOOP combined with parallel or teams propagate as shared
on the combined construct.  Handle OMP_CLAUSE_BIND.
(gimplify_adjust_omp_clauses): Handle OMP_CLAUSE_BIND.
(gimplify_omp_for): Pass OMP_LOOP instead of OMP_{FOR,DISTRIBUTE}
for constructs from a loop construct to gimplify_scan_omp_clauses.
Don't predetermine iterator linear on OMP_SIMD from loop construct.
(replace_reduction_placeholders, gimplify_omp_loop): New functions.
(gimplify_omp_workshare): Use ORT_IMPLICIT_TARGET instead of trying
to match the implicit ORT_TARGET construct around whole body.
Temporarily clear in_omp_construct when processing body.
(gimplify_expr): Handle OMP_LOOP.  For OMP_MASTER, OMP_TASKGROUP
etc. temporarily set in_omp_construct when processing body.
(gimplify_body): Create ORT_IMPLICIT_TARGET instead of ORT_TARGET.
* omp-low.c (struct omp_context): Add loop_p.
(build_outer_var_ref): Treat ctx->loop_p similarly to simd construct
in that the original var might be private.
(scan_sharing_clauses): Handle OMP_CLAUSE_BIND.
(check_omp_nesting_restrictions): Adjust nesting restrictions for
addition of loop construct.
(scan_omp_1_stmt): Allow setjmp inside of loop construct.
gcc/c-family/
* c-pragma.h (enum pragma_kind): Add PRAGMA_OMP_LOOP.
(enum pragma_omp_clause): Add PRAGMA_OMP_CLAUSE_BIND.
* c-pragma.c (omp_pragmas_simd): Add PRAGMA_OMP_LOOP entry.
* c-common.h (enum c_omp_clause_split): Add C_OMP_CLAUSE_SPLIT_LOOP.
* c-omp.c (c_omp_split_clauses): Add support for 4 new combined
constructs with the loop construct.
gcc/c/
* c-parser.c (c_parser_omp_clause_name): Handle bind clause.
(c_parser_omp_clause_bind): New function.
(c_parser_omp_all_clauses): Handle PRAGMA_OMP_CLAUSE_BIND.
(OMP_LOOP_CLAUSE_MASK): Define.
(c_parser_omp_loop): New function.
(c_parser_omp_parallel, c_parser_omp_teams): Handle parsing of
loop combined with parallel or teams.
(c_parser_omp_construct): Handle PRAGMA_OMP_LOOP.
* c-typeck.c (c_finish_omp_clauses): Handle OMP_CLAUSE_BIND.
gcc/cp/
* cp-tree.h (OMP_FOR_GIMPLIFYING_P): Use OMP_LOOPING_CHECK
instead of OMP_LOOP_CHECK.
* parser.c (cp_parser_omp_clause_name): Handle bind clause.
(cp_parser_omp_clause_bind): New function.
(cp_parser_omp_all_clauses): Handle PRAGMA_OMP_CLAUSE_BIND.
(OMP_LOOP_CLAUSE_MASK): Define.
(cp_parser_omp_loop): New function.
(cp_parser_omp_parallel, cp_parser_omp_teams): Handle parsing of
loop combined with parallel or teams.
(cp_parser_omp_construct): Handle PRAGMA_OMP_LOOP.
(cp_parser_pragma): Likewise.
* pt.c (tsubst_expr): Handle OMP_LOOP.
* semantics.c (finish_omp_clauses): Handle OMP_CLAUSE_BIND.
gcc/testsuite/
* c-c++-common/gomp/cancel-1.c: Adjust expected diagnostic wording.
* c-c++-common/gomp/clauses-1.c (foo, baz, bar): Add order(concurrent)
clause where allowed.  Add combined constructs with loop with all
possible clauses.
(qux): New function.
* c-c++-common/gomp/loop-1.c: New test.
* c-c++-common/gomp/loop-2.c: New test.
* c-c++-common/gomp/loop-3.c: New test.
* c-c++-common/gomp/loop-4.c: New test.
* c-c++-common/gomp/loop-5.c: New test.
* c-c++-common/gomp/order-3.c: Adjust expected diagnostic wording.
* c-c++-common/gomp/simd-setjmp-1.c: New test.
* c-c++-common/gomp/teams-2.c: Adjust expected diagnostic wording.
libgomp/
* testsuite/libgomp.c-c++-common/loop-1.c: New test.

From-SVN: r273621

5 years agoomp-low.c (lower_rec_input_clauses): Don't force simd arrays for lastprivate non...
Jakub Jelinek [Sat, 20 Jul 2019 06:38:59 +0000 (08:38 +0200)]
omp-low.c (lower_rec_input_clauses): Don't force simd arrays for lastprivate non-addressable iterator of a...

* omp-low.c (lower_rec_input_clauses): Don't force simd arrays for
lastprivate non-addressable iterator of a collapse(1) simd.

* gcc.dg/vect/vect-simd-16.c: New test.

From-SVN: r273620

5 years agoDaily bump.
GCC Administrator [Sat, 20 Jul 2019 00:16:21 +0000 (00:16 +0000)]
Daily bump.

From-SVN: r273615

5 years agocompiler: don't export bodies for functions marked "go:noinline"
Ian Lance Taylor [Fri, 19 Jul 2019 23:10:55 +0000 (23:10 +0000)]
compiler: don't export bodies for functions marked "go:noinline"

    The current Mark_inline_candidates helper looks only at budget when
    deciding to mark a function or method as inline (with the proviso that
    IR constructs not yet supported by the inliner are given artificially
    high cost). This patch changes the helper to also look at whether a
    function has the "go:noinline" pragma; if it does have the pragma
    there is no point putting it into the export data (it will just make
    the export data bigger).

    Reviewed-on: https://go-review.googlesource.com/c/gofrontend/+/186923

From-SVN: r273611

5 years agors6000-call.c (HAVE_AS_GNU_ATTRIBUTE): define value as in rs6000.c.
Bill Seurer [Fri, 19 Jul 2019 22:14:56 +0000 (22:14 +0000)]
rs6000-call.c (HAVE_AS_GNU_ATTRIBUTE): define value as in rs6000.c.

2019-07-17  Bill Seurer  <seurer@linux.vnet.ibm.com>

* config/rs6000/rs6000-call.c (HAVE_AS_GNU_ATTRIBUTE): define value
as in rs6000.c.

From-SVN: r273610

5 years agostl_tempbuf.h (__detail::__return_temporary_buffer): Fix sized deallocation size...
François Dumont [Fri, 19 Jul 2019 21:14:41 +0000 (21:14 +0000)]
stl_tempbuf.h (__detail::__return_temporary_buffer): Fix sized deallocation size computation.

2019-07-19  François Dumont  <fdumont@gcc.gnu.org>

* include/bits/stl_tempbuf.h (__detail::__return_temporary_buffer): Fix
sized deallocation size computation.

From-SVN: r273609

5 years ago[Darwin] More specs TLC.
Iain Sandoe [Fri, 19 Jul 2019 20:10:33 +0000 (20:10 +0000)]
[Darwin] More specs TLC.

This strips out a few driver specs that are only specifying a default state.
Also warn on an option now ignored, and add some comments to the driver specs
section.

2019-07-19  Iain Sandoe  <iain@sandoe.co.uk>

* config/darwin.h (DRIVER_SELF_SPECS): Ignore X and Mach specs which
refer to default conditions.  Warn for the 'y' spec which is ignored
by current linkers.

From-SVN: r273608

5 years ago[PATCH, rs6000] Split up rs6000.c.
Bill Seurer [Fri, 19 Jul 2019 18:33:59 +0000 (18:33 +0000)]
[PATCH, rs6000] Split up rs6000.c.

The source file rs6000.c has grown to unreasonable size and is being
split up into several smaller source files.  This should improve
compilation speed for building gcc.

This is the second of several patches to do this and moves most of the
function call and builtin code to a new source file.

Bootstrapped and tested on powerpc64le-unknown-linux-gnu and
powerpc64-unknown-linux-gnu with no regressions.  Is this ok for trunk?

2019-07-17  Bill Seurer  <seurer@linux.vnet.ibm.com>

* config/rs6000/rs6000.c (builtin_description, cpu_is_info,
cpu_supports_info, builtin_hash_struct, builtin_hasher,
builtin_hash_table, rs6000_builtin_info_type, rs6000_builtin_info,
rs6000_aggregate_candidate, rs6000_discover_homogeneous_aggregate,
rs6000_return_in_memory, rs6000_return_in_msb, call_ABI_of_interest,
init_cumulative_args, rs6000_promote_function_mode,
rs6000_must_pass_in_stack, is_complex_IBM_long_double,
abi_v4_pass_in_fpr, rs6000_function_arg_padding,
rs6000_function_arg_boundary, rs6000_parm_offset,
rs6000_parm_start, rs6000_arg_size,
rs6000_darwin64_record_arg_advance_flush,
rs6000_darwin64_record_arg_advance_recurse,
rs6000_darwin64_struct_check_p, rs6000_function_arg_advance_1,
rs6000_function_arg_advance, rs6000_darwin64_record_arg_flush,
rs6000_darwin64_record_arg_recurse, rs6000_darwin64_record_arg,
rs6000_mixed_function_arg, rs6000_psave_function_arg,
rs6000_finish_function_arg, rs6000_function_arg,
rs6000_arg_partial_bytes, rs6000_pass_by_reference,
rs6000_parm_needs_stack, rs6000_function_parms_need_stack,
rs6000_reg_parm_stack_space, rs6000_move_block_from_reg,
setup_incoming_varargs, rs6000_build_builtin_va_list, rs6000_va_start,
rs6000_gimplify_va_arg, def_builtin, bdesc_3arg, bdesc_dst,
bdesc_2arg, bdesc_altivec_preds, bdesc_abs, bdesc_1arg, bdesc_0arg,
bdesc_htm, rs6000_overloaded_builtin_p, rs6000_overloaded_builtin_name,
rs6000_expand_zeroop_builtin, rs6000_expand_mtfsf_builtin,
rs6000_expand_mtfsb_builtin, rs6000_expand_set_fpscr_rn_builtin,
rs6000_expand_set_fpscr_drn_builtin, rs6000_expand_unop_builtin,
altivec_expand_abs_builtin, rs6000_expand_binop_builtin,
altivec_expand_predicate_builtin, swap_endian_selector_for_mode,
altivec_expand_lv_builtin, altivec_expand_stxvl_builtin,
altivec_expand_stv_builtin, htm_spr_num, rs6000_htm_spr_icode,
htm_expand_builtin, cpu_expand_builtin, rs6000_expand_ternop_builtin,
altivec_expand_dst_builtin, altivec_expand_vec_init_builtin,
get_element_number, altivec_expand_vec_set_builtin,
altivec_expand_vec_ext_builtin, altivec_expand_builtin,
rs6000_builtin_is_supported_p, rs6000_invalid_builtin,
rs6000_fold_builtin, rs6000_builtin_valid_without_lhs,
fold_build_vec_cmp, fold_compare_helper, fold_mergehl_helper,
fold_mergeeo_helper, rs6000_gimple_fold_builtin,
rs6000_expand_builtin, rs6000_vector_type,
rs6000_init_builtins, rs6000_builtin_decl, altivec_init_builtins,
htm_init_builtins, builtin_function_type, rs6000_common_init_builtins,
rs6000_internal_arg_pointer, rs6000_output_mi_thunk): Move
to rs6000-call.c.
* config/rs6000/rs6000-call.c (builtin_description, cpu_is_info,
cpu_supports_info, builtin_hash_struct, builtin_hasher,
builtin_hash_table, rs6000_builtin_info_type, rs6000_builtin_info,
rs6000_aggregate_candidate, rs6000_discover_homogeneous_aggregate,
rs6000_return_in_memory, rs6000_return_in_msb, call_ABI_of_interest,
init_cumulative_args, rs6000_promote_function_mode,
rs6000_must_pass_in_stack, is_complex_IBM_long_double,
abi_v4_pass_in_fpr, rs6000_function_arg_padding,
rs6000_function_arg_boundary, rs6000_parm_offset,
rs6000_parm_start, rs6000_arg_size,
rs6000_darwin64_record_arg_advance_flush,
rs6000_darwin64_record_arg_advance_recurse,
rs6000_darwin64_struct_check_p, rs6000_function_arg_advance_1,
rs6000_function_arg_advance, rs6000_darwin64_record_arg_flush,
rs6000_darwin64_record_arg_recurse, rs6000_darwin64_record_arg,
rs6000_mixed_function_arg, rs6000_psave_function_arg,
rs6000_finish_function_arg, rs6000_function_arg,
rs6000_arg_partial_bytes, rs6000_pass_by_reference,
rs6000_parm_needs_stack, rs6000_function_parms_need_stack,
rs6000_reg_parm_stack_space, rs6000_move_block_from_reg,
setup_incoming_varargs, rs6000_build_builtin_va_list, rs6000_va_start,
rs6000_gimplify_va_arg, def_builtin, bdesc_3arg, bdesc_dst,
bdesc_2arg, bdesc_altivec_preds, bdesc_abs, bdesc_1arg, bdesc_0arg,
bdesc_htm, rs6000_overloaded_builtin_p, rs6000_overloaded_builtin_name,
rs6000_expand_zeroop_builtin, rs6000_expand_mtfsf_builtin,
rs6000_expand_mtfsb_builtin, rs6000_expand_set_fpscr_rn_builtin,
rs6000_expand_set_fpscr_drn_builtin, rs6000_expand_unop_builtin,
altivec_expand_abs_builtin, rs6000_expand_binop_builtin,
altivec_expand_predicate_builtin, swap_endian_selector_for_mode,
altivec_expand_lv_builtin, altivec_expand_stxvl_builtin,
altivec_expand_stv_builtin, htm_spr_num, rs6000_htm_spr_icode,
htm_expand_builtin, cpu_expand_builtin, rs6000_expand_ternop_builtin,
altivec_expand_dst_builtin, altivec_expand_vec_init_builtin,
get_element_number, altivec_expand_vec_set_builtin,
altivec_expand_vec_ext_builtin, altivec_expand_builtin,
rs6000_builtin_is_supported_p, rs6000_invalid_builtin,
rs6000_fold_builtin, rs6000_builtin_valid_without_lhs,
fold_build_vec_cmp, fold_compare_helper, fold_mergehl_helper,
fold_mergeeo_helper, rs6000_gimple_fold_builtin,
rs6000_expand_builtin, rs6000_vector_type,
rs6000_init_builtins, rs6000_builtin_decl, altivec_init_builtins,
htm_init_builtins, builtin_function_type, rs6000_common_init_builtins,
rs6000_internal_arg_pointer, rs6000_output_mi_thunk: Move
to here from rs6000.c.
* config/rs6000/rs6000-internal.h: (rs6000_darwin64_struct_check_p,
rs6000_discover_homogeneous_aggregate, rs6000_output_mi_thunk,
rs6000_output_addr_const_extra, rs6000_gimple_fold_builtin,
rs6000_invalid_builtin, rs6000_build_builtin_va_list, rs6000_va_start,
rs6000_gimplify_va_arg, rs6000_promote_function_mode,
rs6000_return_in_memory, rs6000_return_in_msb,
rs6000_pass_by_reference, setup_incoming_varargs,
rs6000_function_arg_boundary, rs6000_must_pass_in_stack,
rs6000_arg_partial_bytes, rs6000_function_arg_advance,
rs6000_function_arg_padding, rs6000_function_arg,
rs6000_darwin64_record_arg, rs6000_internal_arg_pointer,
rs6000_init_builtins, rs6000_builtin_decl, rs6000_expand_builtin,
rs6000_fold_builtin, rs6000_passes_ieee128, rs6000_passes_float,
rs6000_passes_long_double, rs6000_passes_vector,
rs6000_returns_struct, cpu_builtin_p, tree builtin_mode_to_type,
altivec_builtin_mask_for_load) Add declarations.
* config/rs6000/t-rs6000: Add new source file rs6000-call.c.
* config/config.gcc: Add new source file rs6000-call.c to garbage
collector and extra_objs.

From-SVN: r273607

5 years agotree-ssa-dse.c (initialize_ao_ref_for_dse): Handle strncpy.
Jeff Law [Fri, 19 Jul 2019 17:04:51 +0000 (11:04 -0600)]
tree-ssa-dse.c (initialize_ao_ref_for_dse): Handle strncpy.

* tree-ssa-dse.c (initialize_ao_ref_for_dse): Handle
strncpy.  Drop some trivial dead code.
(maybe_trim_memstar_call): Handle strncpy.

* gcc.dg/tree-ssa/ssa-dse-37.c: New test.
* gcc.dg/tree-ssa/ssa-dse-38.c: New test.

From-SVN: r273606

5 years agore PR tree-optimization/91211 (wrong code with __builtin_memset() and __builtin_memcp...
Richard Biener [Fri, 19 Jul 2019 16:19:39 +0000 (16:19 +0000)]
re PR tree-optimization/91211 (wrong code with __builtin_memset() and __builtin_memcpy() at -O1 and above)

2019-07-19  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91211
* tree-ssa-sccvn.c (vn_walk_cb_data::push_partial_def): Fix
memset encoding size.

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

From-SVN: r273605

5 years agore PR target/91204 (ICE in expand_expr_real_2, at expr.c:9215 with -O3)
Uros Bizjak [Fri, 19 Jul 2019 14:36:49 +0000 (16:36 +0200)]
re PR target/91204 (ICE in expand_expr_real_2, at expr.c:9215 with -O3)

PR target/91204
* config/i386/mmx.md (one_cmpl<mode>2): New expander.

From-SVN: r273604

5 years agore PR ipa/91194 (A suspicious condition in recursive_inlining)
Jan Hubicka [Fri, 19 Jul 2019 14:31:09 +0000 (16:31 +0200)]
re PR ipa/91194 (A suspicious condition in recursive_inlining)

PR ipa/91194
* ipa-inline.c (recursive_inlining): Fix limits check.

From-SVN: r273603

5 years agore PR tree-optimization/91200 (ICE on valid code at -O1: verify_ssa failed)
Richard Biener [Fri, 19 Jul 2019 12:24:53 +0000 (12:24 +0000)]
re PR tree-optimization/91200 (ICE on valid code at -O1: verify_ssa failed)

2019-07-19  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91200
* tree-ssa-phiopt.c (cond_store_replacement): Check we have
no PHI nodes in middle-bb.

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

From-SVN: r273602

5 years ago[AArch64] Rename +bitperm to +sve2-bitperm
Richard Sandiford [Fri, 19 Jul 2019 11:24:31 +0000 (11:24 +0000)]
[AArch64] Rename +bitperm to +sve2-bitperm

After some discussion, we've decided to rename the +bitperm feature
flag to +sve2-bitperm, so that it's consistent with the other SVE2
feature flags.  The associated macro was already
__ARM_FEATURE_SVE2_BITPERM, so only the feature flag itself
needs to change.

2019-07-19  Richard Sandiford  <richard.sandiford@arm.com>

gcc/
* doc/invoke.texi: Rename the AArch64 +bitperm extension flag
to +sve-bitperm.
* config/aarch64/aarch64-option-extensions.def: Likewise.

From-SVN: r273600

5 years agore PR middle-end/91190 (ICE on valid code: in hashtab_chk_error, at hash-table.c...
Jakub Jelinek [Fri, 19 Jul 2019 10:26:23 +0000 (12:26 +0200)]
re PR middle-end/91190 (ICE on valid code: in hashtab_chk_error, at hash-table.c:137)

PR middle-end/91190
* function.c (insert_temp_slot_address): Store into the hash table
a copy of address to avoid RTL sharing issues.

* gcc.c-torture/compile/pr91190.c: New test.

From-SVN: r273599

5 years ago* config/abi/post/m68k-linux-gnu/baseline_symbols.txt: Update.
Andreas Schwab [Fri, 19 Jul 2019 09:57:08 +0000 (09:57 +0000)]
* config/abi/post/m68k-linux-gnu/baseline_symbols.txt: Update.

From-SVN: r273598

5 years agore PR tree-optimization/91207 (Wrong code with -O3)
Richard Biener [Fri, 19 Jul 2019 08:47:41 +0000 (08:47 +0000)]
re PR tree-optimization/91207 (Wrong code with -O3)

2019-07-19  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91207
Revert
2019-07-17  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91178
* tree-vect-stmts.c (get_group_load_store_type): For SLP
loads with a gap larger than the vector size always use
VMAT_STRIDED_SLP.
(vectorizable_load): For VMAT_STRIDED_SLP with a permutation
avoid loading vectors that are only contained in the gap
and thus are not needed.

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

From-SVN: r273593

5 years agoPR c++/90101 - dependent class non-type parameter.
Jason Merrill [Fri, 19 Jul 2019 07:29:15 +0000 (03:29 -0400)]
PR c++/90101 - dependent class non-type parameter.

We shouldn't complain that a dependent type is incomplete.

* pt.c (invalid_nontype_parm_type_p): Check for dependent class type.

From-SVN: r273592

5 years agoPR c++/90098 - partial specialization and class non-type parms.
Jason Merrill [Fri, 19 Jul 2019 06:52:47 +0000 (02:52 -0400)]
PR c++/90098 - partial specialization and class non-type parms.

A non-type template parameter of class type used in an expression has
const-qualified type; the pt.c hunks deal with this difference from the
unqualified type of the parameter declaration.  WAhen we use such a
parameter as an argument to another template, we don't want to confuse
things by copying it, we should pass it straight through.  And we might as
well skip copying other classes in constant evaluation context in a
template, too; we'll get the copy semantics at instantiation time.

PR c++/90099
PR c++/90101
* call.c (build_converted_constant_expr_internal): Don't copy.
* pt.c (process_partial_specialization): Allow VIEW_CONVERT_EXPR
around class non-type parameter.
(unify) [TEMPLATE_PARM_INDEX]: Ignore cv-quals.

From-SVN: r273591

5 years agoDaily bump.
GCC Administrator [Fri, 19 Jul 2019 00:16:26 +0000 (00:16 +0000)]
Daily bump.

From-SVN: r273590

5 years agostl_tempbuf.h (__detail::__return_temporary_buffer): New.
François Dumont [Thu, 18 Jul 2019 21:52:35 +0000 (21:52 +0000)]
stl_tempbuf.h (__detail::__return_temporary_buffer): New.

2019-07-18  François Dumont  <fdumont@gcc.gnu.org>

* include/bits/stl_tempbuf.h (__detail::__return_temporary_buffer): New.
(~_Temporary_buffer()): Use latter.
(_Temporary_buffer(_FIterator, size_type)): Likewise.

From-SVN: r273586

5 years agoi386.md (*addqi_2_slp): Remove.
Uros Bizjak [Thu, 18 Jul 2019 19:59:55 +0000 (21:59 +0200)]
i386.md (*addqi_2_slp): Remove.

* config/i386/i386.md (*addqi_2_slp): Remove.
(*<code>qi_2_slp): Ditto.

From-SVN: r273583

5 years agoRename function.
Michael Meissner [Thu, 18 Jul 2019 19:07:13 +0000 (19:07 +0000)]
Rename function.

2019-07-18  Michael Meissner  <meissner@linux.ibm.com>

* config/rs6000/predicates.md (prefixed_mem_operand): Call
rs6000_prefixed_address_mode_p instead of rs6000_prefixed_address.
* config/rs6000/rs6000-protos.h (rs6000_prefixed_address_mode_p):
Rename function from rs6000_prefixed_address.
* config/rs6000/rs6000.c (rs6000_prefixed_address_mode_p): Rename
function from rs6000_prefixed_address.

From-SVN: r273580

5 years agoUpdate PowerPC compiler for pc-relative support.
Michael Meissner [Thu, 18 Jul 2019 18:16:43 +0000 (18:16 +0000)]
Update PowerPC compiler for pc-relative support.

2019-07-18  Michael Meissner  <meissner@linux.ibm.com>

* config/rs6000/aix.h (TARGET_HAS_TOC): Rename TARGET_TOC to
TARGET_HAS_TOC.
(TARGET_TOC): Likewise.
(TARGET_NO_TOC): Delete here, define TARGET_NO_TOC_OR_PCREL in
rs6000.h.
* config/rs6000/darwin.h (TARGET_HAS_TOC): Rename TARGET_TOC to
TARGET_HAS_TOC.
(TARGET_TOC): Likewise.
(TARGET_NO_TOC): Delete here, define TARGET_NO_TOC_OR_PCREL in
rs6000.h.
* config/rs6000/linux64.h (TARGET_HAS_TOC): Rename TARGET_TOC to
TARGET_HAS_TOC.
(TARGET_TOC): Likewise.
* config/rs6000/rs6000.c (rs6000_option_override_internal): Add
check to require -mcmodel=medium for pc-relative addressing.
(create_TOC_reference): Add assertion for TARGET_TOC.
(rs6000_legitimize_address): Use TARGET_NO_TOC_OR_PCREL instead of
TARGET_NO_TOC.
(rs6000_emit_move): Likewise.
(TOC_alias_set): Rename TOC alias set static variable from 'set'
to 'TOC_alias_set'.
(get_TOC_alias_set): Likewise.
(output_toc): Use TARGET_NO_TOC_OR_PCREL instead of
TARGET_NO_TOC.
(rs6000_can_eliminate): Likewise.
* config/rs6000/rs6000.h (TARGET_TOC): Define in terms of
TARGET_HAS_TOC and not pc-relative.
(TARGET_NO_TOC_OR_PCREL): New macro to replace TARGET_NO_TOC.
* config/rs6000/sysv4.h (TARGET_HAS_TOC): Rename TARGET_TOC to
TARGET_HAS_TOC.
(TARGET_TOC): Likewise.
(TARGET_NO_TOC): Delete here, define TARGET_NO_TOC_OR_PCREL in
rs6000.h.

From-SVN: r273579

5 years agore PR target/91188 (strict_low_part operations do not work)
Uros Bizjak [Thu, 18 Jul 2019 17:17:31 +0000 (19:17 +0200)]
re PR target/91188 (strict_low_part operations do not work)

PR target/91188
* config/i386/i386.md (*addqi_1_slp): Use register_operand predicate
for operand 0.  Do not use (match_dup) to match operand 1 with
operand 0.  Add check in insn constraint that either input operand
matches operand 0.  Use SWI12 mode iterator to also handle
HImode operands.
(*and<mode>_1_slp): Ditto.
(*<code>qi_1_slp): Ditto.
(*sub<mode>_1_slp): Use register_operand predicate for operand 0.
Do not use (match_dup) to match operand 1 with operand 0.  Add
check in insn constraint that operand 1 matches operand 0.
Use SWI12 mode iterator to also handle HImode operands.
(*ashl<mode>3_1_slp): Ditto.
(*<shift_insn><mode>3_1_slp): Ditto.
(*<rotate_insn><mode>3_1_slp): Ditto.

testsuite/ChangeLog:

PR target/91188
* gcc.target/i386/pr91188-1a.c: New test.
* gcc.target/i386/pr91188-1b.c: Ditto.
* gcc.target/i386/pr91188-1c.c: Ditto.
* gcc.target/i386/pr91188-2a.c: Ditto.
* gcc.target/i386/pr91188-2b.c: Ditto.
* gcc.target/i386/pr91188-2c.c: Ditto.

From-SVN: r273578

5 years agocompiler: fix bug in importing blocks from inline functions
Ian Lance Taylor [Thu, 18 Jul 2019 16:51:00 +0000 (16:51 +0000)]
compiler: fix bug in importing blocks from inline functions

    This patch fixes a buglet in the function body importer. Add hooks for
    keeping a stack of blocks corresponding to the block nesting in the
    imported function. This ensures that local variables and temps wind up
    correctly scoped and don't introduce collisions.

    New test case for this problem in CL 186717.

    Fixes golang/go#33158.

    Reviewed-on: https://go-review.googlesource.com/c/gofrontend/+/186757

From-SVN: r273577

5 years agoMakefile.rtl, [...]: Introduce a "STANDALONE" mode where C runtime files do not have...
Arnaud Charlet [Thu, 18 Jul 2019 16:37:40 +0000 (16:37 +0000)]
Makefile.rtl, [...]: Introduce a "STANDALONE" mode where C runtime files do not have any dependency...

* Makefile.rtl, expect.c, env.c, aux-io.c, mkdir.c, initialize.c,
cstreams.c, raise.c, tracebak.c, adadecode.c, init.c, raise-gcc.c,
argv.c, adaint.c, adaint.h, ctrl_c.c, sysdep.c, rtinit.c, cio.c,
seh_init.c, exit.c, targext.c: Introduce a "STANDALONE" mode where C
runtime files do not have any dependency on GCC include files.
Remove unnecessary includes.
Remove remaining references to VMS in runtime C file.
* runtime.h: new File.

From-SVN: r273576

5 years ago[patch2/2][arm]: remove builtin expand for sha1
Sylvia Taylor [Thu, 18 Jul 2019 16:02:05 +0000 (16:02 +0000)]
[patch2/2][arm]: remove builtin expand for sha1

This patch removes the builtin expand handling for sha1h/c/m/p and
replaces it with expand patterns. This should make it more consistent
with how we handle intrinsic implementations and cleans up the custom
sha1 code in the arm_expand builtins for unop and ternop.

2019-07-18  Sylvia Taylor  <sylvia.taylor@arm.com>

* config/arm/arm-builtins.c
(arm_expand_ternop_builtin): Remove explicit sha1 builtin handling.
(arm_expand_unop_builtin): Likewise.
* config/arm/crypto.md
(crypto_sha1h): Convert from define_insn to define_expand.
(crypto_<crypto_pattern>): Likewise.
(crypto_sha1h_lb): New define_insn.
(crypto_<crypto_pattern>_lb): Likewise.

From-SVN: r273575

5 years ago[patch1/2][arm][PR90317]: fix sha1 patterns
Sylvia Taylor [Thu, 18 Jul 2019 15:42:13 +0000 (15:42 +0000)]
[patch1/2][arm][PR90317]: fix sha1 patterns

This patch fixes:

1) Ice message thrown when using the crypto_sha1h intrinsic due to
incompatible mode used for zero_extend. Removed zero extend as it is
not a good choice for vector modes and using an equivalent single
mode like TI (128bits) instead of V4SI produces extra instructions
making it inefficient.

This affects gcc version 8 and above.

2) Incorrect combine optimizations made due to vec_select usage
in the sha1 patterns on arm. The patterns should only combine
a vec select within a sha1h<op> instruction when the lane is 0.

This affects gcc version 5 and above.

- Fixed by explicitly declaring the valid const int for such
optimizations. For cases when the lane is not 0, the vector
lane selection now occurs in a e.g. vmov instruction prior
to sha1h<op>.

- Updated the sha1h testcases on arm to check for additional
cases with custom vector lane selection.

The intrinsic functions for the sha1 patterns have also been
simplified which seems to eliminate extra vmovs like:
- vmov.i32 q8, #0.

2019-07-18  Sylvia Taylor  <sylvia.taylor@arm.com>

        PR target/90317
        * config/arm/arm_neon.h
        (vsha1h_u32): Refactor.
        (vsha1cq_u32): Likewise.
        (vsha1pq_u32): Likewise.
        (vsha1mq_u32): Likewise.
        * config/arm/crypto.md:
        (crypto_sha1h): Remove zero extend, correct vec select.
        (crypto_sha1c): Correct vec select.
        (crypto_sha1m): Likewise.
        (crypto_sha1p): Likewise.

        * gcc.target/arm/crypto-vsha1cq_u32.c (foo): Change return type to
        uint32_t.
        (GET_LANE, TEST_SHA1C_VEC_SELECT): New.
        * gcc.target/arm/crypto-vsha1h_u32.c (foo): Change return type to
        uint32_t.
        (GET_LANE, TEST_SHA1H_VEC_SELECT): New.
        * gcc.target/arm/crypto-vsha1mq_u32.c (foo): Change return type to
        uint32_t.
        (GET_LANE, TEST_SHA1M_VEC_SELECT): New.
        * gcc.target/arm/crypto-vsha1pq_u32.c (foo): Change return type to
        uint32_t.
        (GET_LANE, TEST_SHA1P_VEC_SELECT): New.

From-SVN: r273574

5 years agodemangle.h (rust_is_mangled): Move to libiberty/rust-demangle.h.
Eduard-Mihai Burtescu [Thu, 18 Jul 2019 14:10:51 +0000 (16:10 +0200)]
demangle.h (rust_is_mangled): Move to libiberty/rust-demangle.h.

include/
* demangle.h (rust_is_mangled): Move to libiberty/rust-demangle.h.
(rust_demangle_sym): Move to libiberty/rust-demangle.h.
libiberty/
* cplus-dem.c: Include rust-demangle.h.
* rust-demangle.c: Include rust-demangle.h.
* rust-demangle.h: New file.

From-SVN: r273573

5 years ago[arm] Fix incorrect modes with 'borrow' operations
Richard Earnshaw [Thu, 18 Jul 2019 13:56:52 +0000 (13:56 +0000)]
[arm] Fix incorrect modes with 'borrow' operations

Looking through the arm backend I noticed that the modes used to pass
comparison types into subtract-with-carry operations were being
incorrectly set.  The result is that the compiler is not truly
self-consistent.  To clean this up I've introduced a new predicate,
arm_borrow_operation (borrowed from the AArch64 backend) which can
match the comparison type with the required mode and then fixed all
the patterns to use this.  The split patterns that were generating
incorrect modes have all obviously been fixed as well.

The basic rule for the use of a borrow is:
- if the condition code was set by a 'subtract-like' operation (subs, cmp),
  then use CCmode and LTU.
- if the condition code was by unsigned overflow of addition (adds), then
  use CC_Cmode and GEU.

* config/arm/predicates.md (arm_borrow_operation): New predicate.
* config/arm/arm.c (subdi3_compare1): Use CCmode for the split.
(arm_subdi3, subdi_di_zesidi, subdi_di_sesidi): Likewise.
(subdi_zesidi_zesidi): Likewise.
(negdi2_compare, negdi2_insn): Likewise.
(negdi_extensidi): Likewise.
(negdi_zero_extendsidi): Likewise.
(arm_cmpdi_insn): Likewise.
(subsi3_carryin): Use arm_borrow_operation.
(subsi3_carryin_const): Likewise.
(subsi3_carryin_const0): Likewise.
(subsi3_carryin_compare): Likewise.
(subsi3_carryin_compare_const): Likewise.
(subsi3_carryin_compare_const0): Likewise.
(subsi3_carryin_shift): Likewise.
(rsbsi3_carryin_shift): Likewise.
(negsi2_carryin_compare): Likewise.

From-SVN: r273572

5 years agolto-common.c (gimple_register_canonical_type_1): Do not look for non-ODR conflicts...
Jan Hubicka [Thu, 18 Jul 2019 13:08:34 +0000 (15:08 +0200)]
lto-common.c (gimple_register_canonical_type_1): Do not look for non-ODR conflicts of types in anonymous namespaces.

* lto-common.c (gimple_register_canonical_type_1): Do not look for
non-ODR conflicts of types in anonymous namespaces.
(unify_scc): Do not merge anonymous namespace types.
* g++.dg/lto/alias-5_0.C: New testcase.
* g++.dg/lto/alias-5_1.C: New.
* g++.dg/lto/alias-5_2.c: New.

From-SVN: r273571

5 years agore PR tree-optimization/91137 (Wrong code with -O3)
Bin Cheng [Thu, 18 Jul 2019 08:38:09 +0000 (08:38 +0000)]
re PR tree-optimization/91137 (Wrong code with -O3)

        PR tree-optimization/91137
        * tree-ssa-loop-ivopts.c (struct ivopts_data): New field.
        (tree_ssa_iv_optimize_init, alloc_iv, tree_ssa_iv_optimize_finalize):
        Init, use and fini the above new field.
        (determine_base_object_1): New function.
        (determine_base_object): Reimplement using walk_tree.

gcc/testsuite
        PR tree-optimization/91137
        * gcc.c-torture/execute/pr91137.c: New test.

From-SVN: r273570

5 years agoMake ifcvt clean up dead comparisons
Richard Sandiford [Thu, 18 Jul 2019 08:24:16 +0000 (08:24 +0000)]
Make ifcvt clean up dead comparisons

This change is needed to avoid a regression in gcc.dg/ifcvt-3.c
for a later patch.  Without it, we enter CSE with a dead comparison left
by if-conversion and then eliminate the second (live) comparison in
favour of the dead one.  That's functionally correct in itself, but it
meant that we'd combine the subtraction and comparison into a SUBS
before we have a chance to fold away the subtraction.

2019-07-18  Richard Sandiford  <richard.sandiford@arm.com>

gcc/
* basic-block.h (CLEANUP_FORCE_FAST_DCE): New macro.
* cfgcleanup.c (cleanup_cfg): Call run_fast_dce if
CLEANUP_FORCE_FAST_DCE is set.
* ifcvt.c (rest_of_handle_if_conversion): Pass
CLEANUP_FORCE_FAST_DCE to the final cleanup_cfg call if
if-conversion succeeded.

From-SVN: r273569

5 years agoFix -Wreturn-type for static naked functions in C
Richard Sandiford [Thu, 18 Jul 2019 08:22:50 +0000 (08:22 +0000)]
Fix -Wreturn-type for static naked functions in C

This patch extends the fix for PR53633 to include static functions,
which were giving a bogus -Wreturn-type warning for C but not for C++.

2019-07-18  Richard Sandiford  <richard.sandiford@arm.com>

gcc/c/
PR c/53633
* c-decl.c (finish_function): Check targetm.warn_func_return
before issuing a -Wreturn-type warning.

gcc/testsuite/
* c-c++-common/pr53633-2.c: New test.

From-SVN: r273568

5 years agotree-ssa-sccvn.c (vn_walk_cb_data::push_partial_def): Refactor branches to make code...
Richard Biener [Thu, 18 Jul 2019 08:09:16 +0000 (08:09 +0000)]
tree-ssa-sccvn.c (vn_walk_cb_data::push_partial_def): Refactor branches to make code less indented.

2019-07-18  Richard Biener  <rguenther@suse.de>

* tree-ssa-sccvn.c (vn_walk_cb_data::push_partial_def): Refactor
branches to make code less indented.

From-SVN: r273567

5 years agocompiler: fix bug in handling of unordered set during exporting
Ian Lance Taylor [Thu, 18 Jul 2019 05:05:20 +0000 (05:05 +0000)]
compiler: fix bug in handling of unordered set during exporting

    In CL 183850 a change was made to combine tracking/discovery of
    exported types and imported packages during export data generation. As
    a result of this refactoring a bug was introduced: the new code can
    potentially insert items into the exports set (an unordered_set) while
    iterating through the same set, which is illegal according to the spec
    for std::unordered_set.

    This patch fixes the problem by changing the type discovery phase to
    iterate through a separate list of sorted exports, as opposed to
    iterating through the main unordered set.  Also included is a change
    to fix the code that looks for variables that are referenced from
    inlined routine bodies (this code wasn't scanning all of the function
    that it needed to scan).

    New test case for this problem in CL 186697.

    Updates golang/go#33020.

    Reviewed-on: https://go-review.googlesource.com/c/gofrontend/+/185977

From-SVN: r273564

5 years ago-Wmissing-attributes: check that we avoid duplicates and false positives
Alexandre Oliva [Thu, 18 Jul 2019 00:38:45 +0000 (00:38 +0000)]
-Wmissing-attributes: check that we avoid duplicates and false positives

The initial patch for PR 81824 fixed various possibilities of
-Wmissing-attributes reporting duplicates and false positives.  The
test that avoided them was a little obscure, though, so this patch
rewrites it into a more self-evident form.

The patch also adds a testcase that already passed, but that
explicitly covers some of the possibilities of reporting duplicates
and false positives that preexisting tests did not cover.

for  gcc/ChangeLog

PR middle-end/81824
* attribs.c (decls_mismatched_attributes): Simplify the logic
that avoids duplicates and false positives.

for  gcc/testsuite/ChangeLog

PR middle-end/81824
* g++.dg/Wmissing-attributes-1.C: New.  Some of its fragments
are from Martin Sebor.

From-SVN: r273563

5 years agoDaily bump.
GCC Administrator [Thu, 18 Jul 2019 00:16:38 +0000 (00:16 +0000)]
Daily bump.

From-SVN: r273562

5 years agopa.c (pa_som_asm_init_sections): Don't force all constant data into data section...
John David Anglin [Thu, 18 Jul 2019 00:06:41 +0000 (00:06 +0000)]
pa.c (pa_som_asm_init_sections): Don't force all constant data into data section when generating PIC code.

* config/pa/pa.c (pa_som_asm_init_sections): Don't force all constant
data into data section when generating PIC code.
(pa_select_section): Use pa_reloc_rw_mask() to qualify relocs.
(pa_reloc_rw_mask): Return 3 when generating PIC code and when
generating code for SOM targets earlier than HP-UX 11.  Otherwise,
return 2 for SOM and 0 for other targets.

From-SVN: r273557

5 years agotree-ssa-dse.c (initialize_ao_ref_for_dse): Fix formatting.
Jeff Law [Wed, 17 Jul 2019 20:58:23 +0000 (14:58 -0600)]
tree-ssa-dse.c (initialize_ao_ref_for_dse): Fix formatting.

        * tree-ssa-dse.c (initialize_ao_ref_for_dse): Fix formatting.
        (dse_walker::dse_optimize_stmt): Likewise.  Add missing return to
        avoid unexpected switch statement fallthru.

From-SVN: r273556

5 years agoi386.md (*add<dwi>3_doubleword): Remove redundant constraints.
Uros Bizjak [Wed, 17 Jul 2019 18:32:36 +0000 (20:32 +0200)]
i386.md (*add<dwi>3_doubleword): Remove redundant constraints.

* config/i386/i386.md (*add<dwi>3_doubleword):
Remove redundant constraints.
(*add<mode>_1): Ditto.
(*addhi_1): Ditto.
(*addqi_1): Ditto.
(*addqi_1_slp): Ditto.
(*add<mode>_2): Ditto.
(*addv<mode>4): Ditto.
(*sub<dwi>3_doubleword): Ditto.
(*sub<mode>_1): Ditto.
(*subqi_1_slp): Ditto.
(*sub<mode>_2): Ditto.
(*subv<mode>4): Ditto.
(*sub<mode>_3): Ditto.
(@add<mode>3_carry): Ditto.
(@sub<mode>3_carry): Ditto.
(*add<mode>3_cc_overflow_1): Ditto.
(*add<mode>3_zext_cc_overflow_2): Ditto.
(*anddi_1): Ditto.
(*and<mode>_1): Ditto.
(*andqi_1): Ditto.
(*andqi_1_slp): Ditto.
(*anddi_2): Ditto.
(*andqi_2_maybe_si): Ditto.
(*and<mode>_2): Ditto.
(*andqi_2_slp): Ditto.
(*<code><mode>_1): Ditto.
(*<code>qi_1): Ditto.
(*<code>qi_1_slp): Ditto.
(*<code><mode>_2): Ditto.
(*<code>qi_2_slp): Ditto.

From-SVN: r273554

5 years agore PR c++/90455 (braced-init and incomplete type instantiation)
Marek Polacek [Wed, 17 Jul 2019 18:10:14 +0000 (18:10 +0000)]
re PR c++/90455 (braced-init and incomplete type instantiation)

PR c++/90455
* g++.dg/cpp0x/nsdmi-list6.C: New test.

From-SVN: r273553

5 years agoalias.c (record_component_aliases): Do not simplify pointed-to types of ODR types
Jan Hubicka [Wed, 17 Jul 2019 17:19:21 +0000 (19:19 +0200)]
alias.c (record_component_aliases): Do not simplify pointed-to types of ODR types

* alias.c (record_component_aliases): Do not simplify pointed-to
types of ODR types
* testsuite/g++.dg/lto/alias-4_0.C

From-SVN: r273552

5 years agoi386.md (*andqi_2_maybe_si): Handle potential partial reg stall on alternative 2.
Uros Bizjak [Wed, 17 Jul 2019 14:33:53 +0000 (16:33 +0200)]
i386.md (*andqi_2_maybe_si): Handle potential partial reg stall on alternative 2.

* config/i386/i386.md (*andqi_2_maybe_si): Handle potential
partial reg stall on alternative 2.

From-SVN: r273551

5 years agore PR tree-optimization/91178 (Infinite recursion in split_constant_offset in slp...
Richard Biener [Wed, 17 Jul 2019 11:21:49 +0000 (11:21 +0000)]
re PR tree-optimization/91178 (Infinite recursion in split_constant_offset in slp after r260289)

2019-07-17  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91178
* tree-ssa.c (release_defs_bitset): Iterate from higher to
lower SSA names to avoid quadratic behavior in the common case.
* tree-data-ref.c (split_constant_offset): Add limit argument
and pass it down.  Initialize it from PARAM_SSA_NAME_DEF_CHAIN_LIMIT.
(split_constant_offset_1): Add limit argument and use it to
limit SSA def walking.  Optimize the common plus/minus case.

From-SVN: r273550

5 years agore PR tree-optimization/91178 (Infinite recursion in split_constant_offset in slp...
Richard Biener [Wed, 17 Jul 2019 10:26:25 +0000 (10:26 +0000)]
re PR tree-optimization/91178 (Infinite recursion in split_constant_offset in slp after r260289)

2019-07-17  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91178
* tree-vect-stmts.c (get_group_load_store_type): For SLP
loads with a gap larger than the vector size always use
VMAT_STRIDED_SLP.
(vectorizable_load): For VMAT_STRIDED_SLP with a permutation
avoid loading vectors that are only contained in the gap
and thus are not needed.

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

From-SVN: r273549

5 years agore PR tree-optimization/91180 (wrong code at -O and above with __builtin_memset())
Richard Biener [Wed, 17 Jul 2019 09:35:04 +0000 (09:35 +0000)]
re PR tree-optimization/91180 (wrong code at -O and above with __builtin_memset())

2019-07-17  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91180
* tree-ssa-sccvn.c (vn_reference_lookup_3): Fix offset
computation for memset partial defs.

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

From-SVN: r273548

5 years ago* config/abi/post/ia64-linux-gnu/baseline_symbols.txt: Update.
Andreas Schwab [Wed, 17 Jul 2019 08:17:53 +0000 (08:17 +0000)]
* config/abi/post/ia64-linux-gnu/baseline_symbols.txt: Update.

From-SVN: r273547

5 years agore PR tree-optimization/91157 (ICE: verify_gimple failed (error: position plus size...
Jakub Jelinek [Wed, 17 Jul 2019 07:15:30 +0000 (09:15 +0200)]
re PR tree-optimization/91157 (ICE: verify_gimple failed (error: position plus size exceeds size of referenced object in 'bit_field_ref'))

PR tree-optimization/91157
* tree-vect-generic.c (expand_vector_comparison): Handle lhs being
a vector boolean with scalar mode.
(expand_vector_condition): Handle first operand being a vector boolean
with scalar mode.
(expand_vector_operations_1): For comparisons, don't bail out early
if the return type is vector boolean with scalar mode, but comparison
operand type is not.

* gcc.target/i386/avx512f-pr91157.c: New test.
* gcc.target/i386/avx512bw-pr91157.c: New test.

From-SVN: r273545

5 years agogimple.h (enum gf_mask): Remove GF_OMP_FOR_SIMD...
Jakub Jelinek [Wed, 17 Jul 2019 07:13:52 +0000 (09:13 +0200)]
gimple.h (enum gf_mask): Remove GF_OMP_FOR_SIMD...

* gimple.h (enum gf_mask): Remove GF_OMP_FOR_SIMD, change
GF_OMP_FOR_KIND_SIMD to a value serially after other kinds,
divide GF_OMP_FOR_KIND_MASK, GF_OMP_FOR_COMBINED,
GF_OMP_FOR_COMBINED_INTO, GF_OMP_FOR_GRID_PHONY,
GF_OMP_FOR_GRID_INTRA_GROUP and GF_OMP_FOR_GRID_GROUP_ITER by two.
* omp-grid.c (grid_process_grid_body,
grid_eliminate_combined_simd_part): Use GF_OMP_FOR_KIND_SIMD instead
of GF_OMP_FOR_SIMD, don't test & GF_OMP_FOR_SIMD but
== GF_OMP_FOR_KIND_SIMD.
* omp-low.c (build_outer_var_ref, scan_sharing_clauses,
check_omp_nesting_restrictions, scan_omp_1_stmt,
lower_rec_input_clauses, lower_lastprivate_conditional_clauses,
lower_lastprivate_clauses, lower_reduction_clauses, lower_omp_scan,
omp_find_scan): Likewise.
* omp-expand.c (expand_omp_for): Likewise.
* omp-general.c (omp_extract_for_data): Likewise.

From-SVN: r273544

5 years agore PR tree-optimization/91157 (ICE: verify_gimple failed (error: position plus size...
Jakub Jelinek [Wed, 17 Jul 2019 07:13:17 +0000 (09:13 +0200)]
re PR tree-optimization/91157 (ICE: verify_gimple failed (error: position plus size exceeds size of referenced object in 'bit_field_ref'))

PR tree-optimization/91157
* tree-vect-generic.c (expand_vector_comparison): Handle lhs being
a vector boolean with scalar mode.
(expand_vector_condition): Handle first operand being a vector boolean
with scalar mode.
(expand_vector_operations_1): For comparisons, don't bail out early
if the return type is vector boolean with scalar mode, but comparison
operand type is not.

* gcc.target/i386/avx512f-pr91157.c: New test.
* gcc.target/i386/avx512bw-pr91157.c: New test.

From-SVN: r273543

5 years agore PR tree-optimization/91181 (Failing as_as type conversion in vect_build_slp_tree_1)
Richard Biener [Wed, 17 Jul 2019 07:07:21 +0000 (07:07 +0000)]
re PR tree-optimization/91181 (Failing as_as type conversion in vect_build_slp_tree_1)

2019-07-17  Richard Biener  <rguenther@suse.de>

PR tree-optimization/91181
* tree-vect-slp.c (vect_build_slp_tree_1): Do not compare
IFN_LOADs as calls.

* gcc.dg/pr91181.c: New testcase.

From-SVN: r273542

5 years agoDaily bump.
GCC Administrator [Wed, 17 Jul 2019 00:16:21 +0000 (00:16 +0000)]
Daily bump.

From-SVN: r273541

5 years agore PR fortran/90903 (Implement runtime checks for bit manipulation intrinsics)
Harald Anlauf [Tue, 16 Jul 2019 19:58:15 +0000 (19:58 +0000)]
re PR fortran/90903 (Implement runtime checks for bit manipulation intrinsics)

2019-07-16  Harald Anlauf  <anlauf@gmx.de>

PR fortran/90903
* libgfortran.h: Add mask for -fcheck=bits option.
* options.c (gfc_handle_runtime_check_option): Add option "bits"
to run-time checks selectable via -fcheck.
* trans-intrinsic.c (gfc_conv_intrinsic_btest)
(gfc_conv_intrinsic_singlebitop, gfc_conv_intrinsic_ibits)
(gfc_conv_intrinsic_shift, gfc_conv_intrinsic_ishft)
(gfc_conv_intrinsic_ishftc): Implement run-time checks for the
POS, LEN, SHIFT, and SIZE arguments.
* gfortran.texi: Document run-time checks for bit manipulation
intrinsics.
* invoke.texi: Document new -fcheck=bits option.

PR fortran/90903
* gfortran.dg/check_bits_1.f90: New testcase.

From-SVN: r273535

5 years agoi386.md (*testdi_1): Match CCZmode for constants that might have the SImode sign...
Uros Bizjak [Tue, 16 Jul 2019 17:18:32 +0000 (19:18 +0200)]
i386.md (*testdi_1): Match CCZmode for constants that might have the SImode sign bit set.

* config/i386/i386.md (*testdi_1): Match CCZmode for
constants that might have the SImode sign bit set.
(*testqi_1_maybe_si): Remove "!" constraint modifier.
Use correct constraints for pentium pairing.
(*test<mode>_1): Ditto.

From-SVN: r273534

5 years agore PR rtl-optimization/91173 (ICE: in int_mode_for_mode, at stor-layout.c:403)
Jeff Law [Tue, 16 Jul 2019 14:57:51 +0000 (08:57 -0600)]
re PR rtl-optimization/91173 (ICE: in int_mode_for_mode, at stor-layout.c:403)

PR rtl-optimization/91173
* g++.dg/pr91173.C: New test.

From-SVN: r273531

5 years agore PR rtl-optimization/91173 (ICE: in int_mode_for_mode, at stor-layout.c:403)
Jeff Law [Tue, 16 Jul 2019 14:44:44 +0000 (08:44 -0600)]
re PR rtl-optimization/91173 (ICE: in int_mode_for_mode, at stor-layout.c:403)

PR rtl-optimization/91173
* tree-ssa-address.c (addr_for_mem_ref): If the base is an
SSA_NAME with a constant value, fold its value into the offset
and clear the base before calling gen_addr_rtx.

From-SVN: r273529