170560 Commits

Author SHA1 Message Date
Ed Schonberg
8c029ee8cf [Ada] Misleading warning on variable not assigned
This patch removes a warning on a referenced entity with no explicit
prior assignment, if the type of the entity has
Preelaborable_Initialixation, such as Exception_Occurrence.

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

gcc/ada/

	* sem_warn.adb (Check_References): Do not emit s warning on a
	referenced entity with no explicit assignment if the type of the
	entity has Preelaborable_Initialixation, such as
	Exception_Occurrence.

gcc/testsuite/

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

From-SVN: r273686
2019-07-22 13:57:51 +00:00
Javier Miranda
22862ba6d6 [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
2019-07-22 13:57:46 +00:00
Yannick Moy
5dcbefb1c4 [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
2019-07-22 13:57:42 +00:00
Eric Botcazou
1169925707 [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
2019-07-22 13:57:37 +00:00
Eric Botcazou
ff9d220ede [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
2019-07-22 13:57:31 +00:00
Eric Botcazou
78e92e11d4 [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
2019-07-22 13:57:26 +00:00
Ed Schonberg
a517030d8b [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
2019-07-22 13:57:22 +00:00
Eric Botcazou
2c26d262eb [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
2019-07-22 13:57:18 +00:00
Gary Dismukes
2418e23139 [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
2019-07-22 13:57:13 +00:00
Eric Botcazou
e7f4682af2 [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
2019-07-22 13:57:09 +00:00
Eric Botcazou
fd90c80862 [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
2019-07-22 13:57:04 +00:00
Nicolas Roche
7ddc639b77 [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
2019-07-22 13:56:59 +00:00
Eric Botcazou
52860cc145 [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
2019-07-22 13:56:55 +00:00
Eric Botcazou
f3d2fbfdb8 [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
2019-07-22 13:56:50 +00:00
Nicolas Roche
1a79e03b80 [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
2019-07-22 13:56:45 +00:00
Ed Schonberg
4123b47342 [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
2019-07-22 13:56:40 +00:00
Javier Miranda
2fdc20b65c [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
2019-07-22 13:56:36 +00:00
Ed Schonberg
0af66bdce0 [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
2019-07-22 13:56:31 +00:00
Eric Botcazou
c961d8205b [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
2019-07-22 13:56:26 +00:00
Richard Biener
8801ca5c28 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
2019-07-22 11:18:55 +00:00
Jan Beulich
ff8f129bc2 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
2019-07-22 08:07:29 +00:00
Martin Liska
a861990d21 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
2019-07-22 07:34:47 +00:00
Martin Liska
d1caf05a89 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
2019-07-22 07:34:32 +00:00
Martin Liska
2df89b66f1 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
2019-07-22 07:34:10 +00:00
Claudiu Zissulescu
4be6c9b9a2 [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
2019-07-22 09:06:37 +02:00
GCC Administrator
9e23d3bb28 Daily bump.
From-SVN: r273656
2019-07-22 00:16:23 +00:00
Marek Polacek
33c4306928 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
2019-07-21 21:20:27 +00:00
Stafford Horne
575ce89342 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
2019-07-21 21:02:54 +00:00
Stafford Horne
44080af98e 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
2019-07-21 21:01:59 +00:00
Stafford Horne
1e2e81c1a3 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
2019-07-21 21:00:47 +00:00
Stafford Horne
9c0dba7c45 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
2019-07-21 20:59:50 +00:00
Stafford Horne
2e92185a03 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
2019-07-21 20:58:54 +00:00
Iain Sandoe
48df93911a [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
2019-07-21 20:15:00 +00:00
Thomas Koenig
c37b0163fe 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
2019-07-21 15:55:49 +00:00
GCC Administrator
037455d49c Daily bump.
From-SVN: r273640
2019-07-21 00:16:16 +00:00
Segher Boessenkool
925763576e rs6000: Make offsettable_mem_operand use any_memory_operand
* config/rs6000/predicates.md (offsettable_mem_operand): Allow volatile
	memory.

From-SVN: r273633
2019-07-20 19:37:07 +02:00
Segher Boessenkool
4f5ddf2708 rs6000: Make input_operand use any_memory_operand
* config/rs6000/predicates.md (input_operand): Allow volatile memory.

From-SVN: r273632
2019-07-20 19:35:04 +02:00
Segher Boessenkool
45986ed939 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
2019-07-20 19:34:06 +02:00
Segher Boessenkool
5744faa985 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
2019-07-20 19:28:37 +02:00
Jakub Jelinek
4b3df26574 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
2019-07-20 19:13:00 +02:00
John David Anglin
7604f4351a 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
2019-07-20 16:47:25 +00:00
Jason Merrill
2dc1070584 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
2019-07-20 10:43:49 -04:00
Jason Merrill
1ab1f35020 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
2019-07-20 09:48:38 -04:00
Jakub Jelinek
554a530ff8 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
2019-07-20 13:21:42 +02:00
Jakub Jelinek
b6339213ff 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
2019-07-20 08:38:59 +02:00
GCC Administrator
05584e7c94 Daily bump.
From-SVN: r273615
2019-07-20 00:16:21 +00:00
Ian Lance Taylor
aa4d56e2ce 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
2019-07-19 23:10:55 +00:00
Bill Seurer
c35504626e 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
2019-07-19 22:14:56 +00:00
François Dumont
2be3193b82 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
2019-07-19 21:14:41 +00:00
Iain Sandoe
db67ea0f93 [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
2019-07-19 20:10:33 +00:00