diff gcc/ada/sinfo.ads @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
children 1830386684a0
line wrap: on
line diff
--- a/gcc/ada/sinfo.ads	Fri Oct 27 22:46:09 2017 +0900
+++ b/gcc/ada/sinfo.ads	Thu Oct 25 07:37:49 2018 +0900
@@ -6,7 +6,7 @@
 --                                                                          --
 --                                 S p e c                                  --
 --                                                                          --
---          Copyright (C) 1992-2017, Free Software Foundation, Inc.         --
+--          Copyright (C) 1992-2018, Free Software Foundation, Inc.         --
 --                                                                          --
 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
 -- terms of the  GNU General Public License as published  by the Free Soft- --
@@ -38,7 +38,7 @@
 
 --  The tree contains not only the full syntactic representation of the
 --  program, but also the results of semantic analysis. In particular, the
---  nodes for defining identifiers, defining character literals and defining
+--  nodes for defining identifiers, defining character literals, and defining
 --  operator symbols, collectively referred to as entities, represent what
 --  would normally be regarded as the symbol table information. In addition a
 --  number of the tree nodes contain semantic information.
@@ -213,7 +213,7 @@
 
    --  The Present function tests for Empty, which in this case signals the end
    --  of the list. First returns Empty immediately if the list is empty.
-   --  Present is defined in Atree, First and Next are defined in Nlists.
+   --  Present is defined in Atree; First and Next are defined in Nlists.
 
    --  The exceptions to this rule occur with {DEFINING_IDENTIFIERS} in all
    --  contexts, which is handled as described in the previous section, and
@@ -389,7 +389,7 @@
 
    --  In the following node definitions, all fields, both syntactic and
    --  semantic, are documented. The one exception is in the case of entities
-   --  (defining identifiers, character literals and operator symbols), where
+   --  (defining identifiers, character literals, and operator symbols), where
    --  the usage of the fields depends on the entity kind. Entity fields are
    --  fully documented in the separate package Einfo.
 
@@ -531,75 +531,89 @@
    --  The SPARK RM 6.9 defines two classes of constructs - Ghost entities and
    --  Ghost statements. The intent of the feature is to treat Ghost constructs
    --  as non-existent when Ghost assertion policy Ignore is in effect.
-
+   --
    --  The corresponding nodes which map to Ghost constructs are:
-
+   --
    --    Ghost entities
    --      Declaration nodes
    --      N_Package_Body
    --      N_Subprogram_Body
-
+   --
    --    Ghost statements
    --      N_Assignment_Statement
    --      N_Procedure_Call_Statement
    --      N_Pragma
-
+   --
    --  In addition, the compiler treats instantiations as Ghost entities
-
+   --
    --  To achieve the removal of ignored Ghost constructs, the compiler relies
-   --  on global variable Ghost_Mode and a mechanism called "Ghost regions".
-   --  The values of the global variable are as follows:
-
+   --  on global variables Ghost_Mode and Ignored_Ghost_Region, which comprise
+   --  a mechanism called "Ghost regions".
+   --
+   --  The values of Ghost_Mode are as follows:
+   --
    --    1. Check - All static semantics as defined in SPARK RM 6.9 are in
    --       effect. The Ghost region has mode Check.
-
+   --
    --    2. Ignore - Same as Check, ignored Ghost code is not present in ALI
    --       files, object files, and the final executable. The Ghost region
    --       has mode Ignore.
-
+   --
    --    3. None - No Ghost region is in effect
-
+   --
+   --  The value of Ignored_Ghost_Region captures the node which initiates an
+   --  ignored Ghost region.
+   --
    --  A Ghost region is a compiler operating mode, similar to Check_Syntax,
    --  however a region is much more finely grained and depends on the policy
    --  in effect. The region starts prior to the analysis of a Ghost construct
    --  and ends immediately after its expansion. The region is established as
    --  follows:
-
+   --
    --    1. Declarations - Prior to analysis, if the declaration is subject to
    --       pragma Ghost.
-
+   --
    --    2. Renaming declarations - Same as 1) or when the renamed entity is
    --       Ghost.
-
+   --
    --    3. Completing declarations - Same as 1) or when the declaration is
    --       partially analyzed and the declaration completes a Ghost entity.
-
+   --
    --    4. N_Package_Body, N_Subprogram_Body - Same as 1) or when the body is
    --       partially analyzed and completes a Ghost entity.
-
+   --
    --    5. N_Assignment_Statement - After the left hand side is analyzed and
    --       references a Ghost entity.
-
+   --
    --    6. N_Procedure_Call_Statement - After the name is analyzed and denotes
    --       a Ghost procedure.
-
+   --
    --    7. N_Pragma - During analysis, when the related entity is Ghost or the
    --       pragma encloses a Ghost entity.
-
+   --
    --    8. Instantiations - Save as 1) or when the instantiation is partially
    --       analyzed and the generic template is Ghost.
-
-   --  Routines Mark_And_Set_Ghost_xxx and Set_Ghost_Mode install a new Ghost
-   --  region and routine Restore_Ghost_Mode ends a Ghost region. A region may
-   --  be reinstalled similarly to scopes for decoupled expansion such as the
-   --  generation of dispatch tables or the creation of a predicate function.
-
+   --
+   --  The following routines install a new Ghost region:
+   --
+   --     Install_Ghost_Region
+   --     Mark_And_Set_Ghost_xxx
+   --     Set_Ghost_Mode
+   --
+   --  The following routine ends a Ghost region:
+   --
+   --     Restore_Ghost_Region
+   --
+   --  A region may be reinstalled similarly to scopes for decoupled expansion
+   --  such as the generation of dispatch tables or the creation of a predicate
+   --  function.
+   --
    --  If the mode of a Ghost region is Ignore, any newly created nodes as well
    --  as source entities are marked as ignored Ghost. In additon, the marking
    --  process signals all enclosing scopes that an ignored Ghost node resides
    --  within. The compilation unit where the node resides is also added to an
    --  auxiliary table for post processing.
-
+   --
    --  After the analysis and expansion of all compilation units takes place
    --  as well as the instantiation of all inlined [generic] bodies, the GNAT
    --  driver initiates a separate pass which removes all ignored Ghost nodes
