1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                                  S E M                                   --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2021, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26--------------------------------------
27-- Semantic Analysis: General Model --
28--------------------------------------
29
30--  Semantic processing involves 3 phases which are highly intertwined
31--  (i.e. mutually recursive):
32
33--    Analysis     implements the bulk of semantic analysis such as
34--                 name analysis and type resolution for declarations,
35--                 instructions and expressions. The main routine
36--                 driving this process is procedure Analyze given below.
37--                 This analysis phase is really a bottom up pass that is
38--                 achieved during the recursive traversal performed by the
39--                 Analyze_... procedures implemented in the sem_* packages.
40--                 For expressions this phase determines unambiguous types
41--                 and collects sets of possible types where the
42--                 interpretation is potentially ambiguous.
43
44--    Resolution   is carried out only for expressions to finish type
45--                 resolution that was initiated but not necessarily
46--                 completed during analysis (because of overloading
47--                 ambiguities). Specifically, after completing the bottom
48--                 up pass carried out during analysis for expressions, the
49--                 Resolve routine (see the spec of sem_res for more info)
50--                 is called to perform a top down resolution with
51--                 recursive calls to itself to resolve operands.
52
53--    Expansion    if we are not generating code this phase is a no-op.
54--                 Otherwise this phase expands, i.e. transforms, original
55--                 declaration, expressions or instructions into simpler
56--                 structures that can be handled by the back-end. This
57--                 phase is also in charge of generating code which is
58--                 implicit in the original source (for instance for
59--                 default initializations, controlled types, etc.)
60--                 There are two separate instances where expansion is
61--                 invoked. For declarations and instructions, expansion is
62--                 invoked just after analysis since no resolution needs
63--                 to be performed. For expressions, expansion is done just
64--                 after resolution. In both cases expansion is done from the
65--                 bottom up just before the end of Analyze for instructions
66--                 and declarations or the call to Resolve for expressions.
67--                 The main routine driving expansion is Expand.
68--                 See the spec of Expander for more details.
69
70--  To summarize, in normal code generation mode we recursively traverse the
71--  abstract syntax tree top-down performing semantic analysis bottom
72--  up. For instructions and declarations, before the call to the Analyze
73--  routine completes we perform expansion since at that point we have all
74--  semantic information needed. For expression nodes, after the call to
75--  Analyze terminates we invoke the Resolve routine to transmit top-down
76--  the type that was gathered by Analyze which will resolve possible
77--  ambiguities in the expression. Just before the call to Resolve
78--  terminates, the expression can be expanded since all the semantic
79--  information is available at that point.
80
81--  If we are not generating code then the expansion phase is a no-op
82
83--  When generating code there are a number of exceptions to the basic
84--  Analysis-Resolution-Expansion model for expressions. The most prominent
85--  examples are the handling of default expressions and aggregates.
86
87-----------------------------------------------------------------------
88-- Handling of Default and Per-Object Expressions (Spec-Expressions) --
89-----------------------------------------------------------------------
90
91--  The default expressions in component declarations and in procedure
92--  specifications (but not the ones in object declarations) are quite tricky
93--  to handle. The problem is that some processing is required at the point
94--  where the expression appears:
95
96--    visibility analysis (including user defined operators)
97--    freezing of static expressions
98
99--  but other processing must be deferred until the enclosing entity (record or
100--  procedure specification) is frozen:
101
102--    freezing of any other types in the expression expansion
103--    generation of code
104
105--  A similar situation occurs with the argument of priority and interrupt
106--  priority pragmas that appear in task and protected definition specs and
107--  other cases of per-object expressions (see RM 3.8(18)).
108
109--  Another similar case is the conditions in precondition and postcondition
110--  pragmas that appear with subprogram specifications rather than in the body.
111
112--  Collectively we call these Spec_Expressions. The routine that performs the
113--  special analysis is called Analyze_Spec_Expression.
114
115--  Expansion has to be deferred since you can't generate code for expressions
116--  that reference types that have not been frozen yet. As an example, consider
117--  the following:
118
119--      type x is delta 0.5 range -10.0 .. +10.0;
120--      ...
121--      type q is record
122--        xx : x := y * z;
123--      end record;
124
125--      for x'small use 0.25;
126
127--  The expander is in charge of dealing with fixed-point, and of course the
128--  small declaration, which is not too late, since the declaration of type q
129--  does *not* freeze type x, definitely affects the expanded code.
130
131--  Another reason that we cannot expand early is that expansion can generate
132--  range checks. These range checks need to be inserted not at the point of
133--  definition but at the point of use. The whole point here is that the value
134--  of the expression cannot be obtained at the point of declaration, only at
135--  the point of use.
136
137--  Generally our model is to combine analysis resolution and expansion, but
138--  this is the one case where this model falls down. Here is how we patch
139--  it up without causing too much distortion to our basic model.
140
141--  A flag (In_Spec_Expression) is set to show that we are in the initial
142--  occurrence of a default expression. The analyzer is then called on this
143--  expression with the switch set true. Analysis and resolution proceed almost
144--  as usual, except that Freeze_Expression will not freeze non-static
145--  expressions if this switch is set, and the call to Expand at the end of
146--  resolution is skipped. This also skips the code that normally sets the
147--  Analyzed flag to True. The result is that when we are done the tree is
148--  still marked as unanalyzed, but all types for static expressions are frozen
149--  as required, and all entities of variables have been recorded. We then turn
150--  off the switch, and later on reanalyze the expression with the switch off.
151--  The effect is that this second analysis freezes the rest of the types as
152--  required, and generates code but visibility analysis is not repeated since
153--  all the entities are marked.
154
155--  The second analysis (the one that generates code) is in the context
156--  where the code is required. For a record field default, this is in the
157--  initialization procedure for the record and for a subprogram default
158--  parameter, it is at the point the subprogram is frozen. For a priority or
159--  storage size pragma it is in the context of the Init_Proc for the task or
160--  protected object. For a pre/postcondition pragma it is in the body when
161--  code for the pragma is generated.
162
163------------------
164-- Preanalysis --
165------------------
166
167--  For certain kind of expressions, such as aggregates, we need to defer
168--  expansion of the aggregate and its inner expressions until after the whole
169--  set of expressions appearing inside the aggregate have been analyzed.
170--  Consider, for instance the following example:
171--
172--     (1 .. 100 => new Thing (Function_Call))
173--
174--  The normal Analysis-Resolution-Expansion mechanism where expansion of the
175--  children is performed before expansion of the parent does not work if the
176--  code generated for the children by the expander needs to be evaluated
177--  repeatedly (for instance in the above aggregate "new Thing (Function_Call)"
178--  needs to be called 100 times.)
179
180--  The reason this mechanism does not work is that the expanded code for the
181--  children is typically inserted above the parent and thus when the parent
182--  gets expanded no re-evaluation takes place. For instance in the case of
183--  aggregates if "new Thing (Function_Call)" is expanded before the aggregate
184--  the expanded code will be placed outside of the aggregate and when
185--  expanding the aggregate the loop from 1 to 100 will not surround the
186--  expanded code for "new Thing (Function_Call)".
187
188--  To remedy this situation we introduce a flag that signals whether we want a
189--  full analysis (i.e. expansion is enabled) or a preanalysis which performs
190--  Analysis and Resolution but no expansion.
191
192--  After the complete preanalysis of an expression has been carried out we
193--  can transform the expression and then carry out the full three stage
194--  (Analyze-Resolve-Expand) cycle on the transformed expression top-down so
195--  that the expansion of inner expressions happens inside the newly generated
196--  node for the parent expression.
197
198--  Note that the difference between processing of default expressions and
199--  preanalysis of other expressions is that we do carry out freezing in
200--  the latter but not in the former (except for static scalar expressions).
201--  The routine that performs preanalysis and corresponding resolution is
202--  called Preanalyze_And_Resolve and is in Sem_Res.
203
204with Alloc;
205with Opt;    use Opt;
206with Table;
207with Types;  use Types;
208
209package Sem is
210
211   -----------------------------
212   -- Semantic Analysis Flags --
213   -----------------------------
214
215   Full_Analysis : Boolean := True;
216   --  Switch to indicate if we are doing a full analysis or a preanalysis.
217   --  In normal analysis mode (Analysis-Expansion for instructions or
218   --  declarations) or (Analysis-Resolution-Expansion for expressions) this
219   --  flag is set. Note that if we are not generating code the expansion phase
220   --  merely sets the Analyzed flag to True in this case. If we are in
221   --  Preanalysis mode (see above) this flag is set to False then the
222   --  expansion phase is skipped.
223   --
224   --  When this flag is False the flag Expander_Active is also False (the
225   --  Expander_Active flag defined in the spec of package Expander tells you
226   --  whether expansion is currently enabled). You should really regard this
227   --  as a read only flag.
228
229   In_Spec_Expression : Boolean := False;
230   --  Switch to indicate that we are in a spec-expression, as described
231   --  above. Note that this must be recursively saved on a Semantics call
232   --  since it is possible for the analysis of an expression to result in a
233   --  recursive call (e.g. to get the entity for System.Address as part of the
234   --  processing of an Address attribute reference). When this switch is True
235   --  then Full_Analysis above must be False. You should really regard this as
236   --  a read only flag.
237
238   In_Deleted_Code : Boolean := False;
239   --  If the condition in an if-statement is statically known, the branch
240   --  that is not taken is analyzed with expansion disabled, and the tree
241   --  is deleted after analysis. Itypes generated in deleted code must be
242   --  frozen from start, because the tree on which they depend will not
243   --  be available at the freeze point.
244
245   In_Assertion_Expr : Nat := 0;
246   --  This is set non-zero if we are within the expression of an assertion
247   --  pragma or aspect. It is incremented at the start of expanding such an
248   --  expression, and decremented on completion of expanding that
249   --  expression. This needs to be a counter, rather than a Boolean, because
250   --  assertions can contain declare_expressions, which can contain
251   --  assertions. As with In_Spec_Expression, it must be recursively saved and
252   --  restored for a Semantics call.
253
254   In_Declare_Expr : Nat := 0;
255   --  This is set non-zero if we are within a declare_expression. It is
256   --  incremented at the start of expanding such an expression, and
257   --  decremented on completion of expanding that expression. This needs to be
258   --  a counter, rather than a Boolean, because declare_expressions can
259   --  nest. As with In_Spec_Expression, it must be recursively saved and
260   --  restored for a Semantics call.
261
262   In_Compile_Time_Warning_Or_Error : Boolean := False;
263   --  Switch to indicate that we are validating a pragma Compile_Time_Warning
264   --  or Compile_Time_Error after the back end has been called (to check these
265   --  pragmas for size and alignment appropriateness).
266
267   In_Default_Expr : Boolean := False;
268   --  Switch to indicate that we are analyzing a default component expression.
269   --  As with In_Spec_Expression, it must be recursively saved and restored
270   --  for a Semantics call.
271
272   In_Inlined_Body : Boolean := False;
273   --  Switch to indicate that we are analyzing and resolving an inlined body.
274   --  Type checking is disabled in this context, because types are known to be
275   --  compatible. This avoids problems with private types whose full view is
276   --  derived from private types.
277
278   Inside_A_Generic : Boolean := False;
279   --  This flag is set if we are processing a generic specification, generic
280   --  definition, or generic body. When this flag is True the Expander_Active
281   --  flag is False to disable any code expansion (see package Expander). Only
282   --  the generic processing can modify the status of this flag, any other
283   --  client should regard it as read-only.
284
285   Inside_Freezing_Actions : Nat := 0;
286   --  Flag indicating whether we are within a call to Expand_N_Freeze_Actions.
287   --  Non-zero means we are inside (it is actually a level counter to deal
288   --  with nested calls). Used to avoid traversing the tree each time a
289   --  subprogram call is processed to know if we must not clear all constant
290   --  indications from entities in the current scope. Only the expansion of
291   --  freezing nodes can modify the status of this flag, any other client
292   --  should regard it as read-only.
293
294   Inside_Class_Condition_Preanalysis : Boolean := False;
295   --  Flag indicating whether we are preanalyzing a class-wide precondition
296   --  or postcondition.
297
298   Inside_Preanalysis_Without_Freezing : Nat := 0;
299   --  Flag indicating whether we are preanalyzing an expression performing no
300   --  freezing. Non-zero means we are inside (it is actually a level counter
301   --  to deal with nested calls).
302
303   Unloaded_Subunits : Boolean := False;
304   --  This flag is set True if we have subunits that are not loaded. This
305   --  occurs when the main unit is a subunit, and contains lower level
306   --  subunits that are not loaded. We use this flag to suppress warnings
307   --  about unused variables, since these warnings are unreliable in this
308   --  case. We could perhaps do a more accurate job and retain some of the
309   --  warnings, but it is quite a tricky job.
310
311   -----------------------------------
312   -- Handling of Check Suppression --
313   -----------------------------------
314
315   --  There are two kinds of suppress checks: scope based suppress checks,
316   --  and entity based suppress checks.
317
318   --  Scope based suppress checks for the predefined checks (from initial
319   --  command line arguments, or from Suppress pragmas not including an entity
320   --  name) are recorded in the Sem.Scope_Suppress variable, and all that
321   --  is necessary is to save the state of this variable on scope entry, and
322   --  restore it on scope exit. This mechanism allows for fast checking of the
323   --  scope suppress state without needing complex data structures.
324
325   --  Entity based checks, from Suppress/Unsuppress pragmas giving an
326   --  Entity_Id and scope based checks for non-predefined checks (introduced
327   --  using pragma Check_Name), are handled as follows. If a suppress or
328   --  unsuppress pragma is encountered for a given entity, then the flag
329   --  Checks_May_Be_Suppressed is set in the entity and an entry is made in
330   --  either the Local_Entity_Suppress stack (case of pragma that appears in
331   --  other than a package spec), or in the Global_Entity_Suppress stack (case
332   --  of pragma that appears in a package spec, which is by the rule of RM
333   --  11.5(7) applicable throughout the life of the entity). Similarly, a
334   --  Suppress/Unsuppress pragma for a non-predefined check which does not
335   --  specify an entity is also stored in one of these stacks.
336
337   --  If the Checks_May_Be_Suppressed flag is set in an entity then the
338   --  procedure is to search first the local and then the global suppress
339   --  stacks (we search these in reverse order, top element first). The only
340   --  other point is that we have to make sure that we have proper nested
341   --  interaction between such specific pragmas and locally applied general
342   --  pragmas applying to all entities. This is achieved by including in the
343   --  Local_Entity_Suppress table dummy entries with an empty Entity field
344   --  that are applicable to all entities. A similar search is needed for any
345   --  non-predefined check even if no specific entity is involved.
346
347   Scope_Suppress : Suppress_Record;
348   --  This variable contains the current scope based settings of the suppress
349   --  switches. It is initialized from Suppress_Options in Gnat1drv, and then
350   --  modified by pragma Suppress. On entry to each scope, the current setting
351   --  is saved on the scope stack, and then restored on exit from the scope.
352   --  This record may be rapidly checked to determine the current status of
353   --  a check if no specific entity is involved or if the specific entity
354   --  involved is one for which no specific Suppress/Unsuppress pragma has
355   --  been set (as indicated by the Checks_May_Be_Suppressed flag being set).
356
357   --  This scheme is a little complex, but serves the purpose of enabling
358   --  a very rapid check in the common case where no entity specific pragma
359   --  applies, and gives the right result when such pragmas are used even
360   --  in complex cases of nested Suppress and Unsuppress pragmas.
361
362   --  The Local_Entity_Suppress and Global_Entity_Suppress stacks are handled
363   --  using dynamic allocation and linked lists. We do not often use this
364   --  approach in the compiler (preferring to use extensible tables instead).
365   --  The reason we do it here is that scope stack entries save a pointer to
366   --  the current local stack top, which is also saved and restored on scope
367   --  exit. Furthermore for processing of generics we save pointers to the
368   --  top of the stack, so that the local stack is actually a tree of stacks
369   --  rather than a single stack, a structure that is easy to represent using
370   --  linked lists, but impossible to represent using a single table. Note
371   --  that because of the generic issue, we never release entries in these
372   --  stacks, but that's no big deal, since we are unlikely to have a huge
373   --  number of Suppress/Unsuppress entries in a single compilation.
374
375   type Suppress_Stack_Entry;
376   type Suppress_Stack_Entry_Ptr is access all Suppress_Stack_Entry;
377
378   type Suppress_Stack_Entry is record
379      Entity : Entity_Id;
380      --  Entity to which the check applies, or Empty for a check that has
381      --  no entity name (and thus applies to all entities).
382
383      Check : Check_Id;
384      --  Check which is set (can be All_Checks for the All_Checks case)
385
386      Suppress : Boolean;
387      --  Set True for Suppress, and False for Unsuppress
388
389      Prev : Suppress_Stack_Entry_Ptr;
390      --  Pointer to previous entry on stack
391
392      Next : Suppress_Stack_Entry_Ptr;
393      --  All allocated Suppress_Stack_Entry records are chained together in
394      --  a linked list whose head is Suppress_Stack_Entries, and the Next
395      --  field is used as a forward pointer (null ends the list). This is
396      --  used to free all entries in Sem.Init (which will be important if
397      --  we ever setup the compiler to be reused).
398   end record;
399
400   Suppress_Stack_Entries : Suppress_Stack_Entry_Ptr := null;
401   --  Pointer to linked list of records (see comments for Next above)
402
403   Local_Suppress_Stack_Top : Suppress_Stack_Entry_Ptr;
404   --  Pointer to top element of local suppress stack. This is the entry that
405   --  is saved and restored in the scope stack, and also saved for generic
406   --  body expansion.
407
408   Global_Suppress_Stack_Top : Suppress_Stack_Entry_Ptr;
409   --  Pointer to top element of global suppress stack
410
411   procedure Push_Local_Suppress_Stack_Entry
412     (Entity   : Entity_Id;
413      Check    : Check_Id;
414      Suppress : Boolean);
415   --  Push a new entry on to the top of the local suppress stack, updating
416   --  the value in Local_Suppress_Stack_Top;
417
418   procedure Push_Global_Suppress_Stack_Entry
419     (Entity   : Entity_Id;
420      Check    : Check_Id;
421      Suppress : Boolean);
422   --  Push a new entry on to the top of the global suppress stack, updating
423   --  the value in Global_Suppress_Stack_Top;
424
425   -----------------
426   -- Scope Stack --
427   -----------------
428
429   --  The scope stack indicates the declarative regions that are currently
430   --  being processed (analyzed and/or expanded). The scope stack is one of
431   --  the basic visibility structures in the compiler: entities that are
432   --  declared in a scope that is currently on the scope stack are immediately
433   --  visible (leaving aside issues of hiding and overloading).
434
435   --  Initially, the scope stack only contains an entry for package Standard.
436   --  When a compilation unit, subprogram unit, block or declarative region
437   --  is being processed, the corresponding entity is pushed on the scope
438   --  stack. It is removed after the processing step is completed. A given
439   --  entity can be placed several times on the scope stack, for example
440   --  when processing derived type declarations, freeze nodes, etc. The top
441   --  of the scope stack is the innermost scope currently being processed.
442   --  It is obtained through function Current_Scope. After a compilation unit
443   --  has been processed, the scope stack must contain only Standard.
444   --  The predicate In_Open_Scopes specifies whether a scope is currently
445   --  on the scope stack.
446
447   --  This model is complicated by the need to compile units on the fly, in
448   --  the middle of the compilation of other units. This arises when compiling
449   --  instantiations, and when compiling run-time packages obtained through
450   --  rtsfind. Given that the scope stack is a single static and global
451   --  structure (not originally designed for the recursive processing required
452   --  by rtsfind for example) additional machinery is needed to indicate what
453   --  is currently being compiled. As a result, the scope stack holds several
454   --  contiguous sections that correspond to the compilation of a given
455   --  compilation unit. These sections are separated by distinct occurrences
456   --  of package Standard. The currently active section of the scope stack
457   --  goes from the current scope to the first (innermost) occurrence of
458   --  Standard, which is additionally marked with flag Is_Active_Stack_Base.
459   --  The basic visibility routine (Find_Direct_Name, in Sem_Ch8) uses this
460   --  contiguous section of the scope stack to determine whether a given
461   --  entity is or is not visible at a point. In_Open_Scopes only examines
462   --  the currently active section of the scope stack.
463
464   --  Similar complications arise when processing child instances. These
465   --  must be compiled in the context of parent instances, and therefore the
466   --  parents must be pushed on the stack before compiling the child, and
467   --  removed afterwards. Routines Save_Scope_Stack and Restore_Scope_Stack
468   --  are used to set/reset the visibility of entities declared in scopes
469   --  that are currently on the scope stack, and are used when compiling
470   --  instance bodies on the fly.
471
472   --  It is clear in retrospect that all semantic processing and visibility
473   --  structures should have been fully recursive. The rtsfind mechanism,
474   --  and the complexities brought about by subunits and by generic child
475   --  units and their instantiations, have led to a hybrid model that carries
476   --  more state than one would wish.
477
478   type Scope_Action_Kind is (Before, After, Cleanup);
479   type Scope_Actions is array (Scope_Action_Kind) of List_Id;
480   --  Transient blocks have three associated actions list, to be inserted
481   --  before and after the block's statements, and as cleanup actions.
482
483   Configuration_Component_Alignment : Component_Alignment_Kind :=
484                                         Calign_Default;
485   --  Used for handling the pragma Component_Alignment in the context of a
486   --  configuration file.
487
488   type Scope_Stack_Entry is record
489      Entity : Entity_Id;
490      --  Entity representing the scope
491
492      Last_Subprogram_Name : String_Ptr;
493      --  Pointer to name of last subprogram body in this scope. Used for
494      --  testing proper alpha ordering of subprogram bodies in scope.
495
496      Save_Scope_Suppress : Suppress_Record;
497      --  Save contents of Scope_Suppress on entry
498
499      Save_Local_Suppress_Stack_Top : Suppress_Stack_Entry_Ptr;
500      --  Save contents of Local_Suppress_Stack on entry to restore on exit
501
502      Save_Check_Policy_List : Node_Id;
503      --  Save contents of Check_Policy_List on entry to restore on exit. The
504      --  Check_Policy pragmas are chained with Check_Policy_List pointing to
505      --  the most recent entry. This list is searched starting here, so that
506      --  the search finds the most recent appicable entry. When we restore
507      --  Check_Policy_List on exit from the scope, the effect is to remove
508      --  all entries set in the scope being exited.
509
510      Save_Default_Storage_Pool : Node_Id;
511      --  Save contents of Default_Storage_Pool on entry to restore on exit
512
513      Save_SPARK_Mode : SPARK_Mode_Type;
514      --  Setting of SPARK_Mode on entry to restore on exit
515
516      Save_SPARK_Mode_Pragma : Node_Id;
517      --  Setting of SPARK_Mode_Pragma on entry to restore on exit
518
519      Save_No_Tagged_Streams : Node_Id;
520      --  Setting of No_Tagged_Streams to restore on exit
521
522      Save_Default_SSO : Character;
523      --  Setting of Default_SSO on entry to restore on exit
524
525      Save_Uneval_Old : Character;
526      --  Setting of Uneval_Old on entry to restore on exit
527
528      Is_Transient : Boolean;
529      --  Marks transient scopes (see Exp_Ch7 body for details)
530
531      Previous_Visibility : Boolean;
532      --  Used when installing the parent(s) of the current compilation unit.
533      --  The parent may already be visible because of an ongoing compilation,
534      --  and the proper visibility must be restored on exit. The flag is
535      --  typically needed when the context of a child unit requires
536      --  compilation of a sibling. In other cases the flag is set to False.
537      --  See Sem_Ch10 (Install_Parents, Remove_Parents).
538
539      Node_To_Be_Wrapped : Node_Id;
540      --  Only used in transient scopes. Records the node that will be wrapped
541      --  by the transient block.
542
543      Actions_To_Be_Wrapped : Scope_Actions;
544      --  Actions that have to be inserted at the start, at the end, or as
545      --  cleanup actions of a transient block. Used to temporarily hold these
546      --  actions until the block is created, at which time the actions are
547      --  moved to the block.
548
549      Pending_Freeze_Actions : List_Id;
550      --  Used to collect freeze entity nodes and associated actions that are
551      --  generated in an inner context but need to be analyzed outside, such
552      --  as records and initialization procedures. On exit from the scope,
553      --  this list of actions is inserted before the scope construct and
554      --  analyzed to generate the corresponding freeze processing and
555      --  elaboration of other associated actions.
556
557      First_Use_Clause : Node_Id;
558      --  Head of list of Use_Clauses in current scope. The list is built when
559      --  the declarations in the scope are processed. The list is traversed
560      --  on scope exit to undo the effect of the use clauses.
561
562      Component_Alignment_Default : Component_Alignment_Kind;
563      --  Component alignment to be applied to any record or array types that
564      --  are declared for which a specific component alignment pragma does not
565      --  set the alignment.
566
567      Is_Active_Stack_Base : Boolean;
568      --  Set to true only when entering the scope for Standard_Standard from
569      --  from within procedure Semantics. Indicates the base of the current
570      --  active set of scopes. Needed by In_Open_Scopes to handle cases where
571      --  Standard_Standard can be pushed anew on the scope stack to start a
572      --  new active section (see comment above).
573
574      Locked_Shared_Objects : Elist_Id;
575      --  List of shared passive protected objects that have been locked in
576      --  this transient scope (always No_Elist for non-transient scopes).
577   end record;
578
579   package Scope_Stack is new Table.Table (
580     Table_Component_Type => Scope_Stack_Entry,
581     Table_Index_Type     => Int,
582     Table_Low_Bound      => 0,
583     Table_Initial        => Alloc.Scope_Stack_Initial,
584     Table_Increment      => Alloc.Scope_Stack_Increment,
585     Table_Name           => "Sem.Scope_Stack");
586
587   -----------------
588   -- Subprograms --
589   -----------------
590
591   procedure Initialize;
592   --  Initialize internal tables
593
594   procedure Lock;
595   --  Lock internal tables before calling back end
596
597   procedure Unlock;
598   --  Unlock internal tables
599
600   procedure Semantics (Comp_Unit : Node_Id);
601   --  This procedure is called to perform semantic analysis on the specified
602   --  node which is the N_Compilation_Unit node for the unit.
603
604   procedure Analyze (N : Node_Id);
605   procedure Analyze (N : Node_Id; Suppress : Check_Id);
606   --  This is the recursive procedure that is applied to individual nodes of
607   --  the tree, starting at the top level node (compilation unit node) and
608   --  then moving down the tree in a top down traversal. It calls individual
609   --  routines with names Analyze_xxx to analyze node xxx. Each of these
610   --  routines is responsible for calling Analyze on the components of the
611   --  subtree.
612   --
613   --  Note: In the case of expression components (nodes whose Nkind is in
614   --  N_Subexpr), the call to Analyze does not complete the semantic analysis
615   --  of the node, since the type resolution cannot be completed until the
616   --  complete context is analyzed. The completion of the type analysis occurs
617   --  in the corresponding Resolve routine (see Sem_Res).
618   --
619   --  Note: for integer and real literals, the analyzer sets the flag to
620   --  indicate that the result is a static expression. If the expander
621   --  generates a literal that does NOT correspond to a static expression,
622   --  e.g. by folding an expression whose value is known at compile time,
623   --  but is not technically static, then the caller should reset the
624   --  Is_Static_Expression flag after analyzing but before resolving.
625   --
626   --  If the Suppress argument is present, then the analysis is done
627   --  with the specified check suppressed (can be All_Checks to suppress
628   --  all checks).
629
630   procedure Analyze_List (L : List_Id);
631   procedure Analyze_List (L : List_Id; Suppress : Check_Id);
632   --  Analyzes each element of a list. If the Suppress argument is present,
633   --  then the analysis is done with the specified check suppressed (can
634   --  be All_Checks to suppress all checks).
635
636   procedure Copy_Suppress_Status
637     (C    : Check_Id;
638      From : Entity_Id;
639      To   : Entity_Id);
640   --  If From is an entity for which check C is explicitly suppressed
641   --  then also explicitly suppress the corresponding check in To.
642
643   procedure Insert_List_After_And_Analyze
644     (N : Node_Id; L : List_Id);
645   --  Inserts list L after node N using Nlists.Insert_List_After, and then,
646   --  after this insertion is complete, analyzes all the nodes in the list,
647   --  including any additional nodes generated by this analysis. If the list
648   --  is empty or No_List, the call has no effect.
649
650   procedure Insert_List_Before_And_Analyze
651     (N : Node_Id; L : List_Id);
652   --  Inserts list L before node N using Nlists.Insert_List_Before, and then,
653   --  after this insertion is complete, analyzes all the nodes in the list,
654   --  including any additional nodes generated by this analysis. If the list
655   --  is empty or No_List, the call has no effect.
656
657   procedure Insert_After_And_Analyze
658     (N : Node_Id; M : Node_Id);
659   procedure Insert_After_And_Analyze
660     (N : Node_Id; M : Node_Id; Suppress : Check_Id);
661   --  Inserts node M after node N and then after the insertion is complete,
662   --  analyzes the inserted node and all nodes that are generated by
663   --  this analysis. If the node is empty, the call has no effect. If the
664   --  Suppress argument is present, then the analysis is done with the
665   --  specified check suppressed (can be All_Checks to suppress all checks).
666
667   procedure Insert_Before_And_Analyze
668     (N : Node_Id; M : Node_Id);
669   procedure Insert_Before_And_Analyze
670     (N : Node_Id; M : Node_Id; Suppress : Check_Id);
671   --  Inserts node M before node N and then after the insertion is complete,
672   --  analyzes the inserted node and all nodes that could be generated by
673   --  this analysis. If the node is empty, the call has no effect. If the
674   --  Suppress argument is present, then the analysis is done with the
675   --  specified check suppressed (can be All_Checks to suppress all checks).
676
677   procedure Insert_Before_First_Source_Declaration
678     (Stmt  : Node_Id;
679      Decls : List_Id);
680   --  Insert node Stmt before the first source declaration of the related
681   --  subprogram's body. If no such declaration exists, Stmt becomes the last
682   --  declaration.
683
684   function External_Ref_In_Generic (E : Entity_Id) return Boolean;
685   --  Return True if we are in the context of a generic and E is
686   --  external (more global) to it.
687
688   procedure Enter_Generic_Scope (S : Entity_Id);
689   --  Called each time a Generic subprogram or package scope is entered. S is
690   --  the entity of the scope.
691   --
692   --  ??? At the moment, only called for package specs because this mechanism
693   --  is only used for avoiding freezing of external references in generics
694   --  and this can only be an issue if the outer generic scope is a package
695   --  spec (otherwise all external entities are already frozen)
696
697   procedure Exit_Generic_Scope  (S : Entity_Id);
698   --  Called each time a Generic subprogram or package scope is exited. S is
699   --  the entity of the scope.
700   --
701   --  ??? At the moment, only called for package specs exit.
702
703   function Explicit_Suppress (E : Entity_Id; C : Check_Id) return Boolean;
704   --  This function returns True if an explicit pragma Suppress for check C
705   --  is present in the package defining E.
706
707   function Preanalysis_Active return Boolean;
708   pragma Inline (Preanalysis_Active);
709   --  Determine whether preanalysis is active at the point of invocation
710
711   procedure Preanalyze (N : Node_Id);
712   --  Performs a preanalysis of node N. During preanalysis no expansion is
713   --  carried out for N or its children. See above for more info on
714   --  preanalysis.
715
716   generic
717      with procedure Action (Item : Node_Id);
718   procedure Walk_Library_Items;
719   --  Primarily for use by CodePeer and GNATprove. Must be called after
720   --  semantic analysis (and expansion in the case of CodePeer) are complete.
721   --  Walks each relevant library item, calling Action for each, in an order
722   --  such that one will not run across forward references. Each Item passed
723   --  to Action is the declaration or body of a library unit, including
724   --  generics and renamings. The first item is the N_Package_Declaration node
725   --  for package Standard. Bodies are not included, except for the main unit
726   --  itself, which always comes last.
727   --
728   --  Item is never a subunit
729   --
730   --  Item is never an instantiation. Instead, the instance declaration is
731   --  passed, and (if the instantiation is the main unit), the instance body.
732
733   ------------------------
734   -- Debugging Routines --
735   ------------------------
736
737   function ss (Index : Int) return Scope_Stack_Entry;
738   pragma Export (Ada, ss);
739   --  "ss" = "scope stack"; returns the Index'th entry in the Scope_Stack
740
741   function sst return Scope_Stack_Entry;
742   pragma Export (Ada, sst);
743   --  "sst" = "scope stack top"; same as ss(Scope_Stack.Last)
744
745end Sem;
746