+2019-08-20 Gary Dismukes <dismukes@adacore.com>
+
+ * ali.adb, ali.ads, aspects.adb, checks.ads, checks.adb,
+ doc/gnat_rm/implementation_defined_pragmas.rst,
+ doc/gnat_ugn/building_executable_programs_with_gnat.rst,
+ einfo.ads, exp_aggr.adb, exp_ch11.adb, exp_ch3.ads, exp_ch4.adb,
+ exp_disp.adb, inline.adb, libgnat/a-locale.ads,
+ libgnat/s-soflin.ads, par_sco.adb, repinfo.adb, sem_ch5.adb,
+ sem_disp.adb, sem_elab.adb, sem_eval.adb, sem_spark.adb,
+ sem_spark.ads, sinfo.ads: Minor reformattings, typo fixes and
+ and rewordings.
+
2019-08-20 Dmitriy Anisimkov <anisimko@adacore.com>
* adaint.c (__gnat_to_gm_time): On _WIN32, don't round time up
Xref.Init;
Xref_Section.Init;
- -- Add dummy zero'th item in Linker_Options and Notes for sort calls
+ -- Add dummy zeroth item in Linker_Options and Notes for sort calls
Linker_Options.Increment_Last;
Notes.Increment_Last;
-- but before the entries from the run-time.
end record;
- -- The indexes of active entries in this table range from 1 to
- -- the value of Linker_Options.Last. The zero'th element is for
- -- convenience if the table needs to be sorted.
+ -- The indexes of active entries in this table range from 1 to the value of
+ -- Linker_Options.Last. The zeroth element is for convenience if the table
+ -- needs to be sorted.
package Linker_Options is new Table.Table (
Table_Component_Type => Linker_Option_Record,
-- location to the last character on the line.
end record;
- -- The indexes of active entries in this table range from 1 to the
- -- value of Notes.Last. The zero'th element is for convenience if
- -- the table needs to be sorted.
+ -- The indexes of active entries in this table range from 1 to the value of
+ -- Notes.Last. The zeroth element is for convenience if the table needs to
+ -- be sorted.
package Notes is new Table.Table (
Table_Component_Type => Notes_Record,
end if;
if Is_Private_Type (Owner)
- and then Present (Full_View (Owner))
- and then not Operational_Aspect (A)
+ and then Present (Full_View (Owner))
+ and then not Operational_Aspect (A)
then
Owner := Full_View (Owner);
end if;
(Formal : Entity_Id;
Prag_Nam : Name_Id;
For_Result : Boolean := False);
- -- Add a single 'Valid[_Scalar] check which verifies the initialization
+ -- Add a single 'Valid[_Scalars] check which verifies the initialization
-- of Formal. Prag_Nam denotes the pre or post condition pragma name.
-- Set flag For_Result when to verify the result of a function.
procedure Activate_Range_Check (N : Node_Id);
pragma Inline (Activate_Range_Check);
- -- Sets Do_Range_Check flag in node N, and handles possible local raise
+ -- Sets Do_Range_Check flag in node N, and handles possible local raise.
-- Always call this routine rather than calling Set_Do_Range_Check to
-- set an explicit value of True, to ensure handling the local raise case.
pragma Aggregate_Individually_Assign;
-Where possible GNAT will store the binary representation of a record aggregate
+Where possible, GNAT will store the binary representation of a record aggregate
in memory for space and performance reasons. This configuration pragma changes
-this behaviour so that record aggregates are instead always converted into
+this behavior so that record aggregates are instead always converted into
individual assignment statements.
The set of style check switches is set to match that used by the GNAT sources.
This may be useful when developing code that is eventually intended to be
- incorporated into GNAT. Currently this is equivalent to :switch:`-gnatwydISux`)
+ incorporated into GNAT. Currently this is equivalent to :switch:`-gnatyydISux`)
but additional style switches may be added to this set in the future without
advance notice.
-- In that case, this field points to that subtype.
--
-- For E_Class_Wide_Subtype, the presence of Equivalent_Type overrides
--- this field. Note that this field ONLY appears in subtype entries, not
--- in type entries, it is not defined, and it is an error to reference
+-- this field. Note that this field ONLY appears in subtype entities, not
+-- in type entities, it is not defined, and it is an error to reference
-- Cloned_Subtype in an E_Record_Type or E_Class_Wide_Type entity.
-- Comes_From_Source
-- depends on a private type.
-- Derived_Type_Link (Node31)
--- Defined in all type and subtype entries. Set in a base type if
+-- Defined in all type and subtype entities. Set in a base type if
-- a derived type declaration is encountered which derives from
-- this base type or one of its subtypes, and there are already
-- primitive operations declared. In this case, it references the
-- initial value). See Exp_Util.Expand_Class_Wide_Subtype for further
-- details. For E_Exception_Type, this points to the record containing
-- the data necessary to represent exceptions (for further details, see
--- System.Standard_Library. For access_to_protected subprograms, it
+-- System.Standard_Library). For access to protected subprograms, it
-- denotes a record that holds pointers to the operation and to the
-- protected object. For remote Access_To_Subprogram types, it denotes
-- the record that is the fat pointer representation of an RAST.
-- set, signalling that Freeze.Inherit_Delayed_Rep_Aspects must be called
-- at the freeze point of the derived type.
--- Has_DIC (syntherized)
+-- Has_DIC (synthesized)
-- Defined in all type entities. Set for a private type and its full view
-- when the type is subject to pragma Default_Initial_Condition (DIC), or
-- when the type inherits a DIC pragma from a parent type.
-- Unmodified and Unreferenced pragmas.
-- Has_Pragma_Unused (Flag294)
--- Defined in all entries. Set if a valid pragma Unused applies to a
+-- Defined in all entities. Set if a valid pragma Unused applies to a
-- variable or entity, indicating that warnings should not be given if
-- it is never modified or referenced. Note: This pragma is exactly
-- equivalent Unmodified and Unreference combined.
-- frozen. If set it indicates that the representation is known to be
-- unsigned (i.e. that no negative values appear in the range). This is
-- normally just a reflection of the lower bound of the subtype or base
--- type, but there is one case in which the setting is non-obvious,
+-- type, but there is one case in which the setting is not obvious,
-- namely the case of an unsigned subtype of a signed type from which
-- a further subtype is obtained using variable bounds. This further
-- subtype is still unsigned, but this cannot be determined by looking
return;
end if;
- -- If the pramga Aggregate_Individually_Assign is set always convert to
+ -- If the pramga Aggregate_Individually_Assign is set, always convert to
-- assignments.
if Aggregate_Individually_Assign then
-- N is the node on which the warning is placed.
procedure Warn_If_No_Propagation (N : Node_Id);
- -- Called for an exception raise that is not a local raise (and thus
- -- cannot be optimized to a goto). Issues warning if
- -- No_Exception_Propagation restriction is set.
- -- N is the node for the raise or equivalent call.
+ -- Called for an exception raise that is not a local raise (and thus cannot
+ -- be optimized to a goto). Issues warning if No_Exception_Propagation
+ -- restriction is set. N is the node for the raise or equivalent call.
---------------------------
-- Expand_At_End_Handler --
(Typ : Entity_Id;
N : Node_Id;
Size : Uint := No_Uint) return Node_Id;
- -- Build an expression which represents the required initial value of type
+ -- Build an expression that represents the required initial value of type
-- Typ for which predicate Needs_Simple_Initialization is True. N is a node
- -- whose source location used in the construction of the expression. Size
- -- is utilized as follows:
+ -- whose source location is used in the construction of the expression.
+ -- Size is used as follows:
--
-- * If the size of the object to be initialized it is known, it should
-- be passed to the routine.
--
-- The object size is needed to prepare a known invalid value for use by
-- Normalize_Scalars. A call to this routine where Typ denotes a scalar
- -- type is only valid when Normalize_Scalars or Initialize_Scalars is
+ -- type is valid only when Normalize_Scalars or Initialize_Scalars is
-- active, or if N is the node for a 'Invalid_Value attribute node.
procedure Init_Secondary_Tags
Statements => New_List (Loop_Stm)));
-- If no separate indexes, return loop statement with explicit
- -- iteration scheme on its own
+ -- iteration scheme on its own.
else
Loop_Stm :=
-- The J'th entry in an expression node that represents the total length
-- of operands 1 through J. It is either an integer literal node, or a
-- reference to a constant entity with the right value, so it is fine
- -- to just do a Copy_Node to get an appropriate copy. The extra zero'th
+ -- to just do a Copy_Node to get an appropriate copy. The extra zeroth
-- entry always is set to zero. The length is of type Artyp.
Low_Bound : Node_Id;
begin
-- Warn on the presence of an allocator of an anonymous access type when
- -- enabled except when its an object declaration at library level.
+ -- enabled, except when it's an object declaration at library level.
if Warn_On_Anonymous_Allocators
and then Ekind (PtrT) = E_Anonymous_Access_Type
end if;
-- Nothing to do if expression was rewritten into a float-to-float
- -- conversion, since this kind of conversions is handled elsewhere.
+ -- conversion, since this kind of conversion is handled elsewhere.
if Is_Floating_Point_Type (Etype (Expr))
and then Is_Floating_Point_Type (Target_Type)
-- If the dispatching call appears in the same scope as the
-- declaration of the dispatching subprogram (for example in
- -- the expression of a local expression function) the prec.
+ -- the expression of a local expression function), the spec
-- has not been analyzed yet, in which case we use the Chars
-- field to recognize intended occurrences of the formals.
F := First_Formal (Subp);
A := First_Actual (Call_Node);
- if Present (Entity (N))
- and then Is_Formal (Entity (N))
- then
+ if Present (Entity (N)) and then Is_Formal (Entity (N)) then
while Present (F) loop
if F = Entity (N) then
Rewrite (N, New_Copy_Tree (A));
Next_Actual (A);
end loop;
- -- If node is not analyzed, recognize occurrences of
- -- a formal by name, as would be done when resolving
- -- the aspect expression in the context of the subprogram.
+ -- If the node is not analyzed, recognize occurrences of a
+ -- formal by name, as would be done when resolving the aspect
+ -- expression in the context of the subprogram.
elsif not Analyzed (N)
and then Nkind (N) = N_Identifier
-- declares the type, and that body is visible to the back end.
-- Do not inline it either if it is in the main unit.
-- Extend the -gnatn2 processing to -gnatn1 for Inline_Always
- -- calls if the back-end takes care of inlining the call.
- -- Note that Level is in Inline_Call | Inline_Packag here.
+ -- calls if the back end takes care of inlining the call.
+ -- Note that Level is in Inline_Call | Inline_Package here.
elsif ((Level = Inline_Call
and then Has_Pragma_Inline_Always (E)
pragma Remote_Types (Locales);
-- A locale identifies a geopolitical place or region and its associated
- -- language, which can be used to determine other
- -- internationalization-related characteristics. The active locale is the
- -- locale associated with the partition of the current task.
+ -- language, which can be used to determine other internationalization-
+ -- related characteristics. The active locale is the locale associated with
+ -- the partition of the current task.
type Language_Code is new String (1 .. 3)
with Dynamic_Predicate =>
-- Wrapper to the possible user specified traceback decorator to be
-- called during automatic output of exception data.
- -- The null value of this wrapper correspond sto the null value of the
+ -- The null value of this wrapper corresponds to the null value of the
-- current actual decorator. This is ensured first by the null initial
-- value of the corresponding variables, and then by Set_Trace_Decorator
-- in g-exctra.adb.
pragma Atomic (Traceback_Decorator_Wrapper);
-- Since concurrent read/write operations may occur on this variable.
- -- See the body of Tailored_Exception_Traceback in Ada.Exceptions for
- -- a more detailed description of the potential problems.
+ -- See the body of Tailored_Exception_Traceback in
+ -- Ada.Exceptions.Exception_Data for a more detailed description of the
+ -- potential problems.
procedure Save_Library_Occurrence (E : EOA);
-- When invoked, this routine saves an exception occurrence into a hidden
-- writing out the SCO information to the ALI file, we can fill in the
-- proper dependency numbers and file names.
- -- Note that the zero'th entry is here for convenience in sorting the
- -- table, the real lower bound is 1.
+ -- Note that the zeroth entry is here for convenience in sorting the table;
+ -- the real lower bound is 1.
package SCO_Unit_Number_Table is new Table.Table
(Table_Component_Type => Unit_Number_Type,
Has_Rep_Item (Ent, Name_Scalar_Storage_Order)
or else SSO_Set_Low_By_Default (Ent)
or else SSO_Set_High_By_Default (Ent);
- -- Scalar_Storage_Order is displayed if specified explicitly
- -- or set by Default_Scalar_Storage_Order.
+ -- Scalar_Storage_Order is displayed if specified explicitly or set by
+ -- Default_Scalar_Storage_Order.
-- Start of processing for List_Scalar_Storage_Order
It : Interp;
begin
- -- THe domain of iteralion must implement either the RM
+ -- The domain of iteration must implement either the RM
-- iterator interface, or the SPARK Iterable aspect.
if No (Iterator) then
- if No
- (Find_Aspect (Etype (Iter_Name), Aspect_Iterable))
- then
- Error_Msg_NE ("cannot iterate over&",
- N, Base_Type (Etype (Iter_Name)));
+ if No (Find_Aspect (Etype (Iter_Name), Aspect_Iterable)) then
+ Error_Msg_NE
+ ("cannot iterate over&",
+ N, Base_Type (Etype (Iter_Name)));
return;
end if;
-- 3. Subprograms associated with stream attributes (built by
-- New_Stream_Subprogram)
- -- 4. Wrapper built for inherited operations with inherited class-
+ -- 4. Wrappers built for inherited operations with inherited class-
-- wide conditions, where the conditions include calls to other
-- overridden primitives. The wrappers include checks on these
-- modified conditions. (AI12-113).
- -- 5. Declarations built for subprograms without separate spec which
+ -- 5. Declarations built for subprograms without separate specs that
-- are eligible for inlining in GNATprove (inside
-- Sem_Ch6.Analyze_Subprogram_Body_Helper).
begin
-- Nothing to do for predefined primitives because they are
-- artifacts of tagged type expansion and cannot override source
- -- primitives. Nothing to do as well for inherited primitives as
- -- the check concerns overridding ones.
+ -- primitives. Nothing to do as well for inherited primitives, as
+ -- the check concerns overriding ones.
if Is_Predefined_Dispatching_Operation (Prim)
or else not Is_Overriding_Subprogram (Prim)
elsif Is_Out_Of_Range (N, Base_Type (T), Assume_Valid => True) then
Out_Of_Range (N);
- -- Give a warning or error on the value outside the subtype. A
- -- warning is omitted if the expression appears in a range that could
- -- be null (warnings are handled elsewhere for this case).
+ -- Give a warning or error on the value outside the subtype. A warning
+ -- is omitted if the expression appears in a range that could be null
+ -- (warnings are handled elsewhere for this case).
elsif T /= Base_Type (T) and then Nkind (Parent (N)) /= N_Range then
if Is_In_Range (N, T, Assume_Valid => True) then
if CodePeer_Mode and then T = RTE (RE_Priority) then
Set_Do_Range_Check (N, False);
- -- Determine if the out of range violation constitutes a warning
- -- or an error based on context according to RM 4.9 (34/3).
+ -- Determine if the out-of-range violation constitutes a warning
+ -- or an error based on context, according to RM 4.9 (34/3).
elsif Nkind_In (Original_Node (N), N_Type_Conversion,
N_Qualified_Expression)
-- CodePeer mode where the target runtime may have more priorities.
elsif not CodePeer_Mode or else Etype (N) /= RTE (RE_Priority) then
- -- Determine if the out of range violation constitutes a warning
- -- or an error based on context according to RM 4.9 (34/3).
+ -- Determine if the out-of-range violation constitutes a warning
+ -- or an error based on context, according to RM 4.9 (34/3).
if Nkind (Original_Node (N)) = N_Type_Conversion
and then not Comes_From_Source (Original_Node (N))
Expr_Root := Get_Root_Object (Expr);
- -- SPARK RM 3.10(8): For an assignment statement where
- -- the target is a stand-alone object of an anonymous
- -- access-to-object type
+ -- SPARK RM 3.10(7): For an assignment statement where the target is
+ -- a stand-alone object of an anonymous access-to-object type.
pragma Assert (Present (Target_Root));
- -- If the type of the target is an anonymous
- -- access-to-constant type (an observing access type), the
- -- source shall be an owning access object denoted by a name
- -- that is not in the Moved state, and whose root object
- -- is not in the Moved state and is not declared at a
- -- statically deeper accessibility level than that of
- -- the target object.
+ -- If the type of the target is an anonymous access-to-constant type
+ -- (an observing access type), the source shall be an owning access
+ -- object denoted by a name that is not in the Moved state, and whose
+ -- root object is not in the Moved state and is not declared at a
+ -- statically deeper accessibility level than that of the target
+ -- object.
if Is_Access_Constant (Target_Typ) then
Perm := Get_Perm (Expr);
-- ??? check accessibility level
- -- If the type of the target is an anonymous
- -- access-to-variable type (an owning access type), the
- -- source shall be an owning access object denoted by a
- -- name that is in the Unrestricted state, and whose root
- -- object is the target object itself.
+ -- If the type of the target is an anonymous access-to-variable
+ -- type (an owning access type), the source shall be an owning
+ -- access object denoted by a name that is in the Unrestricted
+ -- state, and whose root object is the target object itself.
Check_Expression (Expr, Observe);
Handle_Observe (Target_Root, Expr, Is_Decl);
-- when there are violations of ownership rules.
function Is_Deep (Typ : Entity_Id) return Boolean;
- -- A function that can tell whether a type is deep. Returns True if the
- -- type passed as argument is deep.
+ -- Returns True if the type passed as argument is deep
function Is_Traversal_Function (E : Entity_Id) return Boolean;
-- Present in N_Extended_Return_Statement. Points to a list initially
-- containing a single N_Object_Declaration representing the return
-- object. We use a list (instead of just a pointer to the object decl)
- -- because Analyze wants to insert extra actions on this list.
+ -- because Analyze wants to insert extra actions on this list, before the
+ -- N_Object_Declaration, which always remains last on the list.
-- Rounded_Result (Flag18-Sem)
-- Present in N_Type_Conversion, N_Op_Divide, and N_Op_Multiply nodes.