@@ -626,7 +640,7 @@
 
    --  The tree after this light expansion should be fully analyzed
    --  semantically, which sometimes requires the insertion of semantic
-   --  pre-analysis, for example for subprogram contracts and pragma
+   --  preanalysis, for example for subprogram contracts and pragma
    --  check/assert. In particular, all expression must have their proper type,
    --  and semantic links should be set between tree nodes (partial to full
    --  view, etc.) Some kinds of nodes should be either absent, or can be
@@ -1116,7 +1130,7 @@
    --    complete a subprogram declaration.
 
    --  Corresponding_Spec_Of_Stub (Node2-Sem)
-   --    This field is present in subprogram, package, task and protected body
+   --    This field is present in subprogram, package, task, and protected body
    --    stubs where it points to the corresponding spec of the stub. Due to
    --    clashes in the structure of nodes, we cannot use Corresponding_Spec.
 
@@ -1589,25 +1603,32 @@
    --    expansion of the same attribute in the said context.
 
    --  Hidden_By_Use_Clause (Elist5-Sem)
-   --     An entity list present in use clauses that appear within
-   --     instantiations. For the resolution of local entities, entities
-   --     introduced by these use clauses have priority over global ones, and
-   --     outer entities must be explicitly hidden/restored on exit.
+   --    An entity list present in use clauses that appear within
+   --    instantiations. For the resolution of local entities, entities
+   --    introduced by these use clauses have priority over global ones,
+   --    and outer entities must be explicitly hidden/restored on exit.
 
    --  Implicit_With (Flag16-Sem)
-   --    This flag is set in the N_With_Clause node that is implicitly
-   --    generated for runtime units that are loaded by the expander or in
-   --    GNATprove mode, and also for package System, if it is loaded
-   --    implicitly by a use of the 'Address or 'Tag attribute.
-   --    ??? There are other implicit with clauses as well.
-
-   --  Implicit_With_From_Instantiation (Flag12-Sem)
-   --     Set in N_With_Clause nodes from generic instantiations.
+   --    Present in N_With_Clause nodes. The flag indicates that the clause
+   --    does not comes from source and introduces an implicit dependency on
+   --    a particular unit. Such implicit with clauses are generated by:
+   --
+   --      * ABE mechanism - The static elaboration model of both the default
+   --        and the legacy ABE mechanism use with clauses to encode implicit
+   --        Elaborate[_All] pragmas.
+   --
+   --      * Analysis - A with clause for child unit A.B.C is equivalent to
+   --        a series of clauses that with A, A.B, and A.B.C. Manipulation of
+   --        contexts utilizes implicit with clauses to emulate the visibility
+   --        of a particular unit.
+   --
+   --      * RTSfind - The compiler generates code which references entities
+   --        from the runtime.
 
    --  Import_Interface_Present (Flag16-Sem)
-   --     This flag is set in an Interface or Import pragma if a matching
-   --     pragma of the other kind is also present. This is used to avoid
-   --     generating some unwanted error messages.
+   --    This flag is set in an Interface or Import pragma if a matching
+   --    pragma of the other kind is also present. This is used to avoid
+   --    generating some unwanted error messages.
 
    --  Includes_Infinities (Flag11-Sem)
    --    This flag is present in N_Range nodes. It is set for the range of
@@ -1709,7 +1730,7 @@
    --    If this flag is set, the aspect or policy is not analyzed for semantic
    --    correctness, so any expressions etc will not be marked as analyzed.
 
-   --  Is_Dispatching_Call (Flag3-Sem)
+   --  Is_Dispatching_Call (Flag6-Sem)
    --    Present in call marker nodes. Set when the related call which prompted
    --    the creation of the marker is dispatching.
 
@@ -1717,21 +1738,55 @@
    --    Present in allocator nodes, to indicate that this is an allocator
    --    for an access discriminant of a dynamically allocated object. The
    --    coextension must be deallocated and finalized at the same time as
-   --    the enclosing object.
+   --    the enclosing object. The partner flag Is_Static_Coextension must
+   --    be cleared before setting this flag to True.
 
    --  Is_Effective_Use_Clause (Flag1-Sem)
    --    Present in both N_Use_Type_Clause and N_Use_Package_Clause to indicate
    --    a use clause is "used" in the current source.
 
    --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
-   --    Present in nodes which represent an elaboration scenario. Those are
-   --    assignment statement, attribute reference, call marker, entry call
-   --    statement, expanded name, function call, identifier, instantiation,
-   --    procedure call statement, and requeue statement nodes. Set when the
-   --    node appears within a context which allows for the generation of
-   --    run-time ABE checks. This flag detemines whether the ABE Processing
+   --    Present in the following nodes:
+   --
+   --      assignment statement
+   --      attribute reference
+   --      call marker
+   --      entry call statement
+   --      expanded name
+   --      function call
+   --      function instantiation
+   --      identifier
+   --      package instantiation
+   --      procedure call statement
+   --      procedure instantiation
+   --      requeue statement
+   --
+   --    Set when the node appears within a context which allows the generation
+   --    of run-time ABE checks. This flag detemines whether the ABE Processing
    --    phase generates conditional ABE checks and guaranteed ABE failures.
 
+   --  Is_Elaboration_Code (Flag9-Sem)
+   --    Present in assignment statements. Set for an assignment which updates
+   --    the elaboration flag of a package or subprogram when the corresponding
+   --    body is successfully elaborated.
+
+   --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
+   --    Present in the following nodes:
+   --
+   --      attribute reference
+   --      call marker
+   --      entry call statement
+   --      function call
+   --      function instantiation
+   --      package instantiation
+   --      procedure call statement
+   --      procedure instantiation
+   --      requeue statement
+   --
+   --    Set when the node appears within a context where elaboration warnings
+   --    are enabled. This flag determines whether the ABE processing phase
+   --    generates diagnostics on various elaboration issues.
+
    --  Is_Entry_Barrier_Function (Flag8-Sem)
    --    This flag is set on N_Subprogram_Declaration and N_Subprogram_Body
    --    nodes which emulate the barrier function of a protected entry body.
@@ -1754,7 +1809,7 @@
 
    --  Is_Generic_Contract_Pragma (Flag2-Sem)
    --    This flag is present in N_Pragma nodes. It is set when the pragma is
