diff --git a/gcc/ada/ali-util.adb b/gcc/ada/ali-util.adb index c0b8ad6062309b30604b66b8874799d646f0273a..2bd5bcac1849ad7f99ced16924b92dfefa9b4875 100644 --- a/gcc/ada/ali-util.adb +++ b/gcc/ada/ali-util.adb @@ -447,7 +447,7 @@ package body ALI.Util is Stringt.Release; end if; - if (not Read_Only) or else Source.Table (Src).Source_Found then + if not Read_Only or else Source.Table (Src).Source_Found then if not Source.Table (Src).Source_Found or else Sdep.Table (D).Stamp /= Source.Table (Src).Stamp then diff --git a/gcc/ada/bcheck.adb b/gcc/ada/bcheck.adb index f09de1bef3b6c6a531c415b5b822f5f34170da65..86ed92080bb84929b6c873dcc09a6e4053ecd8d4 100644 --- a/gcc/ada/bcheck.adb +++ b/gcc/ada/bcheck.adb @@ -223,7 +223,7 @@ package body Bcheck is end if; end if; - if (not Tolerate_Consistency_Errors) and Verbose_Mode then + if not Tolerate_Consistency_Errors and Verbose_Mode then Error_Msg_File_1 := Source.Table (Src).Stamp_File; if Source.Table (Src).Source_Found then @@ -1402,7 +1402,7 @@ package body Bcheck is Secondary := 0; end if; - if (Primary /= -1) and (Secondary /= -1) then + if Primary /= -1 and Secondary /= -1 then return (Primary => Primary, Secondary => Secondary); end if; @@ -1421,7 +1421,7 @@ package body Bcheck is V2 : constant ALI_Version := Extract_Version (V2_Text); Include_Version_Numbers_In_Message : constant Boolean := - (V1 /= V2) and (V1 /= No_Version) and (V2 /= No_Version); + V1 /= V2 and V1 /= No_Version and V2 /= No_Version; begin Error_Msg_File_1 := ALIs.Table (A).Sfile; Error_Msg_File_2 := ALIs.Table (ALIs.First).Sfile; diff --git a/gcc/ada/binde.adb b/gcc/ada/binde.adb index 101213cd83861b9f73ea837584ae4f062e83ed1f..fe262c0a27f2787472a82176e9672d6c1d9844e7 100644 --- a/gcc/ada/binde.adb +++ b/gcc/ada/binde.adb @@ -1937,7 +1937,7 @@ package body Binde is Units.Table (U).Last_With loop if Withs.Table (W).Sfile /= No_File - and then (not Withs.Table (W).SAL_Interface) + and then not Withs.Table (W).SAL_Interface then -- Check for special case of withing a unit that does not -- exist any more. If the unit was completely missing we @@ -2793,7 +2793,7 @@ package body Binde is Units.Table (U).Last_With loop if Withs.Table (W).Sfile /= No_File - and then (not Withs.Table (W).SAL_Interface) + and then not Withs.Table (W).SAL_Interface then -- Check for special case of withing a unit that does not -- exist any more. diff --git a/gcc/ada/binderr.adb b/gcc/ada/binderr.adb index 765482c4ee5e959b87a294f308b20bd0988f604f..5fb32c60a4f40ddd815844e645db995a04c7d189 100644 --- a/gcc/ada/binderr.adb +++ b/gcc/ada/binderr.adb @@ -50,7 +50,7 @@ package body Binderr is Errors_Detected := Errors_Detected + 1; end if; - if Brief_Output or else (not Verbose_Mode) then + if Brief_Output or else not Verbose_Mode then Set_Standard_Error; Error_Msg_Output (Msg, Info => False); Set_Standard_Output; @@ -90,7 +90,7 @@ package body Binderr is procedure Error_Msg_Info (Msg : String) is begin - if Brief_Output or else (not Verbose_Mode) then + if Brief_Output or else not Verbose_Mode then Set_Standard_Error; Error_Msg_Output (Msg, Info => True); Set_Standard_Output; diff --git a/gcc/ada/checks.adb b/gcc/ada/checks.adb index e21f3065cb15d8fafb062f6db9c998c11dcfa9bc..9f3c679ed7e190eda383e91c5bda5ec4d89aec97 100644 --- a/gcc/ada/checks.adb +++ b/gcc/ada/checks.adb @@ -1810,9 +1810,9 @@ package body Checks is Determine_Range (Left, LOK, Llo, Lhi, Assume_Valid => True); LLB := Expr_Value (Type_Low_Bound (Base_Type (Typ))); - if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi)) + if (not ROK or else (Rlo <= (-1) and then (-1) <= Rhi)) and then - ((not LOK) or else (Llo = LLB)) + (not LOK or else Llo = LLB) then -- Ensure that expressions are not evaluated twice (once -- for their runtime checks and once for their regular @@ -1872,7 +1872,7 @@ package body Checks is then Set_Do_Division_Check (N, False); - if (not ROK) or else (Rlo <= 0 and then 0 <= Rhi) then + if not ROK or else (Rlo <= 0 and then 0 <= Rhi) then if Is_Floating_Point_Type (Etype (N)) then Opnd := Make_Real_Literal (Loc, Ureal_0); else @@ -2727,7 +2727,7 @@ package body Checks is Par : Node_Id; S : Entity_Id; - Check_Disabled : constant Boolean := (not Predicate_Enabled (Typ)) + Check_Disabled : constant Boolean := not Predicate_Enabled (Typ) or else not Predicate_Check_In_Scope (N); begin S := Current_Scope; @@ -3501,7 +3501,7 @@ package body Checks is -- for the subscript, and that convert will do the necessary validity -- check. - if (No_Check_Needed = Empty_Dimension_Set) + if No_Check_Needed = Empty_Dimension_Set or else not No_Check_Needed.Elements (Dimension) then Ensure_Valid (Sub, Holes_OK => True); diff --git a/gcc/ada/clean.adb b/gcc/ada/clean.adb index fe0bda4dcfcce4234dcf0af0e39efe1123c44fb6..993e311d5f15ad2d5e2c213e0bc6bba7c8f3e77a 100644 --- a/gcc/ada/clean.adb +++ b/gcc/ada/clean.adb @@ -554,7 +554,7 @@ package body Clean is -- In verbose mode, if Delete has not been called, indicate that no file -- needs to be deleted. - if Verbose_Mode and (not File_Deleted) then + if Verbose_Mode and not File_Deleted then New_Line; if Do_Nothing then diff --git a/gcc/ada/einfo-utils.adb b/gcc/ada/einfo-utils.adb index febc80a38587db80f18715f347b76a3cdb03a9e5..5916188fa841658d961e4c527ff77f65ea040fb9 100644 --- a/gcc/ada/einfo-utils.adb +++ b/gcc/ada/einfo-utils.adb @@ -1975,7 +1975,7 @@ package body Einfo.Utils is end if; exit when Ekind (D) = E_Discriminant - and then (Is_Completely_Hidden (D) = Is_Completely_Hidden (Id)); + and then Is_Completely_Hidden (D) = Is_Completely_Hidden (Id); end loop; return D; diff --git a/gcc/ada/exp_ch11.adb b/gcc/ada/exp_ch11.adb index e2adefe83fe1be0f57f0b09ef185151bc7da2653..753412eab1650a24023c67e8b99f2e407e792f5e 100644 --- a/gcc/ada/exp_ch11.adb +++ b/gcc/ada/exp_ch11.adb @@ -1210,7 +1210,7 @@ package body Exp_Ch11 is declare Use_Test_And_Set_Flag : constant Boolean := - (not Global_No_Tasking) + not Global_No_Tasking and then RTE_Available (RE_Test_And_Set_Flag); Flag_Decl : Node_Id; diff --git a/gcc/ada/exp_ch2.adb b/gcc/ada/exp_ch2.adb index 06a276bbc03cae4b8353da3fc8e22bbadcf6cfd5..edcb91cf60b119797a738ef2dac1abf195e1f4b9 100644 --- a/gcc/ada/exp_ch2.adb +++ b/gcc/ada/exp_ch2.adb @@ -464,9 +464,9 @@ package body Exp_Ch2 is -- disable if either variable or its type have sync disabled. else - Set := (not Atomic_Synchronization_Disabled (E)) + Set := not Atomic_Synchronization_Disabled (E) and then - (not Atomic_Synchronization_Disabled (Etype (E))); + not Atomic_Synchronization_Disabled (Etype (E)); end if; -- Set flag if required diff --git a/gcc/ada/exp_ch3.adb b/gcc/ada/exp_ch3.adb index 33e96a0ff9045cf619b1de59a2d06629cf34aacd..b8ab549c0fc2d7804332112e4ae655007a517c76 100644 --- a/gcc/ada/exp_ch3.adb +++ b/gcc/ada/exp_ch3.adb @@ -2946,8 +2946,8 @@ package body Exp_Ch3 is while Present (Next (Ins_Nod)) and then (Nkind (Ins_Nod) /= N_If_Statement - or else (Nkind (First (Then_Statements (Ins_Nod))) - /= N_Procedure_Call_Statement) + or else Nkind (First (Then_Statements (Ins_Nod))) + /= N_Procedure_Call_Statement or else not Is_Init_Proc (Name (First (Then_Statements (Ins_Nod))))) @@ -7338,7 +7338,7 @@ package body Exp_Ch3 is and then (Restriction_Active (No_Implicit_Heap_Allocations) or else Restriction_Active (No_Implicit_Task_Allocations)) and then not (Ekind (Typ) in E_Array_Type | E_Array_Subtype - and then (Has_Init_Expression (N))) + and then Has_Init_Expression (N)) then declare PS_Count, SS_Count : Int := 0; @@ -11902,8 +11902,8 @@ package body Exp_Ch3 is -- Spec of Put_Image - if (not No_Run_Time_Mode) - and then RTE_Available (RE_Root_Buffer_Type) + if not No_Run_Time_Mode + and then RTE_Available (RE_Root_Buffer_Type) then -- No_Run_Time_Mode implies that the declaration of Tag_Typ -- (like any tagged type) will be rejected. Given this, avoid @@ -12417,7 +12417,7 @@ package body Exp_Ch3 is -- Body of Put_Image if No (TSS (Tag_Typ, TSS_Put_Image)) - and then (not No_Run_Time_Mode) + and then not No_Run_Time_Mode and then RTE_Available (RE_Root_Buffer_Type) then Build_Record_Put_Image_Procedure (Loc, Tag_Typ, Decl, Ent); diff --git a/gcc/ada/exp_ch4.adb b/gcc/ada/exp_ch4.adb index b63e47335be1634024f9be6d65f94e97ebcc9fe8..f197c2ef570e94949461f4bbff11478f94f8d3fe 100644 --- a/gcc/ada/exp_ch4.adb +++ b/gcc/ada/exp_ch4.adb @@ -3498,7 +3498,7 @@ package body Exp_Ch4 is -- Array case, slice assignment, skipped when argument is fixed -- length and known to be null. - elsif (not Is_Fixed_Length (J)) or else (Fixed_Length (J) > 0) then + elsif not Is_Fixed_Length (J) or else Fixed_Length (J) > 0 then declare Assign : Node_Id := Make_Assignment_Statement (Loc, @@ -8420,8 +8420,8 @@ package body Exp_Ch4 is return Nkind (Sindic) in N_Expanded_Name | N_Identifier and then Is_Unchecked_Union (Base_Type (Etype (Sindic))) - and then (Ekind (Entity (Sindic)) in - E_Private_Type | E_Record_Type); + and then Ekind (Entity (Sindic)) in + E_Private_Type | E_Record_Type; end Unconstrained_UU_In_Component_Declaration; ----------------------------------------- @@ -9125,7 +9125,7 @@ package body Exp_Ch4 is begin Determine_Range (Exp, OK, Lo, Hi, Assume_Valid => True); - if (not OK) or else Hi > MaxS then + if not OK or else Hi > MaxS then Insert_Action (N, Make_Raise_Constraint_Error (Loc, Condition => @@ -9790,8 +9790,8 @@ package body Exp_Ch4 is Expr_Value (Type_Low_Bound (Base_Type (Underlying_Type (Etype (Left))))); - if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi)) - and then ((not LOK) or else (Llo = LLB)) + if (not ROK or else (Rlo <= (-1) and then (-1) <= Rhi)) + and then (not LOK or else Llo = LLB) and then not CodePeer_Mode then Rewrite (N, @@ -10547,10 +10547,10 @@ package body Exp_Ch4 is -- completely in this case. Determine_Range (Right, OK, Lo, Hi, Assume_Valid => True); - Lneg := (not OK) or else Lo < 0; + Lneg := not OK or else Lo < 0; Determine_Range (Left, OK, Lo, Hi, Assume_Valid => True); - Rneg := (not OK) or else Lo < 0; + Rneg := not OK or else Lo < 0; -- We won't mess with trying to find out if the left operand can really -- be the largest negative number (that's a pain in the case of private @@ -11194,8 +11194,8 @@ package body Exp_Ch4 is -- actually performed. else - if (not Is_Unchecked_Union - (Implementation_Base_Type (Etype (Prefix (N))))) + if not Is_Unchecked_Union + (Implementation_Base_Type (Etype (Prefix (N)))) and then not Is_Predefined_Unit (Get_Source_Unit (N)) then Error_Msg_N @@ -11440,9 +11440,9 @@ package body Exp_Ch4 is -- component or its type have sync disabled. elsif Is_Atomic (E) and then Is_Atomic (Etype (E)) then - Set := (not Atomic_Synchronization_Disabled (E)) + Set := not Atomic_Synchronization_Disabled (E) and then - (not Atomic_Synchronization_Disabled (Etype (E))); + not Atomic_Synchronization_Disabled (Etype (E)); else Set := False; @@ -12457,7 +12457,7 @@ package body Exp_Ch4 is -- Special case of converting from non-standard boolean type if Is_Boolean_Type (Operand_Type) - and then (Nonzero_Is_True (Operand_Type)) + and then Nonzero_Is_True (Operand_Type) then Adjust_Condition (Operand); Set_Etype (Operand, Standard_Boolean); diff --git a/gcc/ada/exp_ch5.adb b/gcc/ada/exp_ch5.adb index dfe1112f3419e2469a68f7f2f3dc3315d05948b6..b4d931195d898db0fb775817e487490b716b1529 100644 --- a/gcc/ada/exp_ch5.adb +++ b/gcc/ada/exp_ch5.adb @@ -809,7 +809,7 @@ package body Exp_Ch5 is -- if there is a change of representation since obviously two arrays -- with different representations cannot possibly overlap. - if (not Crep) and L_Slice and R_Slice then + if not Crep and L_Slice and R_Slice then Act_L_Array := Get_Referenced_Object (Prefix (Act_Lhs)); Act_R_Array := Get_Referenced_Object (Prefix (Act_Rhs)); diff --git a/gcc/ada/exp_ch6.adb b/gcc/ada/exp_ch6.adb index b8e5a720a7cdc18fbeb37bf4b8e858de5ed47525..3f81b2a6c270a95aeb6e24903900aff289d907ab 100644 --- a/gcc/ada/exp_ch6.adb +++ b/gcc/ada/exp_ch6.adb @@ -2519,8 +2519,8 @@ package body Exp_Ch6 is or else (Ekind (Formal) = E_In_Out_Parameter and then - (Present (Storage_Model_Copy_From - (Storage_Model_Object (Etype (Prefix (Actual)))))))) + Present (Storage_Model_Copy_From + (Storage_Model_Object (Etype (Prefix (Actual))))))) then Add_Simple_Call_By_Copy_Code (Force => True); diff --git a/gcc/ada/exp_ch9.adb b/gcc/ada/exp_ch9.adb index 96e68805b00a4f8893a61cbfb47d55b920e92180..50b9d072d847ea7452e6aabb3cf2a4de5862c356 100644 --- a/gcc/ada/exp_ch9.adb +++ b/gcc/ada/exp_ch9.adb @@ -618,7 +618,7 @@ package body Exp_Ch9 is Prev := First_Entity (Ttyp); while Chars (Prev) /= Chars (Ent) - or else (Ekind (Prev) /= Ekind (Ent)) + or else Ekind (Prev) /= Ekind (Ent) or else not Sem_Ch6.Type_Conformant (Ent, Prev) loop if Ekind (Prev) = E_Entry then @@ -5468,7 +5468,7 @@ package body Exp_Ch9 is Prev := First_Entity (Ttyp); while Chars (Prev) /= Chars (Ent) - or else (Ekind (Prev) /= Ekind (Ent)) + or else Ekind (Prev) /= Ekind (Ent) or else not Sem_Ch6.Type_Conformant (Ent, Prev) loop if Ekind (Prev) = E_Entry then diff --git a/gcc/ada/exp_put_image.adb b/gcc/ada/exp_put_image.adb index 19e0415e4172eea24fec00933ed4aab41b046b4f..c194237aa20f4cac21ca8c9606937a5ca6e285cb 100644 --- a/gcc/ada/exp_put_image.adb +++ b/gcc/ada/exp_put_image.adb @@ -814,7 +814,7 @@ package body Exp_Put_Image is -- Start of processing for Build_Record_Put_Image_Procedure begin - if (Ada_Version < Ada_2022) + if Ada_Version < Ada_2022 or else not Enable_Put_Image (Btyp) then -- generate a very simple Put_Image implementation diff --git a/gcc/ada/fmap.adb b/gcc/ada/fmap.adb index 798db6e2a7f066c4eac16338c01ed17553b6210b..6cc5ca22438baf9990ff985a39f56c88cd29b573 100644 --- a/gcc/ada/fmap.adb +++ b/gcc/ada/fmap.adb @@ -319,7 +319,7 @@ package body Fmap is exit when First > Last; - if (Last < First + 2) or else (Src (Last - 1) /= '%') + if Last < First + 2 or else Src (Last - 1) /= '%' or else (Src (Last) /= 's' and then Src (Last) /= 'b') then Write_Line diff --git a/gcc/ada/freeze.adb b/gcc/ada/freeze.adb index df3b5ec944e9d01999bfb0fd62a683a597844e92..990bace4fbaccfad0591c9c9cf81e919ef7ded26 100644 --- a/gcc/ada/freeze.adb +++ b/gcc/ada/freeze.adb @@ -1904,8 +1904,8 @@ package body Freeze is if Iface_Prim /= Par_Prim and then Chars (Iface_Prim) = Chars (Prim) and then Comes_From_Source (Iface_Prim) - and then (Is_Interface_Conformant - (R, Iface_Prim, Prim)) + and then Is_Interface_Conformant + (R, Iface_Prim, Prim) then Check_Same_Strub_Mode (Prim, Iface_Prim); end if; @@ -8285,7 +8285,7 @@ package body Freeze is if Desig_Typ /= Empty and then (Is_Frozen (Desig_Typ) - or else (not Is_Fully_Defined (Desig_Typ))) + or else not Is_Fully_Defined (Desig_Typ)) then Desig_Typ := Empty; end if; @@ -8428,7 +8428,7 @@ package body Freeze is if not In_Spec_Expression and then Nkind (N) = N_Identifier - and then (Present (Entity (N))) + and then Present (Entity (N)) then -- We recognize the discriminant case by just looking for -- a reference to a discriminant. It can only be one for diff --git a/gcc/ada/gnatls.adb b/gcc/ada/gnatls.adb index a29205c0ed32a3d776fbf937cde666397c2c500d..a9e88af1bf03d76df5e63698244c9e19e985060f 100644 --- a/gcc/ada/gnatls.adb +++ b/gcc/ada/gnatls.adb @@ -1414,7 +1414,7 @@ procedure Gnatls is First := 3; loop while First <= Name_Len - and then (Name_Buffer (First) = Path_Separator) + and then Name_Buffer (First) = Path_Separator loop First := First + 1; end loop; @@ -2170,7 +2170,7 @@ begin First := Prj_Path'First; loop while First <= Prj_Path'Last - and then (Prj_Path (First) = Path_Separator) + and then Prj_Path (First) = Path_Separator loop First := First + 1; end loop; diff --git a/gcc/ada/gprep.adb b/gcc/ada/gprep.adb index 7c6c09f6a00df4ce5b56c31dfd470a53e9f6b93d..5b589558458aecd6e3433d313d0ad84523e9067f 100644 --- a/gcc/ada/gprep.adb +++ b/gcc/ada/gprep.adb @@ -228,7 +228,7 @@ package body GPrep is -- the deleted lines are not put as comment, we must output them as -- blank lines. - if Source_Ref_Pragma and (not Opt.Comment_Deleted_Lines) then + if Source_Ref_Pragma and not Opt.Comment_Deleted_Lines then Opt.Blank_Deleted_Lines := True; end if; diff --git a/gcc/ada/libgnat/a-costso.adb b/gcc/ada/libgnat/a-costso.adb index fcdd7aa3f987bab3cacff172f64c02533ab5b0a9..fb4da326e4e87ecf4867fdb0f9977aa751311286 100644 --- a/gcc/ada/libgnat/a-costso.adb +++ b/gcc/ada/libgnat/a-costso.adb @@ -124,7 +124,7 @@ package body Ada.Containers.Stable_Sorting is -- Start of processing for Merge_Parts begin - while (P1.Length /= 0) or (P2.Length /= 0) loop + while P1.Length /= 0 or P2.Length /= 0 loop if P1.Length = 0 then Take_From_P2 := True; elsif P2.Length = 0 then diff --git a/gcc/ada/libgnat/a-dhfina.adb b/gcc/ada/libgnat/a-dhfina.adb index a7e9e386ba7d69be5adb29efc3e3534c225ce56a..9435cc02ad02144443f7701d2ed11b515ff0ea66 100644 --- a/gcc/ada/libgnat/a-dhfina.adb +++ b/gcc/ada/libgnat/a-dhfina.adb @@ -307,7 +307,7 @@ package body Ada.Directories.Hierarchical_File_Names is -- Check that directory is valid if Separated_Dir /= "" - and then (not Is_Valid_Path_Name (Separated_Dir & Relative_Name)) + and then not Is_Valid_Path_Name (Separated_Dir & Relative_Name) then raise Name_Error with "invalid path composition """ & Separated_Dir & Relative_Name & '"'; diff --git a/gcc/ada/libgnat/a-direct.adb b/gcc/ada/libgnat/a-direct.adb index d660b69dcb805d8137421a48e17f4d5ffdb96ebd..4b08d41337dda385c8512522962c81251626ad07 100644 --- a/gcc/ada/libgnat/a-direct.adb +++ b/gcc/ada/libgnat/a-direct.adb @@ -176,9 +176,7 @@ package body Ada.Directories is raise Name_Error with "invalid directory path name """ & Containing_Directory & '"'; - elsif - Extension'Length = 0 and then (not Is_Valid_Simple_Name (Name)) - then + elsif Extension'Length = 0 and then not Is_Valid_Simple_Name (Name) then raise Name_Error with "invalid simple name """ & Name & '"'; diff --git a/gcc/ada/libgnat/a-nbnbig.ads b/gcc/ada/libgnat/a-nbnbig.ads index 3979f147d2a18969027c575e3ba91aaca5381de2..f83bf5276b36bd53d74db65fd3a7d11f2b2fbdc6 100644 --- a/gcc/ada/libgnat/a-nbnbig.ads +++ b/gcc/ada/libgnat/a-nbnbig.ads @@ -75,13 +75,13 @@ is with Dynamic_Predicate => (if Is_Valid (Big_Positive) then Big_Positive > To_Big_Integer (0)), - Predicate_Failure => (raise Constraint_Error); + Predicate_Failure => raise Constraint_Error; subtype Big_Natural is Big_Integer with Dynamic_Predicate => (if Is_Valid (Big_Natural) then Big_Natural >= To_Big_Integer (0)), - Predicate_Failure => (raise Constraint_Error); + Predicate_Failure => raise Constraint_Error; function In_Range (Arg : Valid_Big_Integer; Low, High : Big_Integer) return Boolean @@ -96,7 +96,7 @@ is Pre => In_Range (Arg, Low => To_Big_Integer (Integer'First), High => To_Big_Integer (Integer'Last)) - or else (raise Constraint_Error), + or else raise Constraint_Error, Global => null; generic @@ -112,7 +112,7 @@ is Pre => In_Range (Arg, Low => To_Big_Integer (Int'First), High => To_Big_Integer (Int'Last)) - or else (raise Constraint_Error), + or else raise Constraint_Error, Global => null; end Signed_Conversions; @@ -129,7 +129,7 @@ is Pre => In_Range (Arg, Low => To_Big_Integer (Int'First), High => To_Big_Integer (Int'Last)) - or else (raise Constraint_Error), + or else raise Constraint_Error, Global => null; end Unsigned_Conversions; @@ -207,7 +207,7 @@ is with Import, Pre => (L /= To_Big_Integer (0) and R /= To_Big_Integer (0)) - or else (raise Constraint_Error), + or else raise Constraint_Error, Global => null; private diff --git a/gcc/ada/libgnat/a-rbtgbo.adb b/gcc/ada/libgnat/a-rbtgbo.adb index 773e71ae6e71e0456da0340cdf5017d1955e2926..2f965796afa2572427518a3ae27c4ce0a55682d0 100644 --- a/gcc/ada/libgnat/a-rbtgbo.adb +++ b/gcc/ada/libgnat/a-rbtgbo.adb @@ -207,21 +207,21 @@ package body Ada.Containers.Red_Black_Trees.Generic_Bounded_Operations is pragma Assert (Tree.Last /= 0); pragma Assert (Parent (N (Tree.Root)) = 0); - pragma Assert ((Tree.Length > 1) + pragma Assert (Tree.Length > 1 or else (Tree.First = Tree.Last and then Tree.First = Tree.Root)); - pragma Assert ((Left (N (Node)) = 0) - or else (Parent (N (Left (N (Node)))) = Node)); + pragma Assert (Left (N (Node)) = 0 + or else Parent (N (Left (N (Node)))) = Node); - pragma Assert ((Right (N (Node)) = 0) - or else (Parent (N (Right (N (Node)))) = Node)); + pragma Assert (Right (N (Node)) = 0 + or else Parent (N (Right (N (Node)))) = Node); - pragma Assert (((Parent (N (Node)) = 0) and then (Tree.Root = Node)) - or else ((Parent (N (Node)) /= 0) and then - ((Left (N (Parent (N (Node)))) = Node) + pragma Assert ((Parent (N (Node)) = 0 and then Tree.Root = Node) + or else (Parent (N (Node)) /= 0 and then + (Left (N (Parent (N (Node)))) = Node or else - (Right (N (Parent (N (Node)))) = Node)))); + Right (N (Parent (N (Node)))) = Node))); if Left (N (Z)) = 0 then if Right (N (Z)) = 0 then diff --git a/gcc/ada/libgnat/a-strmap.adb b/gcc/ada/libgnat/a-strmap.adb index 53af28b950c061264d81227cb80ae1231dee8f1f..529ecbb410d5a54535f525f61bafb11a476f0f56 100644 --- a/gcc/ada/libgnat/a-strmap.adb +++ b/gcc/ada/libgnat/a-strmap.adb @@ -545,7 +545,7 @@ is Result (Char) = ((for some Prev in Ranges'First .. R - 1 => Char in Ranges (Prev).Low .. Ranges (Prev).High) - or else (Char in Ranges (R).Low .. C))); + or else Char in Ranges (R).Low .. C)); end loop; pragma Loop_Invariant diff --git a/gcc/ada/libgnat/a-strsea.adb b/gcc/ada/libgnat/a-strsea.adb index 7c1e2fac1af57fe5394e31e74459ae42703a3a6b..614b5ac3965438b62495a1322ca19e34a7675a3b 100644 --- a/gcc/ada/libgnat/a-strsea.adb +++ b/gcc/ada/libgnat/a-strsea.adb @@ -545,7 +545,7 @@ package body Ada.Strings.Search with SPARK_Mode is <<Cont2>> pragma Loop_Invariant - (for all J in Ind .. (Source'Last - PL1) => + (for all J in Ind .. Source'Last - PL1 => not (Match (Source, Pattern, Mapping, J))); null; end loop; diff --git a/gcc/ada/libgnat/a-ststio.adb b/gcc/ada/libgnat/a-ststio.adb index fd1017f433023748a1e9e130b2dc8c8e625334a1..2cb9d974bbdd766dff1fdfd3ce6755f0520a8c39 100644 --- a/gcc/ada/libgnat/a-ststio.adb +++ b/gcc/ada/libgnat/a-ststio.adb @@ -354,7 +354,7 @@ package body Ada.Streams.Stream_IO is -- mode now. Note that we can use Inout_File as the mode for the -- call since File_IO handles all modes for all file types. - if ((File.Mode = FCB.In_File) /= (Mode = In_File)) + if (File.Mode = FCB.In_File) /= (Mode = In_File) and then not File.Update_Mode then FIO.Reset (AP (File)'Unrestricted_Access, FCB.Inout_File); diff --git a/gcc/ada/libgnat/a-suenco.adb b/gcc/ada/libgnat/a-suenco.adb index b3748f774389e9cceffc7d3b5feb934e3264f7ce..39a44bf64cce36218d16d284336f1814f365efcf 100644 --- a/gcc/ada/libgnat/a-suenco.adb +++ b/gcc/ada/libgnat/a-suenco.adb @@ -391,7 +391,7 @@ package body Ada.Strings.UTF_Encoding.Conversions is Result (Len + 1) := Character'Val - (2#11110_000# or (Shift_Right (zzzzz, 2))); + (2#11110_000# or Shift_Right (zzzzz, 2)); Result (Len + 2) := Character'Val (2#10_000000# or Shift_Left (zzzzz and 2#11#, 4) diff --git a/gcc/ada/libgnat/g-alleve.adb b/gcc/ada/libgnat/g-alleve.adb index b51181ae886c62a25cbb0aa46b928b76523b944a..91e3ddd5909fc6812fb57a50607a9db246899c92 100644 --- a/gcc/ada/libgnat/g-alleve.adb +++ b/gcc/ada/libgnat/g-alleve.adb @@ -643,8 +643,8 @@ package body GNAT.Altivec.Low_Level_Vectors is begin for J in Varray_Type'Range loop - All_Element := All_Element and then (D (J) = Bool_True); - Any_Element := Any_Element or else (D (J) = Bool_True); + All_Element := All_Element and then D (J) = Bool_True; + Any_Element := Any_Element or else D (J) = Bool_True; end loop; if A = CR6_LT then @@ -1089,8 +1089,8 @@ package body GNAT.Altivec.Low_Level_Vectors is begin for J in Varray_Type'Range loop - All_Element := All_Element and then (D (J) = Bool_True); - Any_Element := Any_Element or else (D (J) = Bool_True); + All_Element := All_Element and then D (J) = Bool_True; + Any_Element := Any_Element or else D (J) = Bool_True; end loop; if A = CR6_LT then @@ -1582,7 +1582,7 @@ package body GNAT.Altivec.Low_Level_Vectors is D : C_float; begin - if (Bits (VSCR, NJ_POS, NJ_POS) = 1) + if Bits (VSCR, NJ_POS, NJ_POS) = 1 and then abs (X) < 2.0 ** (-126) then D := (if X < 0.0 then -0.0 else +0.0); diff --git a/gcc/ada/libgnat/g-debpoo.adb b/gcc/ada/libgnat/g-debpoo.adb index 91c14167bc5c3d413d8fab229cb5a85e78da1a65..521570f9ff64876200ffe87259abb697b187f8cb 100644 --- a/gcc/ada/libgnat/g-debpoo.adb +++ b/gcc/ada/libgnat/g-debpoo.adb @@ -906,7 +906,7 @@ package body GNAT.Debug_Pools is Set_Handled; else Ptr.Valid (Offset / System.Storage_Unit) := - Ptr.Valid (Offset / System.Storage_Unit) and (not Bit); + Ptr.Valid (Offset / System.Storage_Unit) and not Bit; end if; end if; end Set_Valid; diff --git a/gcc/ada/libgnat/g-dynhta.adb b/gcc/ada/libgnat/g-dynhta.adb index 0119b568c6993799a90d714a7dafde0afa3f690d..7a62ac8ac4beac64bd3f7f133160b10b018a1009 100644 --- a/gcc/ada/libgnat/g-dynhta.adb +++ b/gcc/ada/libgnat/g-dynhta.adb @@ -56,9 +56,9 @@ package body GNAT.Dynamic_HTables is -- range of Bucket_Range_Type. return - ((Left and Mask) * Half) + (Left and Mask) * Half or - (Right and Mask); + (Right and Mask); end Hash_Two_Keys; ------------------- diff --git a/gcc/ada/libgnat/g-sercom__linux.adb b/gcc/ada/libgnat/g-sercom__linux.adb index 216092e51a5c22a5a13c8588d3d4faa9a3218993..401ab85cd89d827cfd29bd89a625179d311acf38 100644 --- a/gcc/ada/libgnat/g-sercom__linux.adb +++ b/gcc/ada/libgnat/g-sercom__linux.adb @@ -304,7 +304,7 @@ package body GNAT.Serial_Communications is Current.c_cc (VMIN) := char'Val (0); Current.c_cc (VTIME) := char'Val (Natural (Timeout * 10)); - Current.c_lflag := Current.c_lflag or (not ICANON); + Current.c_lflag := Current.c_lflag or not ICANON; end if; Res := cfsetispeed (Current'Address, C_Data_Rate (Rate)); diff --git a/gcc/ada/libgnat/s-carun8.adb b/gcc/ada/libgnat/s-carun8.adb index 3a88a9c6139b8f7f44f3c81bcfb2b0d02714c1ce..b0f2d94bf8acb16076e0a80decc04ded38840bd1 100644 --- a/gcc/ada/libgnat/s-carun8.adb +++ b/gcc/ada/libgnat/s-carun8.adb @@ -72,7 +72,7 @@ package body System.Compare_Array_Unsigned_8 is begin -- If operands are non-aligned, or length is too short, go by bytes - if (ModA (OrA (Left, Right), 4) /= 0) or else Compare_Len < 4 then + if ModA (OrA (Left, Right), 4) /= 0 or else Compare_Len < 4 then return Compare_Array_U8_Unaligned (Left, Right, Left_Len, Right_Len); end if; diff --git a/gcc/ada/libgnat/s-genbig.adb b/gcc/ada/libgnat/s-genbig.adb index 183ce3262f020ca31e915761502a13418c479a29..e1f2e5c155f2ef65b71b05f9608d2a7cd78b1908 100644 --- a/gcc/ada/libgnat/s-genbig.adb +++ b/gcc/ada/libgnat/s-genbig.adb @@ -322,7 +322,7 @@ package body System.Generic_Bignums is elsif X.Len = 1 and then X.D (1) = 1 then return Normalize - (X.D, Neg => X.Neg and then ((Y.D (Y.Len) and 1) = 1)); + (X.D, Neg => X.Neg and then (Y.D (Y.Len) and 1) = 1); -- If the absolute value of the base is greater than 1, then the -- exponent must not be bigger than one word, otherwise the result @@ -698,14 +698,14 @@ package body System.Generic_Bignums is -- Lengths are different, that's decisive since no leading zeroes elsif X'Last /= Y'Last then - return (if (X'Last > Y'Last) xor X_Neg then GT else LT); + return (if X'Last > Y'Last xor X_Neg then GT else LT); -- Need to compare data else for J in X'Range loop if X (J) /= Y (J) then - return (if (X (J) > Y (J)) xor X_Neg then GT else LT); + return (if X (J) > Y (J) xor X_Neg then GT else LT); end if; end loop; diff --git a/gcc/ada/libgnat/s-mmap.adb b/gcc/ada/libgnat/s-mmap.adb index ed4c2bd2e3904d4f511e48349b2a1841d5281669..60f0db30fb57aa27240e2c25e55b6720abf83fdb 100644 --- a/gcc/ada/libgnat/s-mmap.adb +++ b/gcc/ada/libgnat/s-mmap.adb @@ -284,9 +284,8 @@ package body System.Mmap is if (File.File.Write or else Region.Mutable = Mutable) and then Req_Offset >= Region.System_Offset - and then - (Req_Offset + Req_Length - <= Region.System_Offset + Region.System_Size) + and then Req_Offset + Req_Length <= + Region.System_Offset + Region.System_Size then Region.User_Offset := Req_Offset; Compute_Data (Region); diff --git a/gcc/ada/libgnat/s-regpat.adb b/gcc/ada/libgnat/s-regpat.adb index 256390fd334fecc98f787425d23b3f3f820d849c..3d2a76c0066ea6180f45bceba80138b9b40f13a6 100644 --- a/gcc/ada/libgnat/s-regpat.adb +++ b/gcc/ada/libgnat/s-regpat.adb @@ -895,7 +895,7 @@ package body System.Regpat is Flags.SP_Start := Flags.SP_Start or else New_Flags.SP_Start; while Parse_Pos <= Parse_End - and then (E (Parse_Pos) = '|') + and then E (Parse_Pos) = '|' loop Parse_Pos := Parse_Pos + 1; Parse_Branch (New_Flags, False, Br); diff --git a/gcc/ada/libgnat/s-strcom.adb b/gcc/ada/libgnat/s-strcom.adb index 59e56980db5e48445d0d4b982df482081411f9e0..a2354f3252677a5e6a3207477726c891a84b4eef 100644 --- a/gcc/ada/libgnat/s-strcom.adb +++ b/gcc/ada/libgnat/s-strcom.adb @@ -70,7 +70,7 @@ package body System.String_Compare is begin -- If operands are non-aligned, or length is too short, go by bytes - if (((Left or Right) and 2#11#) /= 0) or else Compare_Len < 4 then + if ((Left or Right) and 2#11#) /= 0 or else Compare_Len < 4 then return Str_Compare_Bytes (Left, Right, Left_Len, Right_Len); end if; diff --git a/gcc/ada/live.adb b/gcc/ada/live.adb index 9b38d51f86eeca6529a9bad35670e9889107fba5..f7057db7572c26f011759ead5eabe14ef8f5b064 100644 --- a/gcc/ada/live.adb +++ b/gcc/ada/live.adb @@ -344,7 +344,7 @@ package body Live is end if; when N_Entity'Range => - if (Ekind (N) = E_Component) and then not Marked (Marks, N) then + if Ekind (N) = E_Component and then not Marked (Marks, N) then if Present (Discriminant_Checking_Func (N)) then Process (Discriminant_Checking_Func (N)); end if; diff --git a/gcc/ada/par-ch2.adb b/gcc/ada/par-ch2.adb index b85e397b07d40d148a73ccdeeb29e1fe71da013f..b6814bdec17edf7789fb067133c0d1002680c8ee 100644 --- a/gcc/ada/par-ch2.adb +++ b/gcc/ada/par-ch2.adb @@ -371,7 +371,7 @@ package body Ch2 is if SIS_Entry_Active then Import_Check_Required := - (Prag_Name = Name_Import) or else (Prag_Name = Name_Interface); + Prag_Name = Name_Import or else Prag_Name = Name_Interface; else Import_Check_Required := False; end if; diff --git a/gcc/ada/par-ch5.adb b/gcc/ada/par-ch5.adb index be821f775ba76a47e7a14c2c075f6e3d1e918b85..8f7224517bc3044f3201fdb7493d703c7a2f4ea5 100644 --- a/gcc/ada/par-ch5.adb +++ b/gcc/ada/par-ch5.adb @@ -2244,7 +2244,7 @@ package body Ch5 is -- END, EOF, or a token which starts declarations. elsif Parent_Nkind = N_Package_Body - and then (Token in Tok_End | Tok_EOF | Token_Class_Declk) + and then Token in Tok_End | Tok_EOF | Token_Class_Declk then Set_Null_HSS (Parent); diff --git a/gcc/ada/par-endh.adb b/gcc/ada/par-endh.adb index 56275bf1cab6515b28b56f10361790b7baf2de21..45cf22a4f247a82c6eef5904cd9dbbad5753db35 100644 --- a/gcc/ada/par-endh.adb +++ b/gcc/ada/par-endh.adb @@ -820,9 +820,9 @@ package body Endh is -- Cases where a label is definitely allowed on the END line elsif End_Type = E_Name then - Syntax_OK := (not Explicit_Start_Label (SS_Index)) + Syntax_OK := not Explicit_Start_Label (SS_Index) or else - (not Scopes (SS_Index).Lreq); + not Scopes (SS_Index).Lreq; -- Otherwise we have cases which don't allow labels anyway, so we -- certainly accept an END which does not have a label. @@ -1164,11 +1164,11 @@ package body Endh is and then (Scope.Last = 1 or else - (not Explicit_Start_Label (Scope.Last - 1)) + not Explicit_Start_Label (Scope.Last - 1) or else - (not Same_Label - (End_Labl, - Scopes (Scope.Last - 1).Labl))) + not Same_Label + (End_Labl, + Scopes (Scope.Last - 1).Labl)) then T_Semicolon; Error_Msg ("duplicate end line ignored", End_Loc); diff --git a/gcc/ada/par-prag.adb b/gcc/ada/par-prag.adb index e78f97d11fbd0bad4dbf56e9d38fa3839ec36cc2..4a3517d2297adde9555fed823a78b88ff0d779c1 100644 --- a/gcc/ada/par-prag.adb +++ b/gcc/ada/par-prag.adb @@ -120,7 +120,7 @@ function Prag (Pragma_Node : Node_Id; Semi : Source_Ptr) return Node_Id is procedure Add_List_Pragma_Entry (PT : List_Pragma_Type; Loc : Source_Ptr) is begin if List_Pragmas.Last < List_Pragmas.First - or else (List_Pragmas.Table (List_Pragmas.Last)) /= ((PT, Loc)) + or else List_Pragmas.Table (List_Pragmas.Last) /= (PT, Loc) then List_Pragmas.Append ((PT, Loc)); end if; @@ -176,7 +176,7 @@ function Prag (Pragma_Node : Node_Id; Semi : Source_Ptr) return Node_Id is Error : Boolean := Nkind (Expression (Arg)) /= N_Identifier; begin if not Error then - Error := (Chars (Argx) not in Name_On | Name_Off) + Error := Chars (Argx) not in Name_On | Name_Off and then not (All_OK_Too and Chars (Argx) = Name_All); end if; if Error then diff --git a/gcc/ada/sem_aggr.adb b/gcc/ada/sem_aggr.adb index 6405fe4c2d4f486010feb532e17d0c844b9b6aaf..c037201885ebb035d6b760a3857514261c6108ad 100644 --- a/gcc/ada/sem_aggr.adb +++ b/gcc/ada/sem_aggr.adb @@ -2302,8 +2302,8 @@ package body Sem_Aggr is -- this discrete choice specifies a single value. Single_Choice := - (Nb_Discrete_Choices = Prev_Nb_Discrete_Choices + 1) - and then (Low = High); + Nb_Discrete_Choices = Prev_Nb_Discrete_Choices + 1 + and then Low = High; exit; end if; diff --git a/gcc/ada/sem_case.adb b/gcc/ada/sem_case.adb index f649122d2f90bd79772b4cbec1bfb70e83d0c8c2..0a47bf91cae5c4b9dec745254403f143dafdb389 100644 --- a/gcc/ada/sem_case.adb +++ b/gcc/ada/sem_case.adb @@ -2752,7 +2752,7 @@ package body Sem_Case is procedure Test_Point_For_Match is function In_Range (Val : Uint; Rang : Discrete_Range_Info) return Boolean is - ((Rang.Low <= Val) and then (Val <= Rang.High)); + (Rang.Low <= Val and then Val <= Rang.High); begin pragma Assert (not Done); Matches (Next_Index) := @@ -3429,8 +3429,8 @@ package body Sem_Case is Others_Seen := True; else if Flag_Overlapping_Within_One_Alternative - and then (Compare (Matches (Choice.Alternative), - Choice.Matches) /= Disjoint) + and then Compare (Matches (Choice.Alternative), + Choice.Matches) /= Disjoint then Error_Msg_N ("bad overlapping within one alternative", N); @@ -3479,7 +3479,7 @@ package body Sem_Case is Union (Target => Covered, Source => Matches (A1)); end loop; - if (not Others_Seen) and then not Complement_Is_Empty (Covered) + if not Others_Seen and then not Complement_Is_Empty (Covered) then Error_Msg_N ("not all values are covered", N); end if; @@ -3823,7 +3823,7 @@ package body Sem_Case is (Choice_Table, Bounds_Type, Subtyp, - Others_Present or else (Choice_Type = Universal_Integer), + Others_Present or else Choice_Type = Universal_Integer, N); -- If no others choice we are all done, otherwise we have one more diff --git a/gcc/ada/sem_cat.adb b/gcc/ada/sem_cat.adb index 5398153a35de5bd4da8ebaf66b443f766c57678d..09560e6179ace7b6efa111ca99f5d29d30cee762 100644 --- a/gcc/ada/sem_cat.adb +++ b/gcc/ada/sem_cat.adb @@ -562,7 +562,7 @@ package body Sem_Cat is -- There are no constraints on the body of Remote_Call_Interface or -- Remote_Types packages. - return (Unit_Entity /= Standard_Standard) + return Unit_Entity /= Standard_Standard and then (Is_Preelaborated (Unit_Entity) or else Is_Pure (Unit_Entity) or else Is_Shared_Passive (Unit_Entity) diff --git a/gcc/ada/sem_ch10.adb b/gcc/ada/sem_ch10.adb index f7f02a2c2ee4db3bd3910b36f464c3ff843308d8..13357924e64354de74b498bb1ef565116d8f2a37 100644 --- a/gcc/ada/sem_ch10.adb +++ b/gcc/ada/sem_ch10.adb @@ -2051,8 +2051,8 @@ package body Sem_Ch10 is Decl := First (Declarations (Parent (N))); while Present (Decl) and then Decl /= N loop if Nkind (Decl) = N_Subprogram_Body_Stub - and then (Chars (Defining_Unit_Name (Specification (Decl))) = - Chars (Defining_Unit_Name (Specification (N)))) + and then Chars (Defining_Unit_Name (Specification (Decl))) = + Chars (Defining_Unit_Name (Specification (N))) then Error_Msg_N ("identifier for stub is not unique", N); end if; @@ -4700,9 +4700,9 @@ package body Sem_Ch10 is -- Save for subsequent examination of import pragmas. if Comes_From_Source (Decl) - and then (Nkind (Decl) in N_Subprogram_Declaration - | N_Subprogram_Renaming_Declaration - | N_Generic_Subprogram_Declaration) + and then Nkind (Decl) in N_Subprogram_Declaration + | N_Subprogram_Renaming_Declaration + | N_Generic_Subprogram_Declaration then Append_Elmt (Defining_Entity (Decl), Subp_List); diff --git a/gcc/ada/sem_ch11.adb b/gcc/ada/sem_ch11.adb index 401e2be17da25a62d4bef9b650480f03b54f2f4f..70fd334613c4cb91e20b002b0adce46db15d6034 100644 --- a/gcc/ada/sem_ch11.adb +++ b/gcc/ada/sem_ch11.adb @@ -120,7 +120,7 @@ package body Sem_Ch11 is elsif Nkind (Id1) /= N_Others_Choice and then (Id_Entity = Entity (Id1) - or else (Id_Entity = Renamed_Entity (Entity (Id1)))) + or else Id_Entity = Renamed_Entity (Entity (Id1))) then if Handler /= Parent (Id) then Error_Msg_Sloc := Sloc (Id1); diff --git a/gcc/ada/sem_ch12.adb b/gcc/ada/sem_ch12.adb index c4cc641c68c72a2fb029cc10bc661c2d12bbce21..d37a82502fcc63834f00a6b65ef0fdaee49bcc0e 100644 --- a/gcc/ada/sem_ch12.adb +++ b/gcc/ada/sem_ch12.adb @@ -5324,7 +5324,7 @@ package body Sem_Ch12 is Par : Entity_Id; begin Par := Scope (Curr_Scope); - while (Present (Par)) and then Par /= Standard_Standard loop + while Present (Par) and then Par /= Standard_Standard loop Install_Private_Declarations (Par); Par := Scope (Par); end loop; diff --git a/gcc/ada/sem_ch13.adb b/gcc/ada/sem_ch13.adb index a4a5084793e09a17dd71a0e4e878da58a455cbfb..9ece773304ae5c83448bd2801990d5c1b6e19088 100644 --- a/gcc/ada/sem_ch13.adb +++ b/gcc/ada/sem_ch13.adb @@ -9591,7 +9591,7 @@ package body Sem_Ch13 is -- skip null-range corner cases - elsif (REntry.Lo > REntry.Hi) or else (TLo > THi) then + elsif REntry.Lo > REntry.Hi or else TLo > THi then null; -- warn if no overlap between subtype bounds and the given range @@ -10772,7 +10772,7 @@ package body Sem_Ch13 is -- Expression from call to Check_Aspect_At_Freeze_Point. T : constant Entity_Id := - (if Present (Freeze_Expr) and (A_Id /= Aspect_Stable_Properties) + (if Present (Freeze_Expr) and A_Id /= Aspect_Stable_Properties then Etype (Original_Node (Freeze_Expr)) else Empty); -- Type required for preanalyze call. We use the original expression to @@ -15966,7 +15966,7 @@ package body Sem_Ch13 is begin Error_Msg_Ada_2022_Feature ("aspect Stable_Properties", Sloc (N)); - if (not Is_Aspect_Of_Type) and then (not Is_Subprogram (E)) then + if not Is_Aspect_Of_Type and then not Is_Subprogram (E) then Error_Msg_N ("Stable_Properties aspect can only be specified for " & "a type or a subprogram", N); elsif Class_Present then @@ -16443,7 +16443,7 @@ package body Sem_Ch13 is function Matches_Param_Type (Typ : Entity_Id) return Boolean is - ((Base_Type (Typ) = Param_Type) + (Base_Type (Typ) = Param_Type or else (Is_Class_Wide_Type (Param_Type) and then Is_Ancestor (Root_Type (Param_Type), diff --git a/gcc/ada/sem_ch3.adb b/gcc/ada/sem_ch3.adb index 7596a59edb98290d1856f93618008bd9f4f9b5ec..2ebbe36abc6789fd8b756123338cc3c3de8a8aa6 100644 --- a/gcc/ada/sem_ch3.adb +++ b/gcc/ada/sem_ch3.adb @@ -7041,7 +7041,7 @@ package body Sem_Ch3 is Desig_Type := Designated_Type (Derived_Type); if Is_Composite_Type (Desig_Type) - and then (not Is_Array_Type (Desig_Type)) + and then not Is_Array_Type (Desig_Type) and then Has_Discriminants (Desig_Type) and then Base_Type (Desig_Type) /= Desig_Type then diff --git a/gcc/ada/sem_ch4.adb b/gcc/ada/sem_ch4.adb index 7e8da9f2d5ae6c5de6b78d434621cb8ddb2e1c37..03737db90d4c5fc9e1c33ce455d79bb5e96cff45 100644 --- a/gcc/ada/sem_ch4.adb +++ b/gcc/ada/sem_ch4.adb @@ -4883,10 +4883,9 @@ package body Sem_Ch4 is function Constraint_Has_Unprefixed_Discriminant_Reference (Typ : Entity_Id) return Boolean is - function Is_Discriminant_Name (N : Node_Id) return Boolean is - ((Nkind (N) = N_Identifier) - and then (Ekind (Entity (N)) = E_Discriminant)); + (Nkind (N) = N_Identifier + and then Ekind (Entity (N)) = E_Discriminant); begin if Is_Array_Type (Typ) then declare diff --git a/gcc/ada/sem_ch6.adb b/gcc/ada/sem_ch6.adb index 8c1fb8c4f32c00ede22b9d9f1117a719a945f1c9..ba88c07e8a4caf6548281811339399433407ef4d 100644 --- a/gcc/ada/sem_ch6.adb +++ b/gcc/ada/sem_ch6.adb @@ -9025,8 +9025,8 @@ package body Sem_Ch6 is or else not (Is_Limited_Type (Formal_Type) and then - (Is_Tagged_Type - (Underlying_Type (Formal_Type))))) + Is_Tagged_Type + (Underlying_Type (Formal_Type)))) then Set_Extra_Constrained (Formal, Add_Extra_Formal (Formal, Standard_Boolean, E, "O")); @@ -10357,7 +10357,7 @@ package body Sem_Ch6 is FCL (Expressions (E1), Expressions (E2)); when N_Integer_Literal => - return (Intval (E1) = Intval (E2)) + return Intval (E1) = Intval (E2) and then not User_Defined_Numeric_Literal_Mismatch; when N_Null => @@ -10444,7 +10444,7 @@ package body Sem_Ch6 is FCE (High_Bound (E1), High_Bound (E2)); when N_Real_Literal => - return (Realval (E1) = Realval (E2)) + return Realval (E1) = Realval (E2) and then not User_Defined_Numeric_Literal_Mismatch; when N_Selected_Component => @@ -11726,7 +11726,7 @@ package body Sem_Ch6 is begin while Present (Param_E1) and then Present (Param_E2) loop - if (Ctype >= Mode_Conformant) and then + if Ctype >= Mode_Conformant and then Ekind (Defining_Identifier (Param_E1)) /= Ekind (Defining_Identifier (Param_E2)) then diff --git a/gcc/ada/sem_ch8.adb b/gcc/ada/sem_ch8.adb index 730d236b8dd8550b617387e3fc6c6493828b639b..876dbacc9515394072b95d7d090811b4ca3df3b4 100644 --- a/gcc/ada/sem_ch8.adb +++ b/gcc/ada/sem_ch8.adb @@ -7634,8 +7634,8 @@ package body Sem_Ch8 is elsif Present (First_Formal (It.Nam)) and then Present (First_Formal (New_S)) - and then (Base_Type (Etype (First_Formal (It.Nam))) = - Base_Type (Etype (First_Formal (New_S)))) + and then Base_Type (Etype (First_Formal (It.Nam))) = + Base_Type (Etype (First_Formal (New_S))) then Candidate_Renaming := It.Nam; end if; @@ -7667,8 +7667,8 @@ package body Sem_Ch8 is elsif Present (First_Formal (Entity (Nam))) and then Present (First_Formal (New_S)) - and then (Base_Type (Etype (First_Formal (Entity (Nam)))) = - Base_Type (Etype (First_Formal (New_S)))) + and then Base_Type (Etype (First_Formal (Entity (Nam)))) = + Base_Type (Etype (First_Formal (New_S))) then Candidate_Renaming := Entity (Nam); end if; @@ -10319,7 +10319,7 @@ package body Sem_Ch8 is if Is_Immediately_Visible (Prev) and then (not Is_Overloadable (Prev) or else not Is_Overloadable (Id) - or else (Type_Conformant (Id, Prev))) + or else Type_Conformant (Id, Prev)) then if No (Current_Instance) then @@ -10422,7 +10422,7 @@ package body Sem_Ch8 is -- On exit, we know entity is not hidden, unless it is private if not Is_Hidden (Id) - and then ((not Is_Child_Unit (Id)) or else Is_Visible_Lib_Unit (Id)) + and then (not Is_Child_Unit (Id) or else Is_Visible_Lib_Unit (Id)) then Set_Is_Potentially_Use_Visible (Id); diff --git a/gcc/ada/sem_ch9.adb b/gcc/ada/sem_ch9.adb index e63d48b457a4e7946cb49ce00099ec72b51ea853..67f8aa9c7bad9983dbcc7921f1c46f668d29a75a 100644 --- a/gcc/ada/sem_ch9.adb +++ b/gcc/ada/sem_ch9.adb @@ -880,7 +880,7 @@ package body Sem_Ch9 is E := First_Entity (Etype (Task_Nam)); while Present (E) loop if Chars (E) = Chars (Nam) - and then (Ekind (E) = Ekind (Accept_Id)) + and then Ekind (E) = Ekind (Accept_Id) and then Type_Conformant (Accept_Id, E) then Entry_Nam := E; @@ -2500,7 +2500,7 @@ package body Sem_Ch9 is -- for error output in some cases not to do that here. if (No (First_Formal (It.Nam)) - or else (Type_Conformant (Enclosing, It.Nam))) + or else Type_Conformant (Enclosing, It.Nam)) and then Ekind (It.Nam) = E_Entry then -- Ada 2005 (AI-345): Since protected and task types have diff --git a/gcc/ada/sem_disp.adb b/gcc/ada/sem_disp.adb index 7820a50793991c4386aae0887582679ef2796e1b..b01e3d4186ee90c46e52673376fef6832961d15a 100644 --- a/gcc/ada/sem_disp.adb +++ b/gcc/ada/sem_disp.adb @@ -1441,7 +1441,7 @@ package body Sem_Disp is -- where it can be a dispatching op is when it overrides an operation -- before the freezing point of the type. - elsif ((not Is_Package_Or_Generic_Package (Scope (Subp))) + elsif (not Is_Package_Or_Generic_Package (Scope (Subp)) or else In_Package_Body (Scope (Subp))) and then not Has_Dispatching_Parent then @@ -1488,7 +1488,7 @@ package body Sem_Disp is Decl_Item := Next (Parent (Tagged_Type)); while Present (Decl_Item) - and then (Decl_Item /= Subp_Body) + and then Decl_Item /= Subp_Body loop if Comes_From_Source (Decl_Item) and then (Nkind (Decl_Item) in N_Proper_Body @@ -2969,7 +2969,7 @@ package body Sem_Disp is end loop; end if; - if (not Is_Package_Or_Generic_Package (Current_Scope)) + if not Is_Package_Or_Generic_Package (Current_Scope) or else not In_Private_Part (Current_Scope) then -- Not a private primitive diff --git a/gcc/ada/sem_elab.adb b/gcc/ada/sem_elab.adb index 07c3df7fc4b4516df05859970b82479a1710a753..1e18b9878639702f058a655ebbbc967b4b04d560 100644 --- a/gcc/ada/sem_elab.adb +++ b/gcc/ada/sem_elab.adb @@ -19617,7 +19617,7 @@ package body Sem_Elab is Etype (First (Parameter_Associations (Call))); begin Elab_Unit := Scope (Typ); - while (Present (Elab_Unit)) + while Present (Elab_Unit) and then not Is_Compilation_Unit (Elab_Unit) loop Elab_Unit := Scope (Elab_Unit); diff --git a/gcc/ada/sem_eval.adb b/gcc/ada/sem_eval.adb index 24cd9e1aeeebb898034a81c0420d69a1f17fa560..e54f4a637e23a924b07482790bfd051453b8d77d 100644 --- a/gcc/ada/sem_eval.adb +++ b/gcc/ada/sem_eval.adb @@ -1523,7 +1523,7 @@ package body Sem_Eval is Determine_Range (R, ROK, RLo, RHi, Assume_Valid); if LOK and ROK then - Single := (LLo = LHi) and then (RLo = RHi); + Single := LLo = LHi and then RLo = RHi; if LHi < RLo then if Single and Assume_Valid then @@ -3076,7 +3076,7 @@ package body Sem_Eval is else Fold_Uint - (N, Test ((Result = Match) xor (Nkind (N) = N_Not_In)), True); + (N, Test (Result = Match xor Nkind (N) = N_Not_In), True); Warn_On_Known_Condition (N); end if; end if; @@ -6644,7 +6644,7 @@ package body Sem_Eval is -- setting Is_Constrained right for Itypes. if Is_Numeric_Type (T1) - and then (Is_Constrained (T1) /= Is_Constrained (T2)) + and then Is_Constrained (T1) /= Is_Constrained (T2) and then (Scope (T1) = Standard_Standard or else Comes_From_Source (T1)) and then (Scope (T2) = Standard_Standard @@ -6658,7 +6658,7 @@ package body Sem_Eval is elsif Is_Generic_Type (T1) and then Is_Generic_Type (T2) - and then (Is_Constrained (T1) /= Is_Constrained (T2)) + and then Is_Constrained (T1) /= Is_Constrained (T2) then return False; end if; diff --git a/gcc/ada/sem_prag.adb b/gcc/ada/sem_prag.adb index 5fe5d6a2d0fb6fc7e9e86172609d431b3ff61ec9..b6c78dbd559b714554b529c371ce5848dd8cd40b 100644 --- a/gcc/ada/sem_prag.adb +++ b/gcc/ada/sem_prag.adb @@ -12940,8 +12940,8 @@ package body Sem_Prag is Standard_String); begin for Idx in Type_Table'Range loop - if (L_Type = Type_Table (Idx)) or - (R_Type = Type_Table (Idx)) + if L_Type = Type_Table (Idx) or + R_Type = Type_Table (Idx) then return Type_Table (Idx); end if; @@ -15493,7 +15493,7 @@ package body Sem_Prag is Default := Fold_Upper (Name_Buffer (1)); if not Support_Nondefault_SSO_On_Target - and then (Ttypes.Bytes_Big_Endian /= (Default = 'H')) + and then Ttypes.Bytes_Big_Endian /= (Default = 'H') then if Warn_On_Unrecognized_Pragma then Error_Msg_N diff --git a/gcc/ada/sem_res.adb b/gcc/ada/sem_res.adb index f6634da42a7809d37d354c8b71c1cf8ee88506aa..3eb13de38dff03cbf1af17f765f977cd94801d39 100644 --- a/gcc/ada/sem_res.adb +++ b/gcc/ada/sem_res.adb @@ -2937,7 +2937,7 @@ package body Sem_Res is -- view-swapping mechanism has no identifier. elsif (In_Instance or else In_Inlined_Body) - and then (Nkind (N) = N_Null) + and then Nkind (N) = N_Null and then Is_Private_Type (Typ) and then Is_Access_Type (Full_View (Typ)) then @@ -6305,11 +6305,11 @@ package body Sem_Res is begin Determine_Range (Left_Opnd (N), OK, Lo, Hi, Assume_Valid => True); - LNeg := (not OK) or else Lo < 0; + LNeg := not OK or else Lo < 0; Determine_Range (Right_Opnd (N), OK, Lo, Hi, Assume_Valid => True); - RNeg := (not OK) or else Lo < 0; + RNeg := not OK or else Lo < 0; -- Check if we will be generating conditionals. There are two -- cases where that can happen, first for REM, the only case @@ -10916,14 +10916,14 @@ package body Sem_Res is if not Parentheses_Found and then Comes_From_Source (Par) and then - ((Nkind (Par) in N_Modular_Type_Definition - | N_Floating_Point_Definition - | N_Ordinary_Fixed_Point_Definition - | N_Decimal_Fixed_Point_Definition - | N_Extension_Aggregate - | N_Discriminant_Specification - | N_Parameter_Specification - | N_Formal_Object_Declaration) + (Nkind (Par) in N_Modular_Type_Definition + | N_Floating_Point_Definition + | N_Ordinary_Fixed_Point_Definition + | N_Decimal_Fixed_Point_Definition + | N_Extension_Aggregate + | N_Discriminant_Specification + | N_Parameter_Specification + | N_Formal_Object_Declaration or else (Nkind (Par) = N_Object_Declaration and then @@ -13229,8 +13229,8 @@ package body Sem_Res is -- For other operators the context does not impose a type on -- the operands, but their types must match. - if (Nkind (Left_Opnd (N)) - not in N_Integer_Literal | N_String_Literal | N_Real_Literal) + if Nkind (Left_Opnd (N)) + not in N_Integer_Literal | N_String_Literal | N_Real_Literal and then Has_Applicable_User_Defined_Literal (Right_Opnd (N), Etype (Left_Opnd (N))) @@ -13238,8 +13238,8 @@ package body Sem_Res is Analyze_And_Resolve (N, Typ); return True; - elsif (Nkind (Right_Opnd (N)) - not in N_Integer_Literal | N_String_Literal | N_Real_Literal) + elsif Nkind (Right_Opnd (N)) + not in N_Integer_Literal | N_String_Literal | N_Real_Literal and then Has_Applicable_User_Defined_Literal (Left_Opnd (N), Etype (Right_Opnd (N))) @@ -13543,8 +13543,8 @@ package body Sem_Res is -- return False if Expr not of form <prefix>.all.Some_Component - if (Nkind (Expr) /= N_Selected_Component) - or else (Nkind (Prefix (Expr)) /= N_Explicit_Dereference) + if Nkind (Expr) /= N_Selected_Component + or else Nkind (Prefix (Expr)) /= N_Explicit_Dereference then -- conditional expressions, declare expressions ??? return False; @@ -13628,8 +13628,8 @@ package body Sem_Res is if not (Is_Integer_Type (Target_Index_Type) and then Is_Integer_Type (Opnd_Index_Type)) - and then (Root_Type (Target_Index_Type) - /= Root_Type (Opnd_Index_Type)) + and then Root_Type (Target_Index_Type) + /= Root_Type (Opnd_Index_Type) then Conversion_Error_N ("incompatible index types for array conversion", diff --git a/gcc/ada/sem_type.adb b/gcc/ada/sem_type.adb index 0c0df68fee5177cc226a12f464c79d1313b4e691..d4006e4270bb888c286d3a39fb43ff9801fa0fed 100644 --- a/gcc/ada/sem_type.adb +++ b/gcc/ada/sem_type.adb @@ -1033,8 +1033,8 @@ package body Sem_Type is and then Ekind (BT1) = E_General_Access_Type and then Ekind (BT2) = E_Anonymous_Access_Type and then Covers (Designated_Type (T1), Designated_Type (T2)) - and then (Is_Class_Wide_Type (Designated_Type (T1)) >= - Is_Class_Wide_Type (Designated_Type (T2))) + and then Is_Class_Wide_Type (Designated_Type (T1)) >= + Is_Class_Wide_Type (Designated_Type (T2)) then return True; @@ -3210,7 +3210,7 @@ package body Sem_Type is elsif Op_Name = Name_Op_Concat then return Is_Array_Type (T) - and then (Base_Type (T) = Base_Type (Etype (Op))) + and then Base_Type (T) = Base_Type (Etype (Op)) and then (Base_Type (T1) = Base_Type (T) or else Base_Type (T1) = Base_Type (Component_Type (T))) diff --git a/gcc/ada/sem_util.adb b/gcc/ada/sem_util.adb index 3ea7ef506dfb552cd39d14bd3872d210ceea2332..391cade9eaca2f58215219090be587d5636931f7 100644 --- a/gcc/ada/sem_util.adb +++ b/gcc/ada/sem_util.adb @@ -7338,7 +7338,7 @@ package body Sem_Util is | N_Defining_Program_Unit_Name then return - (Chars (Select_Node (Name1)) = Chars (Select_Node (Name2))) + Chars (Select_Node (Name1)) = Chars (Select_Node (Name2)) and then Designate_Same_Unit (Prefix_Node (Name1), Prefix_Node (Name2)); @@ -9904,7 +9904,7 @@ package body Sem_Util is -- with Static_Predicate => Null_By_Predicate < 0; -- so test for that null case separately. - if (not Has_Static_Predicate (Discrim_Value_Subtype)) + if not Has_Static_Predicate (Discrim_Value_Subtype) or else Present (First (Static_Discrete_Predicate (Discrim_Value_Subtype))) then @@ -10113,7 +10113,7 @@ package body Sem_Util is -- Checking the type, not the underlying type, for constrainedness -- seems to be necessary. Maybe all the tests should be on the type??? - elsif (not Is_Constrained (Typ)) + elsif not Is_Constrained (Typ) and then (Is_Array_Type (Utyp) or else (Is_Record_Type (Utyp) and then Has_Discriminants (Utyp))) @@ -15764,8 +15764,8 @@ package body Sem_Util is Item_1 : constant Node_Id := Aspect_Rep_Item (Aspect_Spec_1); Item_2 : constant Node_Id := Aspect_Rep_Item (Aspect_Spec_2); begin - if (Nkind (Item_1) /= N_Attribute_Definition_Clause) - or (Nkind (Item_2) /= N_Attribute_Definition_Clause) + if Nkind (Item_1) /= N_Attribute_Definition_Clause + or Nkind (Item_2) /= N_Attribute_Definition_Clause then pragma Assert (Serious_Errors_Detected > 0); return True; @@ -18107,8 +18107,8 @@ package body Sem_Util is Next (First (Expressions (Original_Exp))); Else_Expr : constant Node_Id := Next (Then_Expr); begin - if (Is_NC (Then_Expr) = Bad_Result) - or else (Is_NC (Else_Expr) = Bad_Result) + if Is_NC (Then_Expr) = Bad_Result + or else Is_NC (Else_Expr) = Bad_Result then return Bad_Result; else @@ -27559,7 +27559,7 @@ package body Sem_Util is -- call to Ada.Task_Identification.Abort_Task. if Restriction_Check_Required (No_Abort_Statements) - and then (Is_RTE (Val, RE_Abort_Task)) + and then Is_RTE (Val, RE_Abort_Task) -- A special extra check, don't complain about a reference from within -- the Ada.Task_Identification package itself! @@ -28063,8 +28063,8 @@ package body Sem_Util is High_Value : constant Uint := Expr_Value (Type_High_Bound (Index_Subtype)); begin - if (Index_Value < Low_Value) - or (Index_Value > High_Value) + if Index_Value < Low_Value + or Index_Value > High_Value then return False; end if; @@ -28072,8 +28072,8 @@ package body Sem_Util is Next_Index (Indx); Expr := Next (Expr); - pragma Assert ((Present (Indx) = Present (Expr)) - or else (Serious_Errors_Detected > 0)); + pragma Assert (Present (Indx) = Present (Expr) + or else Serious_Errors_Detected > 0); exit when not (Present (Indx) and Present (Expr)); end loop; end; diff --git a/gcc/ada/sinput.adb b/gcc/ada/sinput.adb index 2e07a424ba294b8fa2e7297246dd537e0b6c6ebc..4352cad62c77c056e1cc15f63d4a43179740056f 100644 --- a/gcc/ada/sinput.adb +++ b/gcc/ada/sinput.adb @@ -550,7 +550,7 @@ package body Sinput is or else S = Standard_ASCII_Location or else S = System_Location; - pragma Assert ((S > No_Location) xor Special); + pragma Assert (S > No_Location xor Special); pragma Assert (Result in Source_File.First .. Source_File.Last); SFR : Source_File_Record renames Source_File.Table (Result); diff --git a/gcc/ada/uintp.adb b/gcc/ada/uintp.adb index 02dd4d90ecf24e992647e2d2e8b06957526d5354..f58353b01394684dddc212e07e6e3de7fbdc5a56 100644 --- a/gcc/ada/uintp.adb +++ b/gcc/ada/uintp.adb @@ -2027,7 +2027,7 @@ package body Uintp is begin Init_Operand (Left, L_Vec); Init_Operand (Right, R_Vec); - Neg := (L_Vec (1) < Int_0) xor (R_Vec (1) < Int_0); + Neg := L_Vec (1) < Int_0 xor R_Vec (1) < Int_0; L_Vec (1) := abs (L_Vec (1)); R_Vec (1) := abs (R_Vec (1));