-   --    a source construct, applies to a generic unit or its body and denotes
+   --    a source construct, applies to a generic unit or its body, and denotes
    --    one of the following contract-related annotations:
    --      Abstract_State
    --      Contract_Cases
@@ -1812,11 +1867,24 @@
    --    finalization actions in initialization contexts.
 
    --  Is_Known_Guaranteed_ABE (Flag18-Sem)
-   --    Present in call markers and instantiations. Set when the elaboration
-   --    or evaluation of the scenario results in a guaranteed ABE. The flag
-   --    is used to suppress the instantiation of generic bodies because gigi
-   --    cannot handle certain forms of premature instantiation, as well as to
-   --    prevent the reexamination of the node by the ABE Processing phase.
+   --    NOTE: this flag is shared between the legacy ABE mechanism and the
+   --    default ABE mechanism.
+   --
+   --    Present in the following nodes:
+   --
+   --      call marker
+   --      formal package declaration
+   --      function call
+   --      function instantiation
+   --      package instantiation
+   --      procedure call statement
+   --      procedure instantiation
+   --
+   --    Set when the elaboration or evaluation of the scenario results in
+   --    a guaranteed ABE. The flag is used to suppress the instantiation of
+   --    generic bodies because gigi cannot handle certain forms of premature
+   --    instantiation, as well as to prevent the reexamination of the node by
+   --    the ABE Processing phase.
 
    --  Is_Machine_Number (Flag11-Sem)
    --    This flag is set in an N_Real_Literal node to indicate that the value
@@ -1828,6 +1896,14 @@
    --    can be determined to be null at compile time. This is used to remove
    --    the loop entirely at expansion time.
 
+   --  Is_OpenAcc_Environment (Flag13-Sem)
+   --    This flag is set in an N_Loop_Statement node if it contains an
+   --    Acc_Data, Acc_Parallel or Add_Kernels pragma.
+
+   --  Is_OpenAcc_Loop (Flag14-Sem)
+   --    This flag is set in an N_Loop_Statement node if it contains an
+   --    OpenAcc_Loop pragma.
+
    --  Is_Overloaded (Flag5-Sem)
    --    A flag present in all expression nodes. Used temporarily during
    --    overloading determination. The setting of this flag is not relevant
@@ -1863,11 +1939,9 @@
    --    the resolution of accidental overloading of binary or unary operators
    --    which may occur in instances.
 
-   --  Is_Recorded_Scenario (Flag6-Sem)
-   --    Present in call marker and instantiation nodes. Set when the scenario
-   --    was saved by the ABE Recording phase. This flag aids the ABE machinery
-   --    to keep its internal data up-to-date in case the node is transformed
-   --    by Atree.Rewrite.
+   --  Is_Read (Flag1-Sem)
+   --    Present in variable reference markers. Set when the original variable
+   --    reference constitues a read of the variable.
 
    --  Is_Source_Call (Flag4-Sem)
    --    Present in call marker nodes. Set when the related call came from
@@ -1884,7 +1958,9 @@
 
    --  Is_Static_Coextension (Flag14-Sem)
    --    Present in N_Allocator nodes. Set if the allocator is a coextension
-   --    of an object allocated on the stack rather than the heap.
+   --    of an object allocated on the stack rather than the heap. The partner
+   --    flag Is_Dynamic_Coextension must be cleared before setting this flag
+   --    to True.
 
    --  Is_Static_Expression (Flag6-Sem)
    --    Indicates that an expression is a static expression according to the
@@ -1912,10 +1988,14 @@
    --    nodes which emulate the body of a task unit.
 
    --  Is_Task_Master (Flag5-Sem)
-   --    A flag set in a Subprogram_Body, Block_Statement or Task_Body node to
+   --    A flag set in a Subprogram_Body, Block_Statement, or Task_Body node to
    --    indicate that the construct is a task master (i.e. has declared tasks
    --    or declares an access to a task type).
 
+   --  Is_Write (Flag2-Sem)
+   --    Present in variable reference markers. Set when the original variable
+   --    reference constitues a write of the variable.
+
    --  Itype (Node1-Sem)
    --    Used in N_Itype_Reference node to reference an itype for which it is
    --    important to ensure that it is defined. See description of this node
@@ -2017,7 +2097,7 @@
    --    calls to Freeze_Expression.
 
    --  Next_Entity (Node2-Sem)
-   --    Present in defining identifiers, defining character literals and
+   --    Present in defining identifiers, defining character literals, and
    --    defining operator symbols (i.e. in all entities). The entities of a
    --    scope are chained, and this field is used as the forward pointer for
    --    this list. See Einfo for further details.
@@ -2083,6 +2163,16 @@
    --    expansions where the generated assignments are initializations, not
    --    real assignments.
 
+   --  No_Elaboration_Check (Flag4-Sem)
+   --    NOTE: this flag is relevant only for the legacy ABE mechanism and
+   --    should not be used outside of that context.
+   --
+   --    Present in N_Function_Call and N_Procedure_Call_Statement. Indicates
+   --    that no elaboration check is needed on the call, because it appears in
+   --    the context of a local Suppress pragma. This is used on calls within
+   --    task bodies, where the actual elaboration checks are applied after
+   --    analysis, when the local scope stack is not present
+
    --  No_Entities_Ref_In_Spec (Flag8-Sem)
    --    Present in N_With_Clause nodes. Set if the with clause is on the
    --    package or subprogram spec where the main unit is the corresponding
@@ -2160,6 +2250,12 @@
    --    package specification. This field is Empty for library bodies (the
    --    parent spec in this case can be found from the corresponding spec).
 
+   --  Parent_With (Flag1-Sem)
+   --    Present in N_With_Clause nodes. The flag indicates that the clause
+   --    was generated for an ancestor unit to provide proper visibility. A
+   --    with clause for child unit A.B.C produces two implicit parent with
+   --    clauses for A and A.B.
+
    --  Premature_Use (Node5-Sem)
    --    Present in N_Incomplete_Type_Declaration node. Used for improved
    --    error diagnostics: if there is a premature usage of an incomplete
@@ -2234,7 +2330,7 @@
    --    because Analyze wants to insert extra actions on this list.
 
    --  Rounded_Result (Flag18-Sem)
-   --    Present in N_Type_Conversion, N_Op_Divide and N_Op_Multiply nodes.
+   --    Present in N_Type_Conversion, N_Op_Divide, and N_Op_Multiply nodes.
    --    Used in the fixed-point cases to indicate that the result must be
    --    rounded as a result of the use of the 'Round attribute. Also used for
    --    integer N_Op_Divide nodes to indicate that the result should be
@@ -2267,7 +2363,7 @@
    --    operation named (statically) in a dispatching call.
 
    --  Scope (Node3-Sem)
-   --    Present in defining identifiers, defining character literals and
+   --    Present in defining identifiers, defining character literals, and
    --    defining operator symbols (i.e. in all entities). The entities of a
    --    scope all use this field to reference the corresponding scope entity.
    --    See Einfo for further details.
@@ -2286,7 +2382,7 @@
 
    --  Split_PPC (Flag17)
    --    When a Pre or Post aspect specification is processed, it is broken
-   --    into AND THEN sections. The left most section has Split_PPC set to
+   --    into AND THEN sections. The leftmost section has Split_PPC set to
    --    False, indicating that it is the original specification (e.g. for
    --    posting errors). For other sections, Split_PPC is set to True.
    --    This flag is set in both the N_Aspect_Specification node itself,
@@ -2318,8 +2414,9 @@
    --    only execute if invalid values are present).
 
    --  Target (Node1-Sem)
-   --    Present in call marker nodes. References the entity of the entry,
-   --    operator, or subprogram invoked by the related call or requeue.
+   --    Present in call and variable reference marker nodes. References the
+   --    entity of the original entity, operator, or subprogram being invoked,
+   --    or the original variable being read or written.
 
    --  Target_Type (Node2-Sem)
    --    Used in an N_Validate_Unchecked_Conversion node to point to the target
@@ -2338,7 +2435,7 @@
    --    always set to No_List.
 
    --  Treat_Fixed_As_Integer (Flag14-Sem)
-   --    This flag appears in operator nodes for divide, multiply, mod and rem
+   --    This flag appears in operator nodes for divide, multiply, mod, and rem
    --    on fixed-point operands. It indicates that the operands are to be
    --    treated as integer values, ignoring small values. This flag is only
    --    set as a result of expansion of fixed-point operations. Typically a
@@ -2415,12 +2512,6 @@
    --    Original_Node here because of the case of nested instantiations where
    --    the substituted node can be copied.
 
-   --  Withed_Body (Node1-Sem)
-   --    Present in N_With_Clause nodes. Set if the unit in whose context
-   --    the with_clause appears instantiates a generic contained in the
-   --    library unit of the with_clause and as a result loads its body.
-   --    Used for a more precise unit traversal for CodePeer.
-
    --------------------------------------------------
    -- Note on Use of End_Label and End_Span Fields --
    --------------------------------------------------
@@ -2728,7 +2819,7 @@
       --  pain to allow these aspects to pervade the pragma syntax, and the
       --  representation of pragma nodes internally. So what we do is to
       --  replace these ASPECT_MARK forms with identifiers whose name is one
-      --  of the special internal names _Pre, _Post or _Type_Invariant.
+      --  of the special internal names _Pre, _Post, or _Type_Invariant.
 
       --  We do a similar replacement of these Aspect_Mark forms in the
       --  Expression of a pragma argument association for the cases of
@@ -2777,7 +2868,7 @@
       --  Einfo.
 
       --  Note: N_Defining_Identifier is an extended node whose fields are
-      --  deliberate layed out to match the layout of fields in an ordinary
+      --  deliberately layed out to match the layout of fields in an ordinary
       --  N_Identifier node allowing for easy alteration of an identifier
       --  node into a defining identifier node. For details, see procedure
       --  Sinfo.CN.Change_Identifier_To_Defining_Identifier.
@@ -3025,8 +3116,8 @@
       --    [abstract] [limited] new [NULL_EXCLUSION] parent_SUBTYPE_INDICATION
       --    [[and INTERFACE_LIST] RECORD_EXTENSION_PART]
 
-      --  Note: ABSTRACT, LIMITED and record extension part are not permitted
-      --  in Ada 83 mode
+      --  Note: ABSTRACT, LIMITED, and record extension part are not permitted
+      --  in Ada 83 mode.
 
       --  Note: a record extension part is required if ABSTRACT is present
 
@@ -3337,7 +3428,7 @@
       --  Subtype_Indication field or else the Access_Definition field.
 
       --  N_Component_Definition
-      --  Sloc points to ALIASED, ACCESS or to first token of subtype mark
+      --  Sloc points to ALIASED, ACCESS, or to first token of subtype mark
       --  Aliased_Present (Flag4)
       --  Null_Exclusion_Present (Flag11)
       --  Subtype_Indication (Node5) (set to Empty if not present)
@@ -3485,7 +3576,7 @@
       --    end record
       --  | null record
 
-      --  Note: the Abstract_Present, Tagged_Present and Limited_Present
+      --  Note: the Abstract_Present, Tagged_Present, and Limited_Present
       --  flags appear only for a record definition appearing in a record
       --  type definition.
 
@@ -3993,6 +4084,7 @@
       --  Associated_Node (Node4-Sem)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
       --  Header_Size_Added (Flag11-Sem)
       --  Redundant_Use (Flag13-Sem)
       --  Must_Be_Byte_Aligned (Flag14-Sem)
@@ -4013,7 +4105,7 @@
       --  Instead the Attribute_Name and Expressions fields of the parent
       --  node (N_Attribute_Reference node) hold the information.
 
-      --  Note: if ACCESS, DELTA or DIGITS appears in an attribute
+      --  Note: if ACCESS, DELTA, or DIGITS appears in an attribute
       --  designator, then they are treated as identifiers internally
       --  rather than the keywords of the same name.
 
@@ -4065,7 +4157,7 @@
       --  makes no attempt to enforce consistency here, so it is up to the
       --  semantic phase to make sure that the aggregate is consistent (i.e.
       --  that it is not a "half-and-half" case that mixes record and array
-      --  syntax. In particular, for a record aggregate, the expressions
+      --  syntax). In particular, for a record aggregate, the expressions
       --  field will be set if there are positional associations.
 
       --  Note: N_Aggregate is not used for all aggregates; in particular,
@@ -4590,7 +4682,7 @@
 
       --------------------------
       -- 4.5.7  If Expression --
-      ----------------------------
+      --------------------------
 
       --  IF_EXPRESSION ::=
       --    if CONDITION then DEPENDENT_EXPRESSION
@@ -4672,7 +4764,7 @@
       --  since the expander converts case expressions into case statements.
 
       ---------------------------------
-      -- 4.5.9 Quantified Expression --
+      -- 4.5.8 Quantified Expression --
       ---------------------------------
 
       --  QUANTIFIED_EXPRESSION ::=
@@ -4897,6 +4989,7 @@
       --  Backwards_OK (Flag6-Sem)
       --  No_Ctrl_Actions (Flag7-Sem)
       --  Has_Target_Names (Flag8-Sem)
+      --  Is_Elaboration_Code (Flag9-Sem)
       --  Do_Tag_Check (Flag13-Sem)
       --  Componentwise_Assignment (Flag14-Sem)
       --  Suppress_Assignment_Checks (Flag18-Sem)
@@ -5041,6 +5134,8 @@
       --  Iteration_Scheme (Node2) (set to Empty if no iteration scheme)
       --  Statements (List3)
       --  End_Label (Node4)
+      --  Is_OpenAcc_Environment (Flag13-Sem)
+      --  Is_OpenAcc_Loop (Flag14-Sem)
       --  Has_Created_Identifier (Flag15)
       --  Is_Null_Loop (Flag16)
       --  Suppress_Loop_Warnings (Flag17)
@@ -5478,7 +5573,10 @@
       --  Controlling_Argument (Node1-Sem) (set to Empty if not dispatching)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
+      --  No_Elaboration_Check (Flag4-Sem)
       --  Do_Tag_Check (Flag13-Sem)
+      --  Is_Known_Guaranteed_ABE (Flag18-Sem)
       --  plus fields for expression
 
       --  If any IN parameter requires a range check, then the corresponding
@@ -5508,9 +5606,12 @@
       --  Controlling_Argument (Node1-Sem) (set to Empty if not dispatching)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
+      --  No_Elaboration_Check (Flag4-Sem)
       --  Is_Expanded_Build_In_Place_Call (Flag11-Sem)
       --  Do_Tag_Check (Flag13-Sem)
       --  No_Side_Effect_Removal (Flag17-Sem)
+      --  Is_Known_Guaranteed_ABE (Flag18-Sem)
       --  plus fields for expression
 
       --------------------------------
@@ -5543,7 +5644,8 @@
       -- 6.4  Actual Parameter --
       ---------------------------
 
-      --  EXPLICIT_ACTUAL_PARAMETER ::= EXPRESSION | variable_NAME
+      --  EXPLICIT_ACTUAL_PARAMETER ::=
+      --    EXPRESSION | variable_NAME | REDUCTION_EXPRESSION_PARAMETER
 
       ---------------------------
       -- 6.5  Return Statement --
@@ -6221,6 +6323,7 @@
       --  First_Named_Actual (Node4-Sem)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
 
       ------------------------------
       -- 9.5.4  Requeue Statement --
@@ -6238,6 +6341,7 @@
       --  Abort_Present (Flag15)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
 
       --------------------------
       -- 9.6  Delay Statement --
@@ -6643,8 +6747,9 @@
 
       --  N_With_Clause
       --  Sloc points to first token of library unit name
-      --  Withed_Body (Node1-Sem)
       --  Name (Node2)
+      --  Private_Present (Flag15) set if with_clause has private keyword
+      --  Limited_Present (Flag17) set if LIMITED is present
       --  Next_Implicit_With (Node3-Sem)
       --  Library_Unit (Node4-Sem)
       --  Corresponding_Spec (Node5-Sem)
@@ -6655,11 +6760,9 @@
       --  Elaborate_All_Present (Flag14-Sem)
       --  Elaborate_All_Desirable (Flag9-Sem)
       --  Elaborate_Desirable (Flag11-Sem)
-      --  Private_Present (Flag15) set if with_clause has private keyword
       --  Implicit_With (Flag16-Sem)
-      --  Implicit_With_From_Instantiation (Flag12-Sem)
-      --  Limited_Present (Flag17) set if LIMITED is present
       --  Limited_View_Installed (Flag18-Sem)
+      --  Parent_With (Flag1-Sem)
       --  Unreferenced_In_Spec (Flag7-Sem)
       --  No_Entities_Ref_In_Spec (Flag8-Sem)
 
@@ -7035,8 +7138,8 @@
       --  Instance_Spec (Node5-Sem)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
       --  Is_Declaration_Level_Node (Flag5-Sem)
-      --  Is_Recorded_Scenario (Flag6-Sem)
       --  Is_Known_Guaranteed_ABE (Flag18-Sem)
 
       --  N_Procedure_Instantiation
@@ -7049,8 +7152,8 @@
       --  Instance_Spec (Node5-Sem)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
       --  Is_Declaration_Level_Node (Flag5-Sem)
-      --  Is_Recorded_Scenario (Flag6-Sem)
       --  Must_Override (Flag14) set if overriding indicator present
       --  Must_Not_Override (Flag15) set if not_overriding indicator present
       --  Is_Known_Guaranteed_ABE (Flag18-Sem)
@@ -7065,8 +7168,8 @@
       --  Instance_Spec (Node5-Sem)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
       --  Is_Declaration_Level_Node (Flag5-Sem)
-      --  Is_Recorded_Scenario (Flag6-Sem)
       --  Must_Override (Flag14) set if overriding indicator present
       --  Must_Not_Override (Flag15) set if not_overriding indicator present
       --  Is_Known_Guaranteed_ABE (Flag18-Sem)
@@ -7382,6 +7485,7 @@
       --   empty generic actual part)
       --  Box_Present (Flag15)
       --  Instance_Spec (Node5-Sem)
+      --  Is_Known_Guaranteed_ABE (Flag18-Sem)
 
       --------------------------------------
       -- 12.7  Formal Package Actual Part --
@@ -7821,10 +7925,10 @@
       --  Target (Node1-Sem)
       --  Is_Elaboration_Checks_OK_Node (Flag1-Sem)
       --  Is_SPARK_Mode_On_Node (Flag2-Sem)
-      --  Is_Dispatching_Call (Flag3-Sem)
+      --  Is_Elaboration_Warnings_OK_Node (Flag3-Sem)
       --  Is_Source_Call (Flag4-Sem)
       --  Is_Declaration_Level_Node (Flag5-Sem)
-      --  Is_Recorded_Scenario (Flag6-Sem)
+      --  Is_Dispatching_Call (Flag6-Sem)
       --  Is_Known_Guaranteed_ABE (Flag18-Sem)
 
       ------------------------
@@ -7911,7 +8015,7 @@
       --  to aspects/pragmas Contract_Cases and Test_Case. The ordering in the
       --  list is in LIFO fashion.
 
-      --  Classifications contains pragmas that either declare, categorize or
+      --  Classifications contains pragmas that either declare, categorize, or
       --  establish dependencies between subprogram or package inputs and
       --  outputs. Currently the following pragmas appear in this list:
       --    Abstract_States
@@ -8455,6 +8559,37 @@
       --  Note: in the case where a debug source file is generated, the Sloc
       --  for this node points to the VALIDATE keyword in the file output.
 
+      -------------------------------
+      -- Variable_Reference_Marker --
+      -------------------------------
+
+      --  This node is created during the analysis of direct or expanded names,
+      --  and the resolution of entry and subprogram calls. It performs several
+      --  functions:
+
+      --    * Variable reference markers provide a uniform model for handling
+      --      variable references by the ABE mechanism, regardless of whether
+      --      expansion took place.
+
+      --    * The variable reference marker captures the entity of the variable
+      --      being read or written.
+
+      --    * The variable reference markers aid the ABE Processing phase by
+      --      signaling the presence of a call in case the original variable
+      --      reference was transformed by expansion.
+
+      --  Sprint syntax:  r#target#  --  for a read
+      --                 rw#target#  --  for a read/write
+      --                  w#target#  --  for a write
+
+      --  The Sprint syntax shown above is not enabled by default
+
+      --  N_Variable_Reference_Marker
+      --  Sloc points to Sloc of original variable reference
+      --  Target (Node1-Sem)
+      --  Is_Read (Flag1-Sem)
+      --  Is_Write (Flag2-Sem)
+
    -----------
    -- Empty --
    -----------
@@ -8877,6 +9012,7 @@
       N_Triggering_Alternative,
       N_Use_Type_Clause,
       N_Validate_Unchecked_Conversion,
+      N_Variable_Reference_Marker,
       N_Variant,
       N_Variant_Part,
       N_With_Clause,
@@ -9598,9 +9734,6 @@
    function Implicit_With
      (N : Node_Id) return Boolean;    -- Flag16
 
-   function Implicit_With_From_Instantiation
-     (N : Node_Id) return Boolean;    -- Flag12
-
    function Import_Interface_Present
      (N : Node_Id) return Boolean;    -- Flag16
 
@@ -9662,7 +9795,7 @@
      (N : Node_Id) return Boolean;    -- Flag15
 
    function Is_Dispatching_Call
-     (N : Node_Id) return Boolean;    -- Flag3
+     (N : Node_Id) return Boolean;    -- Flag6
 
    function Is_Dynamic_Coextension
      (N : Node_Id) return Boolean;    -- Flag18
@@ -9673,6 +9806,12 @@
    function Is_Elaboration_Checks_OK_Node
      (N : Node_Id) return Boolean;    -- Flag1
 
+   function Is_Elaboration_Code
+     (N : Node_Id) return Boolean;    -- Flag9
+
+   function Is_Elaboration_Warnings_OK_Node
+     (N : Node_Id) return Boolean;    -- Flag3
+
    function Is_Elsif
      (N : Node_Id) return Boolean;    -- Flag13
 
@@ -9718,6 +9857,12 @@
    function Is_Null_Loop
      (N : Node_Id) return Boolean;    -- Flag16
 
+   function Is_OpenAcc_Environment
+     (N : Node_Id) return Boolean;    -- Flag13
+
+   function Is_OpenAcc_Loop
+     (N : Node_Id) return Boolean;    -- Flag14
+
    function Is_Overloaded
      (N : Node_Id) return Boolean;    -- Flag5
 
@@ -9733,8 +9878,8 @@
    function Is_Qualified_Universal_Literal
      (N : Node_Id) return Boolean;    -- Flag4
 
-   function Is_Recorded_Scenario
-     (N : Node_Id) return Boolean;    -- Flag6
+   function Is_Read
+     (N : Node_Id) return Boolean;    -- Flag1
 
    function Is_Source_Call
      (N : Node_Id) return Boolean;    -- Flag4
@@ -9760,6 +9905,9 @@
    function Is_Task_Master
      (N : Node_Id) return Boolean;    -- Flag5
 
+   function Is_Write
+     (N : Node_Id) return Boolean;    -- Flag2
+
    function Iteration_Scheme
      (N : Node_Id) return Node_Id;    -- Node2
 
@@ -9859,6 +10007,9 @@
    function No_Ctrl_Actions
      (N : Node_Id) return Boolean;    -- Flag7
 
+   function No_Elaboration_Check
+     (N : Node_Id) return Boolean;    -- Flag4
+
    function No_Entities_Ref_In_Spec
      (N : Node_Id) return Boolean;    -- Flag8
 
@@ -9922,6 +10073,9 @@
    function Parent_Spec
      (N : Node_Id) return Node_Id;    -- Node4
 
+   function Parent_With
+     (N : Node_Id) return Boolean;    -- Flag1
+
    function Position
      (N : Node_Id) return Node_Id;    -- Node2
 
@@ -10162,9 +10316,6 @@
    function Was_Originally_Stub
      (N : Node_Id) return Boolean;    -- Flag13
 
-   function Withed_Body
-     (N : Node_Id) return Node_Id;    -- Node1
-
    --  End functions (note used by xsinfo utility program to end processing)
 
    ----------------------------
@@ -10687,9 +10838,6 @@
    procedure Set_Implicit_With
      (N : Node_Id; Val : Boolean := True);    -- Flag16
 
-   procedure Set_Implicit_With_From_Instantiation
-     (N : Node_Id; Val : Boolean := True);    -- Flag12
-
    procedure Set_Import_Interface_Present
      (N : Node_Id; Val : Boolean := True);    -- Flag16
 
@@ -10751,7 +10899,7 @@
      (N : Node_Id; Val : Boolean := True);    -- Flag15
 
    procedure Set_Is_Dispatching_Call
-     (N : Node_Id; Val : Boolean := True);    -- Flag3
+     (N : Node_Id; Val : Boolean := True);    -- Flag6
 
    procedure Set_Is_Dynamic_Coextension
      (N : Node_Id; Val : Boolean := True);    -- Flag18
@@ -10762,6 +10910,12 @@
    procedure Set_Is_Elaboration_Checks_OK_Node
      (N : Node_Id; Val : Boolean := True);    -- Flag1
 
+   procedure Set_Is_Elaboration_Code
+     (N : Node_Id; Val : Boolean := True);    -- Flag9
+
+   procedure Set_Is_Elaboration_Warnings_OK_Node
+     (N : Node_Id; Val : Boolean := True);    -- Flag3
+
    procedure Set_Is_Elsif
      (N : Node_Id; Val : Boolean := True);    -- Flag13
 
@@ -10807,6 +10961,12 @@
    procedure Set_Is_Null_Loop
      (N : Node_Id; Val : Boolean := True);    -- Flag16
 
+   procedure Set_Is_OpenAcc_Environment
+     (N : Node_Id; Val : Boolean := True);    -- Flag13
+
+   procedure Set_Is_OpenAcc_Loop
+     (N : Node_Id; Val : Boolean := True);    -- Flag14
+
    procedure Set_Is_Overloaded
      (N : Node_Id; Val : Boolean := True);    -- Flag5
 
@@ -10822,8 +10982,8 @@
    procedure Set_Is_Qualified_Universal_Literal
      (N : Node_Id; Val : Boolean := True);    -- Flag4
 
-   procedure Set_Is_Recorded_Scenario
-     (N : Node_Id; Val : Boolean := True);    -- Flag6
+   procedure Set_Is_Read
+     (N : Node_Id; Val : Boolean := True);    -- Flag1
 
    procedure Set_Is_Source_Call
      (N : Node_Id; Val : Boolean := True);    -- Flag4
@@ -10849,6 +11009,9 @@
    procedure Set_Is_Task_Master
      (N : Node_Id; Val : Boolean := True);    -- Flag5
 
+   procedure Set_Is_Write
+     (N : Node_Id; Val : Boolean := True);    -- Flag2
+
    procedure Set_Iteration_Scheme
      (N : Node_Id; Val : Node_Id);            -- Node2
 
@@ -10948,6 +11111,9 @@
    procedure Set_No_Ctrl_Actions
      (N : Node_Id; Val : Boolean := True);    -- Flag7
 
+   procedure Set_No_Elaboration_Check
+     (N : Node_Id; Val : Boolean := True);    -- Flag4
+
    procedure Set_No_Entities_Ref_In_Spec
      (N : Node_Id; Val : Boolean := True);    -- Flag8
 
@@ -11011,6 +11177,9 @@
    procedure Set_Parent_Spec
      (N : Node_Id; Val : Node_Id);            -- Node4
 
+   procedure Set_Parent_With
+     (N : Node_Id; Val : Boolean := True);    -- Flag1
+
    procedure Set_Position
      (N : Node_Id; Val : Node_Id);            -- Node2
 
@@ -11251,9 +11420,6 @@
    procedure Set_Was_Originally_Stub
      (N : Node_Id; Val : Boolean := True);    -- Flag13
 
-   procedure Set_Withed_Body
-     (N : Node_Id; Val : Node_Id);            -- Node1
-
    -------------------------
    -- Iterator Procedures --
    -------------------------
@@ -11363,6 +11529,33 @@
       V8 : Node_Kind;
       V9 : Node_Kind) return Boolean;
 
+   function Nkind_In
+     (T   : Node_Kind;
+      V1  : Node_Kind;
+      V2  : Node_Kind;
+      V3  : Node_Kind;
+      V4  : Node_Kind;
+      V5  : Node_Kind;
+      V6  : Node_Kind;
+      V7  : Node_Kind;
+      V8  : Node_Kind;
+      V9  : Node_Kind;
+      V10 : Node_Kind) return Boolean;
+
+   function Nkind_In
+     (T   : Node_Kind;
+      V1  : Node_Kind;
+      V2  : Node_Kind;
+      V3  : Node_Kind;
+      V4  : Node_Kind;
+      V5  : Node_Kind;
+      V6  : Node_Kind;
+      V7  : Node_Kind;
+      V8  : Node_Kind;
+      V9  : Node_Kind;
+      V10 : Node_Kind;
+      V11 : Node_Kind) return Boolean;
+
    pragma Inline (Nkind_In);
    --  Inline all above functions
 
@@ -11755,7 +11948,7 @@
         5 => False),  --  unused
 
      N_Delta_Aggregate =>
-       (1 => False,   --  Expressions (List1)
+       (1 => False,   --  Expressions (List1-Sem)
         2 => True,    --  Component_Associations (List2)
         3 => True,    --  Expression (Node3)
         4 => False,   --  Unused
@@ -11966,7 +12159,7 @@
 
      N_Quantified_Expression =>
        (1 => True,    --  Condition (Node1)
-        2 => True,    --  Iterator_Specification
+        2 => True,    --  Iterator_Specification (Node2)
         3 => False,   --  unused
         4 => True,    --  Loop_Parameter_Specification (Node4)
         5 => False),  --  Etype (Node5-Sem)
@@ -13023,7 +13216,14 @@
         4 => False,   --  unused
         5 => False),  --  unused
 
-   --  Entries for Empty, Error and Unused. Even thought these have a Chars
+     N_Variable_Reference_Marker =>
+       (1 => False,   --  Target (Node1-Sem)
+        2 => False,   --  unused
+        3 => False,   --  unused
+        4 => False,   --  unused
+        5 => False),  --  unused
+
+   --  Entries for Empty, Error, and Unused. Even though these have a Chars
    --  field for debugging purposes, they are not really syntactic fields, so
    --  we mark all fields as unused.
 
@@ -13228,7 +13428,6 @@
    pragma Inline (High_Bound);
    pragma Inline (Identifier);
    pragma Inline (Implicit_With);
-   pragma Inline (Implicit_With_From_Instantiation);
    pragma Inline (Interface_List);
    pragma Inline (Interface_Present);
    pragma Inline (Includes_Infinities);
@@ -13256,6 +13455,8 @@
    pragma Inline (Is_Dynamic_Coextension);
    pragma Inline (Is_Effective_Use_Clause);
    pragma Inline (Is_Elaboration_Checks_OK_Node);
+   pragma Inline (Is_Elaboration_Code);
+   pragma Inline (Is_Elaboration_Warnings_OK_Node);
    pragma Inline (Is_Elsif);
    pragma Inline (Is_Entry_Barrier_Function);
    pragma Inline (Is_Expanded_Build_In_Place_Call);
@@ -13271,12 +13472,14 @@
    pragma Inline (Is_Known_Guaranteed_ABE);
    pragma Inline (Is_Machine_Number);
    pragma Inline (Is_Null_Loop);
+   pragma Inline (Is_OpenAcc_Environment);
+   pragma Inline (Is_OpenAcc_Loop);
    pragma Inline (Is_Overloaded);
    pragma Inline (Is_Power_Of_2_For_Shift);
    pragma Inline (Is_Prefixed_Call);
    pragma Inline (Is_Protected_Subprogram_Body);
    pragma Inline (Is_Qualified_Universal_Literal);
-   pragma Inline (Is_Recorded_Scenario);
+   pragma Inline (Is_Read);
    pragma Inline (Is_Source_Call);
    pragma Inline (Is_SPARK_Mode_On_Node);
    pragma Inline (Is_Static_Coextension);
@@ -13285,6 +13488,7 @@
    pragma Inline (Is_Task_Allocation_Block);
    pragma Inline (Is_Task_Body_Procedure);
    pragma Inline (Is_Task_Master);
+   pragma Inline (Is_Write);
    pragma Inline (Iteration_Scheme);
    pragma Inline (Itype);
    pragma Inline (Kill_Range_Check);
@@ -13317,6 +13521,7 @@
    pragma Inline (Next_Rep_Item);
    pragma Inline (Next_Use_Clause);
    pragma Inline (No_Ctrl_Actions);
+   pragma Inline (No_Elaboration_Check);
    pragma Inline (No_Entities_Ref_In_Spec);
    pragma Inline (No_Initialization);
    pragma Inline (No_Minimize_Eliminate);
@@ -13338,6 +13543,7 @@
    pragma Inline (Parameter_Specifications);
    pragma Inline (Parameter_Type);
    pragma Inline (Parent_Spec);
+   pragma Inline (Parent_With);
    pragma Inline (Position);
    pragma Inline (Pragma_Argument_Associations);
    pragma Inline (Pragma_Identifier);
@@ -13418,7 +13624,6 @@
    pragma Inline (Was_Attribute_Reference);
    pragma Inline (Was_Expression_Function);
    pragma Inline (Was_Originally_Stub);
-   pragma Inline (Withed_Body);
 
    pragma Inline (Set_Abort_Present);
    pragma Inline (Set_Abortable_Part);
@@ -13614,6 +13819,8 @@
    pragma Inline (Set_Is_Dynamic_Coextension);
    pragma Inline (Set_Is_Effective_Use_Clause);
    pragma Inline (Set_Is_Elaboration_Checks_OK_Node);
+   pragma Inline (Set_Is_Elaboration_Code);
+   pragma Inline (Set_Is_Elaboration_Warnings_OK_Node);
    pragma Inline (Set_Is_Elsif);
    pragma Inline (Set_Is_Entry_Barrier_Function);
    pragma Inline (Set_Is_Expanded_Build_In_Place_Call);
@@ -13629,12 +13836,14 @@
    pragma Inline (Set_Is_Known_Guaranteed_ABE);
    pragma Inline (Set_Is_Machine_Number);
    pragma Inline (Set_Is_Null_Loop);
+   pragma Inline (Set_Is_OpenAcc_Environment);
+   pragma Inline (Set_Is_OpenAcc_Loop);
    pragma Inline (Set_Is_Overloaded);
    pragma Inline (Set_Is_Power_Of_2_For_Shift);
    pragma Inline (Set_Is_Prefixed_Call);
    pragma Inline (Set_Is_Protected_Subprogram_Body);
    pragma Inline (Set_Is_Qualified_Universal_Literal);
-   pragma Inline (Set_Is_Recorded_Scenario);
+   pragma Inline (Set_Is_Read);
    pragma Inline (Set_Is_Source_Call);
    pragma Inline (Set_Is_SPARK_Mode_On_Node);
    pragma Inline (Set_Is_Static_Coextension);
@@ -13643,6 +13852,7 @@
    pragma Inline (Set_Is_Task_Allocation_Block);
    pragma Inline (Set_Is_Task_Body_Procedure);
    pragma Inline (Set_Is_Task_Master);
+   pragma Inline (Set_Is_Write);
    pragma Inline (Set_Iteration_Scheme);
    pragma Inline (Set_Iterator_Specification);
    pragma Inline (Set_Itype);
@@ -13676,6 +13886,7 @@
    pragma Inline (Set_Next_Rep_Item);
    pragma Inline (Set_Next_Use_Clause);
    pragma Inline (Set_No_Ctrl_Actions);
+   pragma Inline (Set_No_Elaboration_Check);
    pragma Inline (Set_No_Entities_Ref_In_Spec);
    pragma Inline (Set_No_Initialization);
    pragma Inline (Set_No_Minimize_Eliminate);
@@ -13697,6 +13908,7 @@
    pragma Inline (Set_Parameter_Specifications);
    pragma Inline (Set_Parameter_Type);
    pragma Inline (Set_Parent_Spec);
+   pragma Inline (Set_Parent_With);
    pragma Inline (Set_Position);
    pragma Inline (Set_Pragma_Argument_Associations);
    pragma Inline (Set_Pragma_Identifier);
@@ -13775,6 +13987,5 @@
    pragma Inline (Set_Was_Attribute_Reference);
    pragma Inline (Set_Was_Expression_Function);
    pragma Inline (Set_Was_Originally_Stub);
-   pragma Inline (Set_Withed_Body);
 
 end Sinfo;