OSDN Git Service

gcc/ada/
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_elab.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ E L A B                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1997-2008, 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 with Atree;    use Atree;
27 with Checks;   use Checks;
28 with Debug;    use Debug;
29 with Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Errout;   use Errout;
32 with Exp_Tss;  use Exp_Tss;
33 with Exp_Util; use Exp_Util;
34 with Expander; use Expander;
35 with Fname;    use Fname;
36 with Lib;      use Lib;
37 with Lib.Load; use Lib.Load;
38 with Namet;    use Namet;
39 with Nlists;   use Nlists;
40 with Nmake;    use Nmake;
41 with Opt;      use Opt;
42 with Output;   use Output;
43 with Restrict; use Restrict;
44 with Rident;   use Rident;
45 with Sem;      use Sem;
46 with Sem_Cat;  use Sem_Cat;
47 with Sem_Ch7;  use Sem_Ch7;
48 with Sem_Ch8;  use Sem_Ch8;
49 with Sem_Res;  use Sem_Res;
50 with Sem_Util; use Sem_Util;
51 with Sinfo;    use Sinfo;
52 with Sinput;   use Sinput;
53 with Snames;   use Snames;
54 with Stand;    use Stand;
55 with Table;
56 with Tbuild;   use Tbuild;
57 with Uname;    use Uname;
58
59 package body Sem_Elab is
60
61    --  The following table records the recursive call chain for output in the
62    --  Output routine. Each entry records the call node and the entity of the
63    --  called routine. The number of entries in the table (i.e. the value of
64    --  Elab_Call.Last) indicates the current depth of recursion and is used to
65    --  identify the outer level.
66
67    type Elab_Call_Entry is record
68       Cloc : Source_Ptr;
69       Ent  : Entity_Id;
70    end record;
71
72    package Elab_Call is new Table.Table (
73      Table_Component_Type => Elab_Call_Entry,
74      Table_Index_Type     => Int,
75      Table_Low_Bound      => 1,
76      Table_Initial        => 50,
77      Table_Increment      => 100,
78      Table_Name           => "Elab_Call");
79
80    --  This table is initialized at the start of each outer level call. It
81    --  holds the entities for all subprograms that have been examined for this
82    --  particular outer level call, and is used to prevent both infinite
83    --  recursion, and useless reanalysis of bodies already seen
84
85    package Elab_Visited is new Table.Table (
86      Table_Component_Type => Entity_Id,
87      Table_Index_Type     => Int,
88      Table_Low_Bound      => 1,
89      Table_Initial        => 200,
90      Table_Increment      => 100,
91      Table_Name           => "Elab_Visited");
92
93    --  This table stores calls to Check_Internal_Call that are delayed
94    --  until all generics are instantiated, and in particular that all
95    --  generic bodies have been inserted. We need to delay, because we
96    --  need to be able to look through the inserted bodies.
97
98    type Delay_Element is record
99       N : Node_Id;
100       --  The parameter N from the call to Check_Internal_Call. Note that
101       --  this node may get rewritten over the delay period by expansion
102       --  in the call case (but not in the instantiation case).
103
104       E : Entity_Id;
105       --  The parameter E from the call to Check_Internal_Call
106
107       Orig_Ent : Entity_Id;
108       --  The parameter Orig_Ent from the call to Check_Internal_Call
109
110       Curscop : Entity_Id;
111       --  The current scope of the call. This is restored when we complete
112       --  the delayed call, so that we do this in the right scope.
113
114       From_Elab_Code : Boolean;
115       --  Save indication of whether this call is from elaboration code
116
117       Outer_Scope : Entity_Id;
118       --  Save scope of outer level call
119    end record;
120
121    package Delay_Check is new Table.Table (
122      Table_Component_Type => Delay_Element,
123      Table_Index_Type     => Int,
124      Table_Low_Bound      => 1,
125      Table_Initial        => 1000,
126      Table_Increment      => 100,
127      Table_Name           => "Delay_Check");
128
129    C_Scope : Entity_Id;
130    --  Top level scope of current scope. Compute this only once at the outer
131    --  level, i.e. for a call to Check_Elab_Call from outside this unit.
132
133    Outer_Level_Sloc : Source_Ptr;
134    --  Save Sloc value for outer level call node for comparisons of source
135    --  locations. A body is too late if it appears after the *outer* level
136    --  call, not the particular call that is being analyzed.
137
138    From_Elab_Code : Boolean;
139    --  This flag shows whether the outer level call currently being examined
140    --  is or is not in elaboration code. We are only interested in calls to
141    --  routines in other units if this flag is True.
142
143    In_Task_Activation : Boolean := False;
144    --  This flag indicates whether we are performing elaboration checks on
145    --  task procedures, at the point of activation. If true, we do not trace
146    --  internal calls in these procedures, because all local bodies are known
147    --  to be elaborated.
148
149    Delaying_Elab_Checks : Boolean := True;
150    --  This is set True till the compilation is complete, including the
151    --  insertion of all instance bodies. Then when Check_Elab_Calls is called,
152    --  the delay table is used to make the delayed calls and this flag is reset
153    --  to False, so that the calls are processed
154
155    -----------------------
156    -- Local Subprograms --
157    -----------------------
158
159    --  Note: Outer_Scope in all following specs represents the scope of
160    --  interest of the outer level call. If it is set to Standard_Standard,
161    --  then it means the outer level call was at elaboration level, and that
162    --  thus all calls are of interest. If it was set to some other scope,
163    --  then the original call was an inner call, and we are not interested
164    --  in calls that go outside this scope.
165
166    procedure Activate_Elaborate_All_Desirable (N : Node_Id; U : Entity_Id);
167    --  Analysis of construct N shows that we should set Elaborate_All_Desirable
168    --  for the WITH clause for unit U (which will always be present). A special
169    --  case is when N is a function or procedure instantiation, in which case
170    --  it is sufficient to set Elaborate_Desirable, since in this case there is
171    --  no possibility of transitive elaboration issues.
172
173    procedure Check_A_Call
174      (N                 : Node_Id;
175       E                 : Entity_Id;
176       Outer_Scope       : Entity_Id;
177       Inter_Unit_Only   : Boolean;
178       Generate_Warnings : Boolean := True);
179    --  This is the internal recursive routine that is called to check for a
180    --  possible elaboration error. The argument N is a subprogram call or
181    --  generic instantiation to be checked, and E is the entity of the called
182    --  subprogram, or instantiated generic unit. The flag Outer_Scope is the
183    --  outer level scope for the original call. Inter_Unit_Only is set if the
184    --  call is only to be checked in the case where it is to another unit (and
185    --  skipped if within a unit). Generate_Warnings is set to False to suppress
186    --  warning messages about missing pragma Elaborate_All's. These messages
187    --  are not wanted for inner calls in the dynamic model.
188
189    procedure Check_Bad_Instantiation (N : Node_Id);
190    --  N is a node for an instantiation (if called with any other node kind,
191    --  Check_Bad_Instantiation ignores the call). This subprogram checks for
192    --  the special case of a generic instantiation of a generic spec in the
193    --  same declarative part as the instantiation where a body is present and
194    --  has not yet been seen. This is an obvious error, but needs to be checked
195    --  specially at the time of the instantiation, since it is a case where we
196    --  cannot insert the body anywhere. If this case is detected, warnings are
197    --  generated, and a raise of Program_Error is inserted. In addition any
198    --  subprograms in the generic spec are stubbed, and the Bad_Instantiation
199    --  flag is set on the instantiation node. The caller in Sem_Ch12 uses this
200    --  flag as an indication that no attempt should be made to insert an
201    --  instance body.
202
203    procedure Check_Internal_Call
204      (N           : Node_Id;
205       E           : Entity_Id;
206       Outer_Scope : Entity_Id;
207       Orig_Ent    : Entity_Id);
208    --  N is a function call or procedure statement call node and E is the
209    --  entity of the called function, which is within the current compilation
210    --  unit (where subunits count as part of the parent). This call checks if
211    --  this call, or any call within any accessed body could cause an ABE, and
212    --  if so, outputs a warning. Orig_Ent differs from E only in the case of
213    --  renamings, and points to the original name of the entity. This is used
214    --  for error messages. Outer_Scope is the outer level scope for the
215    --  original call.
216
217    procedure Check_Internal_Call_Continue
218      (N           : Node_Id;
219       E           : Entity_Id;
220       Outer_Scope : Entity_Id;
221       Orig_Ent    : Entity_Id);
222    --  The processing for Check_Internal_Call is divided up into two phases,
223    --  and this represents the second phase. The second phase is delayed if
224    --  Delaying_Elab_Calls is set to True. In this delayed case, the first
225    --  phase makes an entry in the Delay_Check table, which is processed when
226    --  Check_Elab_Calls is called. N, E and Orig_Ent are as for the call to
227    --  Check_Internal_Call. Outer_Scope is the outer level scope for the
228    --  original call.
229
230    procedure Set_Elaboration_Constraint
231     (Call : Node_Id;
232      Subp : Entity_Id;
233      Scop : Entity_Id);
234    --  The current unit U may depend semantically on some unit P which is not
235    --  in the current context. If there is an elaboration call that reaches P,
236    --  we need to indicate that P requires an Elaborate_All, but this is not
237    --  effective in U's ali file, if there is no with_clause for P. In this
238    --  case we add the Elaborate_All on the unit Q that directly or indirectly
239    --  makes P available. This can happen in two cases:
240    --
241    --    a) Q declares a subtype of a type declared in P, and the call is an
242    --    initialization call for an object of that subtype.
243    --
244    --    b) Q declares an object of some tagged type whose root type is
245    --    declared in P, and the initialization call uses object notation on
246    --    that object to reach a primitive operation or a classwide operation
247    --    declared in P.
248    --
249    --  If P appears in the context of U, the current processing is correct.
250    --  Otherwise we must identify these two cases to retrieve Q and place the
251    --  Elaborate_All_Desirable on it.
252
253    function Has_Generic_Body (N : Node_Id) return Boolean;
254    --  N is a generic package instantiation node, and this routine determines
255    --  if this package spec does in fact have a generic body. If so, then
256    --  True is returned, otherwise False. Note that this is not at all the
257    --  same as checking if the unit requires a body, since it deals with
258    --  the case of optional bodies accurately (i.e. if a body is optional,
259    --  then it looks to see if a body is actually present). Note: this
260    --  function can only do a fully correct job if in generating code mode
261    --  where all bodies have to be present. If we are operating in semantics
262    --  check only mode, then in some cases of optional bodies, a result of
263    --  False may incorrectly be given. In practice this simply means that
264    --  some cases of warnings for incorrect order of elaboration will only
265    --  be given when generating code, which is not a big problem (and is
266    --  inevitable, given the optional body semantics of Ada).
267
268    procedure Insert_Elab_Check (N : Node_Id; C : Node_Id := Empty);
269    --  Given code for an elaboration check (or unconditional raise if the check
270    --  is not needed), inserts the code in the appropriate place. N is the call
271    --  or instantiation node for which the check code is required. C is the
272    --  test whose failure triggers the raise.
273
274    procedure Output_Calls (N : Node_Id);
275    --  Outputs chain of calls stored in the Elab_Call table. The caller has
276    --  already generated the main warning message, so the warnings generated
277    --  are all continuation messages. The argument is the call node at which
278    --  the messages are to be placed.
279
280    function Same_Elaboration_Scope (Scop1, Scop2 : Entity_Id) return Boolean;
281    --  Given two scopes, determine whether they are the same scope from an
282    --  elaboration point of view, i.e. packages and blocks are ignored.
283
284    procedure Set_C_Scope;
285    --  On entry C_Scope is set to some scope. On return, C_Scope is reset
286    --  to be the enclosing compilation unit of this scope.
287
288    function Spec_Entity (E : Entity_Id) return Entity_Id;
289    --  Given a compilation unit entity, if it is a spec entity, it is returned
290    --  unchanged. If it is a body entity, then the spec for the corresponding
291    --  spec is returned
292
293    procedure Supply_Bodies (N : Node_Id);
294    --  Given a node, N, that is either a subprogram declaration or a package
295    --  declaration, this procedure supplies dummy bodies for the subprogram
296    --  or for all subprograms in the package. If the given node is not one
297    --  of these two possibilities, then Supply_Bodies does nothing. The
298    --  dummy body contains a single Raise statement.
299
300    procedure Supply_Bodies (L : List_Id);
301    --  Calls Supply_Bodies for all elements of the given list L
302
303    function Within (E1, E2 : Entity_Id) return Boolean;
304    --  Given two scopes E1 and E2, returns True if E1 is equal to E2, or is one
305    --  of its contained scopes, False otherwise.
306
307    function Within_Elaborate_All (E : Entity_Id) return Boolean;
308    --  Before emitting a warning on a scope E for a missing elaborate_all,
309    --  check whether E may be in the context of a directly visible unit U to
310    --  which the pragma applies. This prevents spurious warnings when the
311    --  called entity is renamed within U.
312
313    --------------------------------------
314    -- Activate_Elaborate_All_Desirable --
315    --------------------------------------
316
317    procedure Activate_Elaborate_All_Desirable (N : Node_Id; U : Entity_Id) is
318       UN  : constant Unit_Number_Type := Get_Code_Unit (N);
319       CU  : constant Node_Id          := Cunit (UN);
320       UE  : constant Entity_Id        := Cunit_Entity (UN);
321       Unm : constant Unit_Name_Type   := Unit_Name (UN);
322       CI  : constant List_Id          := Context_Items (CU);
323       Itm : Node_Id;
324       Ent : Entity_Id;
325
326       procedure Add_To_Context_And_Mark (Itm : Node_Id);
327       --  This procedure is called when the elaborate indication must be
328       --  applied to a unit not in the context of the referencing unit. The
329       --  unit gets added to the context as an implicit with.
330
331       function In_Withs_Of (UEs : Entity_Id) return Boolean;
332       --  UEs is the spec entity of a unit. If the unit to be marked is
333       --  in the context item list of this unit spec, then the call returns
334       --  True and Itm is left set to point to the relevant N_With_Clause node.
335
336       procedure Set_Elab_Flag (Itm : Node_Id);
337       --  Sets Elaborate_[All_]Desirable as appropriate on Itm
338
339       -----------------------------
340       -- Add_To_Context_And_Mark --
341       -----------------------------
342
343       procedure Add_To_Context_And_Mark (Itm : Node_Id) is
344          CW : constant Node_Id :=
345                 Make_With_Clause (Sloc (Itm),
346                   Name => Name (Itm));
347
348       begin
349          Set_Library_Unit  (CW, Library_Unit (Itm));
350          Set_Implicit_With (CW, True);
351
352          --  Set elaborate all desirable on copy and then append the copy to
353          --  the list of body with's and we are done.
354
355          Set_Elab_Flag (CW);
356          Append_To (CI, CW);
357       end Add_To_Context_And_Mark;
358
359       -----------------
360       -- In_Withs_Of --
361       -----------------
362
363       function In_Withs_Of (UEs : Entity_Id) return Boolean is
364          UNs : constant Unit_Number_Type := Get_Source_Unit (UEs);
365          CUs : constant Node_Id          := Cunit (UNs);
366          CIs : constant List_Id          := Context_Items (CUs);
367
368       begin
369          Itm := First (CIs);
370          while Present (Itm) loop
371             if Nkind (Itm) = N_With_Clause then
372                Ent :=
373                  Cunit_Entity (Get_Cunit_Unit_Number (Library_Unit (Itm)));
374
375                if U = Ent then
376                   return True;
377                end if;
378             end if;
379
380             Next (Itm);
381          end loop;
382
383          return False;
384       end In_Withs_Of;
385
386       -------------------
387       -- Set_Elab_Flag --
388       -------------------
389
390       procedure Set_Elab_Flag (Itm : Node_Id) is
391       begin
392          if Nkind (N) in N_Subprogram_Instantiation then
393             Set_Elaborate_Desirable (Itm);
394          else
395             Set_Elaborate_All_Desirable (Itm);
396          end if;
397       end Set_Elab_Flag;
398
399    --  Start of processing for Activate_Elaborate_All_Desirable
400
401    begin
402       --  Do not set binder indication if expansion is disabled, as when
403       --  compiling a generic unit.
404
405       if not Expander_Active then
406          return;
407       end if;
408
409       Itm := First (CI);
410       while Present (Itm) loop
411          if Nkind (Itm) = N_With_Clause then
412             Ent := Cunit_Entity (Get_Cunit_Unit_Number (Library_Unit (Itm)));
413
414             --  If we find it, then mark elaborate all desirable and return
415
416             if U = Ent then
417                Set_Elab_Flag (Itm);
418                return;
419             end if;
420          end if;
421
422          Next (Itm);
423       end loop;
424
425       --  If we fall through then the with clause is not present in the
426       --  current unit. One legitimate possibility is that the with clause
427       --  is present in the spec when we are a body.
428
429       if Is_Body_Name (Unm)
430         and then In_Withs_Of (Spec_Entity (UE))
431       then
432          Add_To_Context_And_Mark (Itm);
433          return;
434       end if;
435
436       --  Similarly, we may be in the spec or body of a child unit, where
437       --  the unit in question is with'ed by some ancestor of the child unit.
438
439       if Is_Child_Name (Unm) then
440          declare
441             Pkg : Entity_Id;
442
443          begin
444             Pkg := UE;
445             loop
446                Pkg := Scope (Pkg);
447                exit when Pkg = Standard_Standard;
448
449                if In_Withs_Of (Pkg) then
450                   Add_To_Context_And_Mark (Itm);
451                   return;
452                end if;
453             end loop;
454          end;
455       end if;
456
457       --  Here if we do not find with clause on spec or body. We just ignore
458       --  this case, it means that the elaboration involves some other unit
459       --  than the unit being compiled, and will be caught elsewhere.
460
461       null;
462    end Activate_Elaborate_All_Desirable;
463
464    ------------------
465    -- Check_A_Call --
466    ------------------
467
468    procedure Check_A_Call
469      (N                 : Node_Id;
470       E                 : Entity_Id;
471       Outer_Scope       : Entity_Id;
472       Inter_Unit_Only   : Boolean;
473       Generate_Warnings : Boolean := True)
474    is
475       Loc  : constant Source_Ptr := Sloc (N);
476       Ent  : Entity_Id;
477       Decl : Node_Id;
478
479       E_Scope : Entity_Id;
480       --  Top level scope of entity for called subprogram. This value includes
481       --  following renamings and derivations, so this scope can be in a
482       --  non-visible unit. This is the scope that is to be investigated to
483       --  see whether an elaboration check is required.
484
485       W_Scope : Entity_Id;
486       --  Top level scope of directly called entity for subprogram. This
487       --  differs from E_Scope in the case where renamings or derivations
488       --  are involved, since it does not follow these links. W_Scope is
489       --  generally in a visible unit, and it is this scope that may require
490       --  an Elaborate_All. However, there are some cases (initialization
491       --  calls and calls involving object notation) where W_Scope might not
492       --  be in the context of the current unit, and there is an intermediate
493       --  package that is, in which case the Elaborate_All has to be placed
494       --  on this intermediate package. These special cases are handled in
495       --  Set_Elaboration_Constraint.
496
497       Body_Acts_As_Spec : Boolean;
498       --  Set to true if call is to body acting as spec (no separate spec)
499
500       Inst_Case : constant Boolean := Nkind (N) in N_Generic_Instantiation;
501       --  Indicates if we have instantiation case
502
503       Caller_Unit_Internal : Boolean;
504       Callee_Unit_Internal : Boolean;
505
506       Inst_Caller : Source_Ptr;
507       Inst_Callee : Source_Ptr;
508
509       Unit_Caller : Unit_Number_Type;
510       Unit_Callee : Unit_Number_Type;
511
512       Cunit_SC : Boolean := False;
513       --  Set to suppress dynamic elaboration checks where one of the
514       --  enclosing scopes has Elaboration_Checks_Suppressed set, or else
515       --  if a pragma Elaborate (_All) applies to that scope, in which case
516       --  warnings on the scope are also suppressed. For the internal case,
517       --  we ignore this flag.
518
519    begin
520       --  If the call is known to be within a local Suppress Elaboration
521       --  pragma, nothing to check. This can happen in task bodies.
522
523       if (Nkind (N) = N_Function_Call
524            or else Nkind (N) = N_Procedure_Call_Statement)
525         and then No_Elaboration_Check (N)
526       then
527          return;
528       end if;
529
530       --  Go to parent for derived subprogram, or to original subprogram in the
531       --  case of a renaming (Alias covers both these cases).
532
533       Ent := E;
534       loop
535          if (Suppress_Elaboration_Warnings (Ent)
536               or else Elaboration_Checks_Suppressed (Ent))
537            and then (Inst_Case or else No (Alias (Ent)))
538          then
539             return;
540          end if;
541
542          --  Nothing to do for imported entities
543
544          if Is_Imported (Ent) then
545             return;
546          end if;
547
548          exit when Inst_Case or else No (Alias (Ent));
549          Ent := Alias (Ent);
550       end loop;
551
552       Decl := Unit_Declaration_Node (Ent);
553
554       if Nkind (Decl) = N_Subprogram_Body then
555          Body_Acts_As_Spec := True;
556
557       elsif Nkind (Decl) = N_Subprogram_Declaration
558         or else Nkind (Decl) = N_Subprogram_Body_Stub
559         or else Inst_Case
560       then
561          Body_Acts_As_Spec := False;
562
563       --  If we have none of an instantiation, subprogram body or
564       --  subprogram declaration, then it is not a case that we want
565       --  to check. (One case is a call to a generic formal subprogram,
566       --  where we do not want the check in the template).
567
568       else
569          return;
570       end if;
571
572       E_Scope := Ent;
573       loop
574          if Elaboration_Checks_Suppressed (E_Scope)
575            or else Suppress_Elaboration_Warnings (E_Scope)
576          then
577             Cunit_SC := True;
578          end if;
579
580          --  Exit when we get to compilation unit, not counting subunits
581
582          exit when Is_Compilation_Unit (E_Scope)
583            and then (Is_Child_Unit (E_Scope)
584                        or else Scope (E_Scope) = Standard_Standard);
585
586          --  If we did not find a compilation unit, other than standard,
587          --  then nothing to check (happens in some instantiation cases)
588
589          if E_Scope = Standard_Standard then
590             return;
591
592          --  Otherwise move up a scope looking for compilation unit
593
594          else
595             E_Scope := Scope (E_Scope);
596          end if;
597       end loop;
598
599       --  No checks needed for pure or preelaborated compilation units
600
601       if Is_Pure (E_Scope)
602         or else Is_Preelaborated (E_Scope)
603       then
604          return;
605       end if;
606
607       --  If the generic entity is within a deeper instance than we are, then
608       --  either the instantiation to which we refer itself caused an ABE, in
609       --  which case that will be handled separately, or else we know that the
610       --  body we need appears as needed at the point of the instantiation.
611       --  However, this assumption is only valid if we are in static mode.
612
613       if not Dynamic_Elaboration_Checks
614         and then Instantiation_Depth (Sloc (Ent)) >
615                  Instantiation_Depth (Sloc (N))
616       then
617          return;
618       end if;
619
620       --  Do not give a warning for a package with no body
621
622       if Ekind (Ent) = E_Generic_Package
623         and then not Has_Generic_Body (N)
624       then
625          return;
626       end if;
627
628       --  Case of entity is not in current unit (i.e. with'ed unit case)
629
630       if E_Scope /= C_Scope then
631
632          --  We are only interested in such calls if the outer call was from
633          --  elaboration code, or if we are in Dynamic_Elaboration_Checks mode.
634
635          if not From_Elab_Code and then not Dynamic_Elaboration_Checks then
636             return;
637          end if;
638
639          --  Nothing to do if some scope said that no checks were required
640
641          if Cunit_SC then
642             return;
643          end if;
644
645          --  Nothing to do for a generic instance, because in this case the
646          --  checking was at the point of instantiation of the generic However,
647          --  this shortcut is only applicable in static mode.
648
649          if Is_Generic_Instance (Ent) and not Dynamic_Elaboration_Checks then
650             return;
651          end if;
652
653          --  Nothing to do if subprogram with no separate spec. However, a
654          --  call to Deep_Initialize may result in a call to a user-defined
655          --  Initialize procedure, which imposes a body dependency. This
656          --  happens only if the type is controlled and the Initialize
657          --  procedure is not inherited.
658
659          if Body_Acts_As_Spec then
660             if Is_TSS (Ent, TSS_Deep_Initialize) then
661                declare
662                   Typ  : Entity_Id;
663                   Init : Entity_Id;
664                begin
665                   Typ  := Etype (Next_Formal (First_Formal (Ent)));
666
667                   if not Is_Controlled (Typ) then
668                      return;
669                   else
670                      Init := Find_Prim_Op (Typ, Name_Initialize);
671
672                      if Comes_From_Source (Init) then
673                         Ent := Init;
674                      else
675                         return;
676                      end if;
677                   end if;
678                end;
679
680             else
681                return;
682             end if;
683          end if;
684
685          --  Check cases of internal units
686
687          Callee_Unit_Internal :=
688            Is_Internal_File_Name
689              (Unit_File_Name (Get_Source_Unit (E_Scope)));
690
691          --  Do not give a warning if the with'ed unit is internal
692          --  and this is the generic instantiation case (this saves a
693          --  lot of hassle dealing with the Text_IO special child units)
694
695          if Callee_Unit_Internal and Inst_Case then
696             return;
697          end if;
698
699          if C_Scope = Standard_Standard then
700             Caller_Unit_Internal := False;
701          else
702             Caller_Unit_Internal :=
703               Is_Internal_File_Name
704                 (Unit_File_Name (Get_Source_Unit (C_Scope)));
705          end if;
706
707          --  Do not give a warning if the with'ed unit is internal
708          --  and the caller is not internal (since the binder always
709          --  elaborates internal units first).
710
711          if Callee_Unit_Internal and (not Caller_Unit_Internal) then
712             return;
713          end if;
714
715          --  For now, if debug flag -gnatdE is not set, do no checking for
716          --  one internal unit withing another. This fixes the problem with
717          --  the sgi build and storage errors. To be resolved later ???
718
719          if (Callee_Unit_Internal and Caller_Unit_Internal)
720             and then not Debug_Flag_EE
721          then
722             return;
723          end if;
724
725          if Is_TSS (E, TSS_Deep_Initialize) then
726             Ent := E;
727          end if;
728
729          --  If the call is in an instance, and the called entity is not
730          --  defined in the same instance, then the elaboration issue
731          --  focuses around the unit containing the template, it is
732          --  this unit which requires an Elaborate_All.
733
734          --  However, if we are doing dynamic elaboration, we need to
735          --  chase the call in the usual manner.
736
737          --  We do not handle the case of calling a generic formal correctly
738          --  in the static case. See test 4703-004 to explore this gap ???
739
740          Inst_Caller := Instantiation (Get_Source_File_Index (Sloc (N)));
741          Inst_Callee := Instantiation (Get_Source_File_Index (Sloc (Ent)));
742
743          if Inst_Caller = No_Location then
744             Unit_Caller := No_Unit;
745          else
746             Unit_Caller := Get_Source_Unit (N);
747          end if;
748
749          if Inst_Callee = No_Location then
750             Unit_Callee := No_Unit;
751          else
752             Unit_Callee := Get_Source_Unit (Ent);
753          end if;
754
755          if Unit_Caller /= No_Unit
756            and then Unit_Callee /= Unit_Caller
757            and then not Dynamic_Elaboration_Checks
758          then
759             E_Scope := Spec_Entity (Cunit_Entity (Unit_Caller));
760
761             --  If we don't get a spec entity, just ignore call. Not quite
762             --  clear why this check is necessary. ???
763
764             if No (E_Scope) then
765                return;
766             end if;
767
768             --  Otherwise step to enclosing compilation unit
769
770             while not Is_Compilation_Unit (E_Scope) loop
771                E_Scope := Scope (E_Scope);
772             end loop;
773
774          --  For the case N is not an instance, or a call within instance, we
775          --  recompute E_Scope for the error message, since we do NOT want to
776          --  go to the unit which has the ultimate declaration in the case of
777          --  renaming and derivation and we also want to go to the generic unit
778          --  in the case of an instance, and no further.
779
780          else
781             --  Loop to carefully follow renamings and derivations one step
782             --  outside the current unit, but not further.
783
784             if not Inst_Case
785               and then Present (Alias (Ent))
786             then
787                E_Scope := Alias (Ent);
788             else
789                E_Scope := Ent;
790             end if;
791
792             loop
793                while not Is_Compilation_Unit (E_Scope) loop
794                   E_Scope := Scope (E_Scope);
795                end loop;
796
797                --  If E_Scope is the same as C_Scope, it means that there
798                --  definitely was a local renaming or derivation, and we
799                --  are not yet out of the current unit.
800
801                exit when E_Scope /= C_Scope;
802                Ent := Alias (Ent);
803                E_Scope := Ent;
804
805                --  If no alias, there is a previous error
806
807                if No (Ent) then
808                   return;
809                end if;
810             end loop;
811          end if;
812
813          if Within_Elaborate_All (E_Scope) then
814             return;
815          end if;
816
817          --  Find top level scope for called entity (not following renamings
818          --  or derivations). This is where the Elaborate_All will go if it
819          --  is needed. We start with the called entity, except in the case
820          --  of an initialization procedure outside the current package, where
821          --  the init proc is in the root package, and we start from the entity
822          --  of the name in the call.
823
824          if Is_Entity_Name (Name (N))
825            and then Is_Init_Proc (Entity (Name (N)))
826            and then not In_Same_Extended_Unit (N, Entity (Name (N)))
827          then
828             W_Scope := Scope (Entity (Name (N)));
829          else
830             W_Scope := E;
831          end if;
832
833          while not Is_Compilation_Unit (W_Scope) loop
834             W_Scope := Scope (W_Scope);
835          end loop;
836
837          --  Now check if an elaborate_all (or dynamic check) is needed
838
839          if not Suppress_Elaboration_Warnings (Ent)
840            and then not Elaboration_Checks_Suppressed (Ent)
841            and then not Suppress_Elaboration_Warnings (E_Scope)
842            and then not Elaboration_Checks_Suppressed (E_Scope)
843            and then Elab_Warnings
844            and then Generate_Warnings
845          then
846             Generate_Elab_Warnings : declare
847                procedure Elab_Warning
848                  (Msg_D : String;
849                   Msg_S : String;
850                   Ent   : Node_Or_Entity_Id);
851                --  Generate a call to Error_Msg_NE with parameters Msg_D or
852                --  Msg_S (for dynamic or static elaboration model), N and Ent.
853
854                ------------------
855                -- Elab_Warning --
856                ------------------
857
858                procedure Elab_Warning
859                  (Msg_D : String;
860                   Msg_S : String;
861                   Ent   : Node_Or_Entity_Id)
862                is
863                begin
864                   if Dynamic_Elaboration_Checks then
865                      Error_Msg_NE (Msg_D, N, Ent);
866                   else
867                      Error_Msg_NE (Msg_S, N, Ent);
868                   end if;
869                end Elab_Warning;
870
871             --  Start of processing for Generate_Elab_Warnings
872
873             begin
874                if Inst_Case then
875                   Elab_Warning
876                     ("instantiation of& may raise Program_Error?",
877                      "info: instantiation of& during elaboration?", Ent);
878
879                else
880                   if Nkind (Name (N)) in N_Has_Entity
881                     and then Is_Init_Proc (Entity (Name (N)))
882                     and then Comes_From_Source (Ent)
883                   then
884                      Elab_Warning
885                        ("implicit call to & may raise Program_Error?",
886                         "info: implicit call to & during elaboration?",
887                         Ent);
888
889                   else
890                      Elab_Warning
891                        ("call to & may raise Program_Error?",
892                         "info: call to & during elaboration?",
893                         Ent);
894                   end if;
895                end if;
896
897                Error_Msg_Qual_Level := Nat'Last;
898
899                if Nkind (N) in N_Subprogram_Instantiation then
900                   Elab_Warning
901                     ("\missing pragma Elaborate for&?",
902                      "\info: implicit pragma Elaborate for& generated?",
903                      W_Scope);
904                else
905                   Elab_Warning
906                     ("\missing pragma Elaborate_All for&?",
907                      "\info: implicit pragma Elaborate_All for & generated?",
908                      W_Scope);
909                end if;
910             end Generate_Elab_Warnings;
911
912             Error_Msg_Qual_Level := 0;
913             Output_Calls (N);
914
915             --  Set flag to prevent further warnings for same unit unless in
916             --  All_Errors_Mode.
917
918             if not All_Errors_Mode and not Dynamic_Elaboration_Checks then
919                Set_Suppress_Elaboration_Warnings (W_Scope, True);
920             end if;
921          end if;
922
923          --  Check for runtime elaboration check required
924
925          if Dynamic_Elaboration_Checks then
926             if not Elaboration_Checks_Suppressed (Ent)
927               and then not Elaboration_Checks_Suppressed (W_Scope)
928               and then not Elaboration_Checks_Suppressed (E_Scope)
929               and then not Cunit_SC
930             then
931                --  Runtime elaboration check required. Generate check of the
932                --  elaboration Boolean for the unit containing the entity.
933
934                --  Note that for this case, we do check the real unit (the one
935                --  from following renamings, since that is the issue!)
936
937                --  Could this possibly miss a useless but required PE???
938
939                Insert_Elab_Check (N,
940                  Make_Attribute_Reference (Loc,
941                    Attribute_Name => Name_Elaborated,
942                    Prefix =>
943                      New_Occurrence_Of
944                        (Spec_Entity (E_Scope), Loc)));
945             end if;
946
947          --  Case of static elaboration model
948
949          else
950             --  Do not do anything if elaboration checks suppressed. Note that
951             --  we check Ent here, not E, since we want the real entity for the
952             --  body to see if checks are suppressed for it, not the dummy
953             --  entry for renamings or derivations.
954
955             if Elaboration_Checks_Suppressed (Ent)
956               or else Elaboration_Checks_Suppressed (E_Scope)
957               or else Elaboration_Checks_Suppressed (W_Scope)
958             then
959                null;
960
961             --  Here we need to generate an implicit elaborate all
962
963             else
964                --  Generate elaborate_all warning unless suppressed
965
966                if (Elab_Warnings and Generate_Warnings and not Inst_Case)
967                  and then not Suppress_Elaboration_Warnings (Ent)
968                  and then not Suppress_Elaboration_Warnings (E_Scope)
969                  and then not Suppress_Elaboration_Warnings (W_Scope)
970                then
971                   Error_Msg_Node_2 := W_Scope;
972                   Error_Msg_NE
973                     ("call to& in elaboration code " &
974                      "requires pragma Elaborate_All on&?", N, E);
975                end if;
976
977                --  Set indication for binder to generate Elaborate_All
978
979                Set_Elaboration_Constraint (N, E, W_Scope);
980             end if;
981          end if;
982
983       --  Case of entity is in same unit as call or instantiation
984
985       elsif not Inter_Unit_Only then
986          Check_Internal_Call (N, Ent, Outer_Scope, E);
987       end if;
988    end Check_A_Call;
989
990    -----------------------------
991    -- Check_Bad_Instantiation --
992    -----------------------------
993
994    procedure Check_Bad_Instantiation (N : Node_Id) is
995       Ent : Entity_Id;
996
997    begin
998       --  Nothing to do if we do not have an instantiation (happens in some
999       --  error cases, and also in the formal package declaration case)
1000
1001       if Nkind (N) not in N_Generic_Instantiation then
1002          return;
1003
1004       --  Nothing to do if serious errors detected (avoid cascaded errors)
1005
1006       elsif Serious_Errors_Detected /= 0 then
1007          return;
1008
1009       --  Nothing to do if not in full analysis mode
1010
1011       elsif not Full_Analysis then
1012          return;
1013
1014       --  Nothing to do if inside a generic template
1015
1016       elsif Inside_A_Generic then
1017          return;
1018
1019       --  Nothing to do if a library level instantiation
1020
1021       elsif Nkind (Parent (N)) = N_Compilation_Unit then
1022          return;
1023
1024       --  Nothing to do if we are compiling a proper body for semantic
1025       --  purposes only. The generic body may be in another proper body.
1026
1027       elsif
1028         Nkind (Parent (Unit_Declaration_Node (Main_Unit_Entity))) = N_Subunit
1029       then
1030          return;
1031       end if;
1032
1033       Ent := Get_Generic_Entity (N);
1034
1035       --  The case we are interested in is when the generic spec is in the
1036       --  current declarative part
1037
1038       if not Same_Elaboration_Scope (Current_Scope, Scope (Ent))
1039         or else not In_Same_Extended_Unit (N, Ent)
1040       then
1041          return;
1042       end if;
1043
1044       --  If the generic entity is within a deeper instance than we are, then
1045       --  either the instantiation to which we refer itself caused an ABE, in
1046       --  which case that will be handled separately. Otherwise, we know that
1047       --  the body we need appears as needed at the point of the instantiation.
1048       --  If they are both at the same level but not within the same instance
1049       --  then the body of the generic will be in the earlier instance.
1050
1051       declare
1052          D1 : constant Int := Instantiation_Depth (Sloc (Ent));
1053          D2 : constant Int := Instantiation_Depth (Sloc (N));
1054
1055       begin
1056          if D1 > D2 then
1057             return;
1058
1059          elsif D1 = D2
1060            and then Is_Generic_Instance (Scope (Ent))
1061            and then not In_Open_Scopes (Scope (Ent))
1062          then
1063             return;
1064          end if;
1065       end;
1066
1067       --  Now we can proceed, if the entity being called has a completion,
1068       --  then we are definitely OK, since we have already seen the body.
1069
1070       if Has_Completion (Ent) then
1071          return;
1072       end if;
1073
1074       --  If there is no body, then nothing to do
1075
1076       if not Has_Generic_Body (N) then
1077          return;
1078       end if;
1079
1080       --  Here we definitely have a bad instantiation
1081
1082       Error_Msg_NE
1083         ("?cannot instantiate& before body seen", N, Ent);
1084
1085       if Present (Instance_Spec (N)) then
1086          Supply_Bodies (Instance_Spec (N));
1087       end if;
1088
1089       Error_Msg_N
1090         ("\?Program_Error will be raised at run time", N);
1091       Insert_Elab_Check (N);
1092       Set_ABE_Is_Certain (N);
1093    end Check_Bad_Instantiation;
1094
1095    ---------------------
1096    -- Check_Elab_Call --
1097    ---------------------
1098
1099    procedure Check_Elab_Call
1100      (N           : Node_Id;
1101       Outer_Scope : Entity_Id := Empty)
1102    is
1103       Ent : Entity_Id;
1104       P   : Node_Id;
1105
1106       function Get_Called_Ent return Entity_Id;
1107       --  Retrieve called entity. If this is a call to a protected subprogram,
1108       --  entity is a selected component. The callable entity may be absent,
1109       --  in which case there is no check to perform. This happens with
1110       --  non-analyzed calls in nested generics.
1111
1112       --------------------
1113       -- Get_Called_Ent --
1114       --------------------
1115
1116       function Get_Called_Ent return Entity_Id is
1117          Nam : Node_Id;
1118
1119       begin
1120          Nam := Name (N);
1121
1122          if No (Nam) then
1123             return Empty;
1124
1125          elsif Nkind (Nam) = N_Selected_Component then
1126             return Entity (Selector_Name (Nam));
1127
1128          elsif not Is_Entity_Name (Nam) then
1129             return Empty;
1130
1131          else
1132             return Entity (Nam);
1133          end if;
1134       end Get_Called_Ent;
1135
1136    --  Start of processing for Check_Elab_Call
1137
1138    begin
1139       --  If the call does not come from the main unit, there is nothing to
1140       --  check. Elaboration call from units in the context of the main unit
1141       --  will lead to semantic dependencies when those units are compiled.
1142
1143       if not In_Extended_Main_Code_Unit (N) then
1144          return;
1145       end if;
1146
1147       --  For an entry call, check relevant restriction
1148
1149       if Nkind (N) = N_Entry_Call_Statement
1150          and then not In_Subprogram_Or_Concurrent_Unit
1151       then
1152          Check_Restriction (No_Entry_Calls_In_Elaboration_Code, N);
1153
1154       --  Nothing to do if this is not a call (happens in some error
1155       --  conditions, and in some cases where rewriting occurs).
1156
1157       elsif Nkind (N) /= N_Function_Call
1158         and then Nkind (N) /= N_Procedure_Call_Statement
1159       then
1160          return;
1161
1162       --  Nothing to do if this is a call already rewritten for elab checking
1163
1164       elsif Nkind (Parent (N)) = N_Conditional_Expression then
1165          return;
1166
1167       --  Nothing to do if inside a generic template
1168
1169       elsif Inside_A_Generic
1170         and then No (Enclosing_Generic_Body (N))
1171       then
1172          return;
1173       end if;
1174
1175       --  Here we have a call at elaboration time which must be checked
1176
1177       if Debug_Flag_LL then
1178          Write_Str ("  Check_Elab_Call: ");
1179
1180          if No (Name (N))
1181            or else not Is_Entity_Name (Name (N))
1182          then
1183             Write_Str ("<<not entity name>> ");
1184          else
1185             Write_Name (Chars (Entity (Name (N))));
1186          end if;
1187
1188          Write_Str ("  call at ");
1189          Write_Location (Sloc (N));
1190          Write_Eol;
1191       end if;
1192
1193       --  Climb up the tree to make sure we are not inside default expression
1194       --  of a parameter specification or a record component, since in both
1195       --  these cases, we will be doing the actual call later, not now, and it
1196       --  is at the time of the actual call (statically speaking) that we must
1197       --  do our static check, not at the time of its initial analysis).
1198
1199       --  However, we have to check calls within component definitions (e.g.
1200       --  a function call that determines an array component bound), so we
1201       --  terminate the loop in that case.
1202
1203       P := Parent (N);
1204       while Present (P) loop
1205          if Nkind (P) = N_Parameter_Specification
1206               or else
1207             Nkind (P) = N_Component_Declaration
1208          then
1209             return;
1210
1211          --  The call occurs within the constraint of a component,
1212          --  so it must be checked.
1213
1214          elsif Nkind (P) = N_Component_Definition then
1215             exit;
1216
1217          else
1218             P := Parent (P);
1219          end if;
1220       end loop;
1221
1222       --  Stuff that happens only at the outer level
1223
1224       if No (Outer_Scope) then
1225          Elab_Visited.Set_Last (0);
1226
1227          --  Nothing to do if current scope is Standard (this is a bit odd, but
1228          --  it happens in the case of generic instantiations).
1229
1230          C_Scope := Current_Scope;
1231
1232          if C_Scope = Standard_Standard then
1233             return;
1234          end if;
1235
1236          --  First case, we are in elaboration code
1237
1238          From_Elab_Code := not In_Subprogram_Or_Concurrent_Unit;
1239          if From_Elab_Code then
1240
1241             --  Complain if call that comes from source in preelaborated unit
1242             --  and we are not inside a subprogram (i.e. we are in elab code).
1243
1244             if Comes_From_Source (N)
1245               and then In_Preelaborated_Unit
1246               and then not In_Inlined_Body
1247             then
1248                --  This is a warning in GNAT mode allowing such calls to be
1249                --  used in the predefined library with appropriate care.
1250
1251                Error_Msg_Warn := GNAT_Mode;
1252                Error_Msg_N
1253                  ("<non-static call not allowed in preelaborated unit", N);
1254                return;
1255             end if;
1256
1257          --  Second case, we are inside a subprogram or concurrent unit, which
1258          --  means we are not in elaboration code.
1259
1260          else
1261             --  In this case, the issue is whether we are inside the
1262             --  declarative part of the unit in which we live, or inside its
1263             --  statements. In the latter case, there is no issue of ABE calls
1264             --  at this level (a call from outside to the unit in which we live
1265             --  might cause an ABE, but that will be detected when we analyze
1266             --  that outer level call, as it recurses into the called unit).
1267
1268             --  Climb up the tree, doing this test, and also testing for being
1269             --  inside a default expression, which, as discussed above, is not
1270             --  checked at this stage.
1271
1272             declare
1273                P : Node_Id;
1274                L : List_Id;
1275
1276             begin
1277                P := N;
1278                loop
1279                   --  If we find a parentless subtree, it seems safe to assume
1280                   --  that we are not in a declarative part and that no
1281                   --  checking is required.
1282
1283                   if No (P) then
1284                      return;
1285                   end if;
1286
1287                   if Is_List_Member (P) then
1288                      L := List_Containing (P);
1289                      P := Parent (L);
1290                   else
1291                      L := No_List;
1292                      P := Parent (P);
1293                   end if;
1294
1295                   exit when Nkind (P) = N_Subunit;
1296
1297                   --  Filter out case of default expressions, where we do not
1298                   --  do the check at this stage.
1299
1300                   if Nkind (P) = N_Parameter_Specification
1301                        or else
1302                      Nkind (P) = N_Component_Declaration
1303                   then
1304                      return;
1305                   end if;
1306
1307                   --  A protected body has no elaboration code and contains
1308                   --  only other bodies.
1309
1310                   if Nkind (P) = N_Protected_Body then
1311                      return;
1312
1313                   elsif Nkind (P) = N_Subprogram_Body
1314                        or else
1315                      Nkind (P) = N_Task_Body
1316                        or else
1317                      Nkind (P) = N_Block_Statement
1318                        or else
1319                      Nkind (P) = N_Entry_Body
1320                   then
1321                      if L = Declarations (P) then
1322                         exit;
1323
1324                      --  We are not in elaboration code, but we are doing
1325                      --  dynamic elaboration checks, in this case, we still
1326                      --  need to do the call, since the subprogram we are in
1327                      --  could be called from another unit, also in dynamic
1328                      --  elaboration check mode, at elaboration time.
1329
1330                      elsif Dynamic_Elaboration_Checks then
1331
1332                         --  This is a rather new check, going into version
1333                         --  3.14a1 for the first time (V1.80 of this unit), so
1334                         --  we provide a debug flag to enable it. That way we
1335                         --  have an easy work around for regressions that are
1336                         --  caused by this new check. This debug flag can be
1337                         --  removed later.
1338
1339                         if Debug_Flag_DD then
1340                            return;
1341                         end if;
1342
1343                         --  Do the check in this case
1344
1345                         exit;
1346
1347                      elsif Nkind (P) = N_Task_Body then
1348
1349                         --  The check is deferred until Check_Task_Activation
1350                         --  but we need to capture local suppress pragmas
1351                         --  that may inhibit checks on this call.
1352
1353                         Ent := Get_Called_Ent;
1354
1355                         if No (Ent) then
1356                            return;
1357
1358                         elsif Elaboration_Checks_Suppressed (Current_Scope)
1359                           or else Elaboration_Checks_Suppressed (Ent)
1360                           or else Elaboration_Checks_Suppressed (Scope (Ent))
1361                         then
1362                            Set_No_Elaboration_Check (N);
1363                         end if;
1364
1365                         return;
1366
1367                      --  Static model, call is not in elaboration code, we
1368                      --  never need to worry, because in the static model the
1369                      --  top level caller always takes care of things.
1370
1371                      else
1372                         return;
1373                      end if;
1374                   end if;
1375                end loop;
1376             end;
1377          end if;
1378       end if;
1379
1380       Ent := Get_Called_Ent;
1381
1382       if No (Ent) then
1383          return;
1384       end if;
1385
1386       --  Nothing to do if this is a recursive call (i.e. a call to
1387       --  an entity that is already in the Elab_Call stack)
1388
1389       for J in 1 .. Elab_Visited.Last loop
1390          if Ent = Elab_Visited.Table (J) then
1391             return;
1392          end if;
1393       end loop;
1394
1395       --  See if we need to analyze this call. We analyze it if either of
1396       --  the following conditions is met:
1397
1398       --    It is an inner level call (since in this case it was triggered
1399       --    by an outer level call from elaboration code), but only if the
1400       --    call is within the scope of the original outer level call.
1401
1402       --    It is an outer level call from elaboration code, or the called
1403       --    entity is in the same elaboration scope.
1404
1405       --  And in these cases, we will check both inter-unit calls and
1406       --  intra-unit (within a single unit) calls.
1407
1408       C_Scope := Current_Scope;
1409
1410       --  If not outer level call, then we follow it if it is within
1411       --  the original scope of the outer call.
1412
1413       if Present (Outer_Scope)
1414         and then Within (Scope (Ent), Outer_Scope)
1415       then
1416          Set_C_Scope;
1417          Check_A_Call (N, Ent, Outer_Scope, Inter_Unit_Only => False);
1418
1419       elsif Elaboration_Checks_Suppressed (Current_Scope) then
1420          null;
1421
1422       elsif From_Elab_Code then
1423          Set_C_Scope;
1424          Check_A_Call (N, Ent, Standard_Standard, Inter_Unit_Only => False);
1425
1426       elsif Same_Elaboration_Scope (C_Scope, Scope (Ent)) then
1427          Set_C_Scope;
1428          Check_A_Call (N, Ent, Scope (Ent), Inter_Unit_Only => False);
1429
1430       --  If none of those cases holds, but Dynamic_Elaboration_Checks mode
1431       --  is set, then we will do the check, but only in the inter-unit case
1432       --  (this is to accommodate unguarded elaboration calls from other units
1433       --  in which this same mode is set). We don't want warnings in this case,
1434       --  it would generate warnings having nothing to do with elaboration.
1435
1436       elsif Dynamic_Elaboration_Checks then
1437          Set_C_Scope;
1438          Check_A_Call
1439            (N,
1440             Ent,
1441             Standard_Standard,
1442             Inter_Unit_Only => True,
1443             Generate_Warnings => False);
1444
1445       --  Otherwise nothing to do
1446
1447       else
1448          return;
1449       end if;
1450
1451       --  A call to an Init_Proc in elaboration code may bring additional
1452       --  dependencies, if some of the record components thereof have
1453       --  initializations that are function calls that come from source. We
1454       --  treat the current node as a call to each of these functions, to check
1455       --  their elaboration impact.
1456
1457       if Is_Init_Proc (Ent)
1458         and then From_Elab_Code
1459       then
1460          Process_Init_Proc : declare
1461             Unit_Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1462
1463             function Find_Init_Call (Nod : Node_Id) return Traverse_Result;
1464             --  Find subprogram calls within body of Init_Proc for Traverse
1465             --  instantiation below.
1466
1467             procedure Traverse_Body is new Traverse_Proc (Find_Init_Call);
1468             --  Traversal procedure to find all calls with body of Init_Proc
1469
1470             --------------------
1471             -- Find_Init_Call --
1472             --------------------
1473
1474             function Find_Init_Call (Nod : Node_Id) return Traverse_Result is
1475                Func : Entity_Id;
1476
1477             begin
1478                if (Nkind (Nod) = N_Function_Call
1479                     or else Nkind (Nod) = N_Procedure_Call_Statement)
1480                  and then Is_Entity_Name (Name (Nod))
1481                then
1482                   Func := Entity (Name (Nod));
1483
1484                   if Comes_From_Source (Func) then
1485                      Check_A_Call
1486                        (N, Func, Standard_Standard, Inter_Unit_Only => True);
1487                   end if;
1488
1489                   return OK;
1490
1491                else
1492                   return OK;
1493                end if;
1494             end Find_Init_Call;
1495
1496          --  Start of processing for Process_Init_Proc
1497
1498          begin
1499             if Nkind (Unit_Decl) = N_Subprogram_Body then
1500                Traverse_Body (Handled_Statement_Sequence (Unit_Decl));
1501             end if;
1502          end Process_Init_Proc;
1503       end if;
1504    end Check_Elab_Call;
1505
1506    -----------------------
1507    -- Check_Elab_Assign --
1508    -----------------------
1509
1510    procedure Check_Elab_Assign (N : Node_Id) is
1511       Ent  : Entity_Id;
1512       Scop : Entity_Id;
1513
1514       Pkg_Spec : Entity_Id;
1515       Pkg_Body : Entity_Id;
1516
1517    begin
1518       --  For record or array component, check prefix. If it is an access type,
1519       --  then there is nothing to do (we do not know what is being assigned),
1520       --  but otherwise this is an assignment to the prefix.
1521
1522       if Nkind (N) = N_Indexed_Component
1523            or else
1524          Nkind (N) = N_Selected_Component
1525            or else
1526          Nkind (N) = N_Slice
1527       then
1528          if not Is_Access_Type (Etype (Prefix (N))) then
1529             Check_Elab_Assign (Prefix (N));
1530          end if;
1531
1532          return;
1533       end if;
1534
1535       --  For type conversion, check expression
1536
1537       if Nkind (N) = N_Type_Conversion then
1538          Check_Elab_Assign (Expression (N));
1539          return;
1540       end if;
1541
1542       --  Nothing to do if this is not an entity reference otherwise get entity
1543
1544       if Is_Entity_Name (N) then
1545          Ent := Entity (N);
1546       else
1547          return;
1548       end if;
1549
1550       --  What we are looking for is a reference in the body of a package that
1551       --  modifies a variable declared in the visible part of the package spec.
1552
1553       if Present (Ent)
1554         and then Comes_From_Source (N)
1555         and then not Suppress_Elaboration_Warnings (Ent)
1556         and then Ekind (Ent) = E_Variable
1557         and then not In_Private_Part (Ent)
1558         and then Is_Library_Level_Entity (Ent)
1559       then
1560          Scop := Current_Scope;
1561          loop
1562             if No (Scop) or else Scop = Standard_Standard then
1563                return;
1564             elsif Ekind (Scop) = E_Package
1565               and then Is_Compilation_Unit (Scop)
1566             then
1567                exit;
1568             else
1569                Scop := Scope (Scop);
1570             end if;
1571          end loop;
1572
1573          --  Here Scop points to the containing library package
1574
1575          Pkg_Spec := Scop;
1576          Pkg_Body := Body_Entity (Pkg_Spec);
1577
1578          --  All OK if the package has an Elaborate_Body pragma
1579
1580          if Has_Pragma_Elaborate_Body (Scop) then
1581             return;
1582          end if;
1583
1584          --  OK if entity being modified is not in containing package spec
1585
1586          if not In_Same_Source_Unit (Scop, Ent) then
1587             return;
1588          end if;
1589
1590          --  All OK if entity appears in generic package or generic instance.
1591          --  We just get too messed up trying to give proper warnings in the
1592          --  presence of generics. Better no message than a junk one.
1593
1594          Scop := Scope (Ent);
1595          while Present (Scop) and then Scop /= Pkg_Spec loop
1596             if Ekind (Scop) = E_Generic_Package then
1597                return;
1598             elsif Ekind (Scop) = E_Package
1599               and then Is_Generic_Instance (Scop)
1600             then
1601                return;
1602             end if;
1603
1604             Scop := Scope (Scop);
1605          end loop;
1606
1607          --  All OK if in task, don't issue warnings there
1608
1609          if In_Task_Activation then
1610             return;
1611          end if;
1612
1613          --  OK if no package body
1614
1615          if No (Pkg_Body) then
1616             return;
1617          end if;
1618
1619          --  OK if reference is not in package body
1620
1621          if not In_Same_Source_Unit (Pkg_Body, N) then
1622             return;
1623          end if;
1624
1625          --  OK if package body has no handled statement sequence
1626
1627          declare
1628             HSS : constant Node_Id :=
1629                     Handled_Statement_Sequence (Declaration_Node (Pkg_Body));
1630          begin
1631             if No (HSS) or else not Comes_From_Source (HSS) then
1632                return;
1633             end if;
1634          end;
1635
1636          --  We definitely have a case of a modification of an entity in
1637          --  the package spec from the elaboration code of the package body.
1638          --  We may not give the warning (because there are some additional
1639          --  checks to avoid too many false positives), but it would be a good
1640          --  idea for the binder to try to keep the body elaboration close to
1641          --  the spec elaboration.
1642
1643          Set_Elaborate_Body_Desirable (Pkg_Spec);
1644
1645          --  All OK in gnat mode (we know what we are doing)
1646
1647          if GNAT_Mode then
1648             return;
1649          end if;
1650
1651          --  All OK if all warnings suppressed
1652
1653          if Warning_Mode = Suppress then
1654             return;
1655          end if;
1656
1657          --  All OK if elaboration checks suppressed for entity
1658
1659          if Checks_May_Be_Suppressed (Ent)
1660            and then Is_Check_Suppressed (Ent, Elaboration_Check)
1661          then
1662             return;
1663          end if;
1664
1665          --  OK if the entity is initialized. Note that the No_Initialization
1666          --  flag usually means that the initialization has been rewritten into
1667          --  assignments, but that still counts for us.
1668
1669          declare
1670             Decl : constant Node_Id := Declaration_Node (Ent);
1671          begin
1672             if Nkind (Decl) = N_Object_Declaration
1673               and then (Present (Expression (Decl))
1674                           or else No_Initialization (Decl))
1675             then
1676                return;
1677             end if;
1678          end;
1679
1680          --  Here is where we give the warning
1681
1682                   --  All OK if warnings suppressed on the entity
1683
1684          if not Has_Warnings_Off (Ent) then
1685             Error_Msg_Sloc := Sloc (Ent);
1686
1687             Error_Msg_NE
1688               ("?elaboration code may access& before it is initialized",
1689                N, Ent);
1690             Error_Msg_NE
1691               ("\?suggest adding pragma Elaborate_Body to spec of &",
1692                N, Scop);
1693             Error_Msg_N
1694               ("\?or an explicit initialization could be added #", N);
1695          end if;
1696
1697          if not All_Errors_Mode then
1698             Set_Suppress_Elaboration_Warnings (Ent);
1699          end if;
1700       end if;
1701    end Check_Elab_Assign;
1702
1703    ----------------------
1704    -- Check_Elab_Calls --
1705    ----------------------
1706
1707    procedure Check_Elab_Calls is
1708    begin
1709       --  If expansion is disabled, do not generate any checks. Also skip
1710       --  checks if any subunits are missing because in either case we lack the
1711       --  full information that we need, and no object file will be created in
1712       --  any case.
1713
1714       if not Expander_Active
1715         or else Is_Generic_Unit (Cunit_Entity (Main_Unit))
1716         or else Subunits_Missing
1717       then
1718          return;
1719       end if;
1720
1721       --  Skip delayed calls if we had any errors
1722
1723       if Serious_Errors_Detected = 0 then
1724          Delaying_Elab_Checks := False;
1725          Expander_Mode_Save_And_Set (True);
1726
1727          for J in Delay_Check.First .. Delay_Check.Last loop
1728             Push_Scope (Delay_Check.Table (J).Curscop);
1729             From_Elab_Code := Delay_Check.Table (J).From_Elab_Code;
1730
1731             Check_Internal_Call_Continue (
1732               N           => Delay_Check.Table (J).N,
1733               E           => Delay_Check.Table (J).E,
1734               Outer_Scope => Delay_Check.Table (J).Outer_Scope,
1735               Orig_Ent    => Delay_Check.Table (J).Orig_Ent);
1736
1737             Pop_Scope;
1738          end loop;
1739
1740          --  Set Delaying_Elab_Checks back on for next main compilation
1741
1742          Expander_Mode_Restore;
1743          Delaying_Elab_Checks := True;
1744       end if;
1745    end Check_Elab_Calls;
1746
1747    ------------------------------
1748    -- Check_Elab_Instantiation --
1749    ------------------------------
1750
1751    procedure Check_Elab_Instantiation
1752      (N           : Node_Id;
1753       Outer_Scope : Entity_Id := Empty)
1754    is
1755       Ent : Entity_Id;
1756
1757    begin
1758       --  Check for and deal with bad instantiation case. There is some
1759       --  duplicated code here, but we will worry about this later ???
1760
1761       Check_Bad_Instantiation (N);
1762
1763       if ABE_Is_Certain (N) then
1764          return;
1765       end if;
1766
1767       --  Nothing to do if we do not have an instantiation (happens in some
1768       --  error cases, and also in the formal package declaration case)
1769
1770       if Nkind (N) not in N_Generic_Instantiation then
1771          return;
1772       end if;
1773
1774       --  Nothing to do if inside a generic template
1775
1776       if Inside_A_Generic then
1777          return;
1778       end if;
1779
1780       --  Nothing to do if the instantiation is not in the main unit
1781
1782       if not In_Extended_Main_Code_Unit (N) then
1783          return;
1784       end if;
1785
1786       Ent := Get_Generic_Entity (N);
1787       From_Elab_Code := not In_Subprogram_Or_Concurrent_Unit;
1788
1789       --  See if we need to analyze this instantiation. We analyze it if
1790       --  either of the following conditions is met:
1791
1792       --    It is an inner level instantiation (since in this case it was
1793       --    triggered by an outer level call from elaboration code), but
1794       --    only if the instantiation is within the scope of the original
1795       --    outer level call.
1796
1797       --    It is an outer level instantiation from elaboration code, or the
1798       --    instantiated entity is in the same elaboration scope.
1799
1800       --  And in these cases, we will check both the inter-unit case and
1801       --  the intra-unit (within a single unit) case.
1802
1803       C_Scope := Current_Scope;
1804
1805       if Present (Outer_Scope)
1806         and then Within (Scope (Ent), Outer_Scope)
1807       then
1808          Set_C_Scope;
1809          Check_A_Call (N, Ent, Outer_Scope, Inter_Unit_Only => False);
1810
1811       elsif From_Elab_Code then
1812          Set_C_Scope;
1813          Check_A_Call (N, Ent, Standard_Standard, Inter_Unit_Only => False);
1814
1815       elsif Same_Elaboration_Scope (C_Scope, Scope (Ent)) then
1816          Set_C_Scope;
1817          Check_A_Call (N, Ent, Scope (Ent), Inter_Unit_Only => False);
1818
1819       --  If none of those cases holds, but Dynamic_Elaboration_Checks mode is
1820       --  set, then we will do the check, but only in the inter-unit case (this
1821       --  is to accommodate unguarded elaboration calls from other units in
1822       --  which this same mode is set). We inhibit warnings in this case, since
1823       --  this instantiation is not occurring in elaboration code.
1824
1825       elsif Dynamic_Elaboration_Checks then
1826          Set_C_Scope;
1827          Check_A_Call
1828            (N,
1829             Ent,
1830             Standard_Standard,
1831             Inter_Unit_Only => True,
1832             Generate_Warnings => False);
1833
1834       else
1835          return;
1836       end if;
1837    end Check_Elab_Instantiation;
1838
1839    -------------------------
1840    -- Check_Internal_Call --
1841    -------------------------
1842
1843    procedure Check_Internal_Call
1844      (N           : Node_Id;
1845       E           : Entity_Id;
1846       Outer_Scope : Entity_Id;
1847       Orig_Ent    : Entity_Id)
1848    is
1849       Inst_Case : constant Boolean := Nkind (N) in N_Generic_Instantiation;
1850
1851    begin
1852       --  If not function or procedure call or instantiation, then ignore
1853       --  call (this happens in some error case and rewriting cases)
1854
1855       if Nkind (N) /= N_Function_Call
1856            and then
1857          Nkind (N) /= N_Procedure_Call_Statement
1858            and then
1859          not Inst_Case
1860       then
1861          return;
1862
1863       --  Nothing to do if this is a call or instantiation that has
1864       --  already been found to be a sure ABE
1865
1866       elsif ABE_Is_Certain (N) then
1867          return;
1868
1869       --  Nothing to do if errors already detected (avoid cascaded errors)
1870
1871       elsif Serious_Errors_Detected /= 0 then
1872          return;
1873
1874       --  Nothing to do if not in full analysis mode
1875
1876       elsif not Full_Analysis then
1877          return;
1878
1879       --  Nothing to do if analyzing in special spec-expression mode, since the
1880       --  call is not actually being made at this time.
1881
1882       elsif In_Spec_Expression then
1883          return;
1884
1885       --  Nothing to do for call to intrinsic subprogram
1886
1887       elsif Is_Intrinsic_Subprogram (E) then
1888          return;
1889
1890       --  No need to trace local calls if checking task activation, because
1891       --  other local bodies are elaborated already.
1892
1893       elsif In_Task_Activation then
1894          return;
1895       end if;
1896
1897       --  Delay this call if we are still delaying calls
1898
1899       if Delaying_Elab_Checks then
1900          Delay_Check.Append (
1901            (N              => N,
1902             E              => E,
1903             Orig_Ent       => Orig_Ent,
1904             Curscop        => Current_Scope,
1905             Outer_Scope    => Outer_Scope,
1906             From_Elab_Code => From_Elab_Code));
1907          return;
1908
1909       --  Otherwise, call phase 2 continuation right now
1910
1911       else
1912          Check_Internal_Call_Continue (N, E, Outer_Scope, Orig_Ent);
1913       end if;
1914    end Check_Internal_Call;
1915
1916    ----------------------------------
1917    -- Check_Internal_Call_Continue --
1918    ----------------------------------
1919
1920    procedure Check_Internal_Call_Continue
1921      (N           : Node_Id;
1922       E           : Entity_Id;
1923       Outer_Scope : Entity_Id;
1924       Orig_Ent    : Entity_Id)
1925    is
1926       Loc       : constant Source_Ptr := Sloc (N);
1927       Inst_Case : constant Boolean := Is_Generic_Unit (E);
1928
1929       Sbody : Node_Id;
1930       Ebody : Entity_Id;
1931
1932       function Find_Elab_Reference (N : Node_Id) return Traverse_Result;
1933       --  Function applied to each node as we traverse the body. Checks for
1934       --  call or entity reference that needs checking, and if so checks it.
1935       --  Always returns OK, so entire tree is traversed, except that as
1936       --  described below subprogram bodies are skipped for now.
1937
1938       procedure Traverse is new Atree.Traverse_Proc (Find_Elab_Reference);
1939       --  Traverse procedure using above Find_Elab_Reference function
1940
1941       -------------------------
1942       -- Find_Elab_Reference --
1943       -------------------------
1944
1945       function Find_Elab_Reference (N : Node_Id) return Traverse_Result is
1946          Actual : Node_Id;
1947
1948       begin
1949          --  If user has specified that there are no entry calls in elaboration
1950          --  code, do not trace past an accept statement, because the rendez-
1951          --  vous will happen after elaboration.
1952
1953          if (Nkind (Original_Node (N)) = N_Accept_Statement
1954               or else Nkind (Original_Node (N)) = N_Selective_Accept)
1955            and then Restriction_Active (No_Entry_Calls_In_Elaboration_Code)
1956          then
1957             return Abandon;
1958
1959             --  If we have a function call, check it
1960
1961          elsif Nkind (N) = N_Function_Call then
1962             Check_Elab_Call (N, Outer_Scope);
1963             return OK;
1964
1965          --  If we have a procedure call, check the call, and also check
1966          --  arguments that are assignments (OUT or IN OUT mode formals).
1967
1968          elsif Nkind (N) = N_Procedure_Call_Statement then
1969             Check_Elab_Call (N, Outer_Scope);
1970
1971             Actual := First_Actual (N);
1972             while Present (Actual) loop
1973                if Known_To_Be_Assigned (Actual) then
1974                   Check_Elab_Assign (Actual);
1975                end if;
1976
1977                Next_Actual (Actual);
1978             end loop;
1979
1980             return OK;
1981
1982          --  If we have a generic instantiation, check it
1983
1984          elsif Nkind (N) in N_Generic_Instantiation then
1985             Check_Elab_Instantiation (N, Outer_Scope);
1986             return OK;
1987
1988          --  Skip subprogram bodies that come from source (wait for call to
1989          --  analyze these). The reason for the come from source test is to
1990          --  avoid catching task bodies.
1991
1992          --  For task bodies, we should really avoid these too, waiting for the
1993          --  task activation, but that's too much trouble to catch for now, so
1994          --  we go in unconditionally. This is not so terrible, it means the
1995          --  error backtrace is not quite complete, and we are too eager to
1996          --  scan bodies of tasks that are unused, but this is hardly very
1997          --  significant!
1998
1999          elsif Nkind (N) = N_Subprogram_Body
2000            and then Comes_From_Source (N)
2001          then
2002             return Skip;
2003
2004          elsif Nkind (N) = N_Assignment_Statement
2005            and then Comes_From_Source (N)
2006          then
2007             Check_Elab_Assign (Name (N));
2008             return OK;
2009
2010          else
2011             return OK;
2012          end if;
2013       end Find_Elab_Reference;
2014
2015    --  Start of processing for Check_Internal_Call_Continue
2016
2017    begin
2018       --  Save outer level call if at outer level
2019
2020       if Elab_Call.Last = 0 then
2021          Outer_Level_Sloc := Loc;
2022       end if;
2023
2024       Elab_Visited.Append (E);
2025
2026       --  If the call is to a function that renames a literal, no check
2027       --  is needed.
2028
2029       if Ekind (E) = E_Enumeration_Literal then
2030          return;
2031       end if;
2032
2033       Sbody := Unit_Declaration_Node (E);
2034
2035       if Nkind (Sbody) /= N_Subprogram_Body
2036            and then
2037          Nkind (Sbody) /= N_Package_Body
2038       then
2039          Ebody := Corresponding_Body (Sbody);
2040
2041          if No (Ebody) then
2042             return;
2043          else
2044             Sbody := Unit_Declaration_Node (Ebody);
2045          end if;
2046       end if;
2047
2048       --  If the body appears after the outer level call or instantiation then
2049       --  we have an error case handled below.
2050
2051       if Earlier_In_Extended_Unit (Outer_Level_Sloc, Sloc (Sbody))
2052         and then not In_Task_Activation
2053       then
2054          null;
2055
2056       --  If we have the instantiation case we are done, since we now
2057       --  know that the body of the generic appeared earlier.
2058
2059       elsif Inst_Case then
2060          return;
2061
2062       --  Otherwise we have a call, so we trace through the called body to see
2063       --  if it has any problems.
2064
2065       else
2066          pragma Assert (Nkind (Sbody) = N_Subprogram_Body);
2067
2068          Elab_Call.Append ((Cloc => Loc, Ent => E));
2069
2070          if Debug_Flag_LL then
2071             Write_Str ("Elab_Call.Last = ");
2072             Write_Int (Int (Elab_Call.Last));
2073             Write_Str ("   Ent = ");
2074             Write_Name (Chars (E));
2075             Write_Str ("   at ");
2076             Write_Location (Sloc (N));
2077             Write_Eol;
2078          end if;
2079
2080          --  Now traverse declarations and statements of subprogram body. Note
2081          --  that we cannot simply Traverse (Sbody), since traverse does not
2082          --  normally visit subprogram bodies.
2083
2084          declare
2085             Decl : Node_Id;
2086          begin
2087             Decl := First (Declarations (Sbody));
2088             while Present (Decl) loop
2089                Traverse (Decl);
2090                Next (Decl);
2091             end loop;
2092          end;
2093
2094          Traverse (Handled_Statement_Sequence (Sbody));
2095
2096          Elab_Call.Decrement_Last;
2097          return;
2098       end if;
2099
2100       --  Here is the case of calling a subprogram where the body has not yet
2101       --  been encountered, a warning message is needed.
2102
2103       --  If we have nothing in the call stack, then this is at the outer
2104       --  level, and the ABE is bound to occur.
2105
2106       if Elab_Call.Last = 0 then
2107          if Inst_Case then
2108             Error_Msg_NE
2109               ("?cannot instantiate& before body seen", N, Orig_Ent);
2110          else
2111             Error_Msg_NE
2112               ("?cannot call& before body seen", N, Orig_Ent);
2113          end if;
2114
2115          Error_Msg_N
2116            ("\?Program_Error will be raised at run time", N);
2117          Insert_Elab_Check (N);
2118
2119       --  Call is not at outer level
2120
2121       else
2122          --  Deal with dynamic elaboration check
2123
2124          if not Elaboration_Checks_Suppressed (E) then
2125             Set_Elaboration_Entity_Required (E);
2126
2127             --  Case of no elaboration entity allocated yet
2128
2129             if No (Elaboration_Entity (E)) then
2130
2131                --  Create object declaration for elaboration entity, and put it
2132                --  just in front of the spec of the subprogram or generic unit,
2133                --  in the same scope as this unit.
2134
2135                declare
2136                   Loce : constant Source_Ptr := Sloc (E);
2137                   Ent  : constant Entity_Id  :=
2138                            Make_Defining_Identifier (Loc,
2139                              Chars => New_External_Name (Chars (E), 'E'));
2140
2141                begin
2142                   Set_Elaboration_Entity (E, Ent);
2143                   Push_Scope (Scope (E));
2144
2145                   Insert_Action (Declaration_Node (E),
2146                     Make_Object_Declaration (Loce,
2147                       Defining_Identifier => Ent,
2148                       Object_Definition =>
2149                         New_Occurrence_Of (Standard_Boolean, Loce),
2150                       Expression => New_Occurrence_Of (Standard_False, Loce)));
2151
2152                   --  Set elaboration flag at the point of the body
2153
2154                   Set_Elaboration_Flag (Sbody, E);
2155
2156                   --  Kill current value indication. This is necessary because
2157                   --  the tests of this flag are inserted out of sequence and
2158                   --  must not pick up bogus indications of the wrong constant
2159                   --  value. Also, this is never a true constant, since one way
2160                   --  or another, it gets reset.
2161
2162                   Set_Current_Value    (Ent, Empty);
2163                   Set_Last_Assignment  (Ent, Empty);
2164                   Set_Is_True_Constant (Ent, False);
2165                   Pop_Scope;
2166                end;
2167             end if;
2168
2169             --  Generate check of the elaboration Boolean
2170
2171             Insert_Elab_Check (N,
2172               New_Occurrence_Of (Elaboration_Entity (E), Loc));
2173          end if;
2174
2175          --  Generate the warning
2176
2177          if not Suppress_Elaboration_Warnings (E)
2178            and then not Elaboration_Checks_Suppressed (E)
2179          then
2180             if Inst_Case then
2181                Error_Msg_NE
2182                  ("instantiation of& may occur before body is seen?",
2183                   N, Orig_Ent);
2184             else
2185                Error_Msg_NE
2186                  ("call to& may occur before body is seen?", N, Orig_Ent);
2187             end if;
2188
2189             Error_Msg_N
2190               ("\Program_Error may be raised at run time?", N);
2191
2192             Output_Calls (N);
2193          end if;
2194       end if;
2195
2196       --  Set flag to suppress further warnings on same subprogram
2197       --  unless in all errors mode
2198
2199       if not All_Errors_Mode then
2200          Set_Suppress_Elaboration_Warnings (E);
2201       end if;
2202    end Check_Internal_Call_Continue;
2203
2204    ---------------------------
2205    -- Check_Task_Activation --
2206    ---------------------------
2207
2208    procedure Check_Task_Activation (N : Node_Id) is
2209       Loc         : constant Source_Ptr := Sloc (N);
2210       Inter_Procs : constant Elist_Id   := New_Elmt_List;
2211       Intra_Procs : constant Elist_Id   := New_Elmt_List;
2212       Ent         : Entity_Id;
2213       P           : Entity_Id;
2214       Task_Scope  : Entity_Id;
2215       Cunit_SC    : Boolean := False;
2216       Decl        : Node_Id;
2217       Elmt        : Elmt_Id;
2218       Enclosing   : Entity_Id;
2219
2220       procedure Add_Task_Proc (Typ : Entity_Id);
2221       --  Add to Task_Procs the task body procedure(s) of task types in Typ.
2222       --  For record types, this procedure recurses over component types.
2223
2224       procedure Collect_Tasks (Decls : List_Id);
2225       --  Collect the types of the tasks that are to be activated in the given
2226       --  list of declarations, in order to perform elaboration checks on the
2227       --  corresponding task procedures which are called implicitly here.
2228
2229       function Outer_Unit (E : Entity_Id) return Entity_Id;
2230       --  find enclosing compilation unit of Entity, ignoring subunits, or
2231       --  else enclosing subprogram. If E is not a package, there is no need
2232       --  for inter-unit elaboration checks.
2233
2234       -------------------
2235       -- Add_Task_Proc --
2236       -------------------
2237
2238       procedure Add_Task_Proc (Typ : Entity_Id) is
2239          Comp : Entity_Id;
2240          Proc : Entity_Id := Empty;
2241
2242       begin
2243          if Is_Task_Type (Typ) then
2244             Proc := Get_Task_Body_Procedure (Typ);
2245
2246          elsif Is_Array_Type (Typ)
2247            and then Has_Task (Base_Type (Typ))
2248          then
2249             Add_Task_Proc (Component_Type (Typ));
2250
2251          elsif Is_Record_Type (Typ)
2252            and then Has_Task (Base_Type (Typ))
2253          then
2254             Comp := First_Component (Typ);
2255             while Present (Comp) loop
2256                Add_Task_Proc (Etype (Comp));
2257                Comp := Next_Component (Comp);
2258             end loop;
2259          end if;
2260
2261          --  If the task type is another unit, we will perform the usual
2262          --  elaboration check on its enclosing unit. If the type is in the
2263          --  same unit, we can trace the task body as for an internal call,
2264          --  but we only need to examine other external calls, because at
2265          --  the point the task is activated, internal subprogram bodies
2266          --  will have been elaborated already. We keep separate lists for
2267          --  each kind of task.
2268
2269          --  Skip this test if errors have occurred, since in this case
2270          --  we can get false indications.
2271
2272          if Serious_Errors_Detected /= 0 then
2273             return;
2274          end if;
2275
2276          if Present (Proc) then
2277             if Outer_Unit (Scope (Proc)) = Enclosing then
2278
2279                if No (Corresponding_Body (Unit_Declaration_Node (Proc)))
2280                  and then
2281                    (not Is_Generic_Instance (Scope (Proc))
2282                       or else
2283                     Scope (Proc) = Scope (Defining_Identifier (Decl)))
2284                then
2285                   Error_Msg_N
2286                     ("task will be activated before elaboration of its body?",
2287                       Decl);
2288                   Error_Msg_N
2289                     ("\Program_Error will be raised at run-time?", Decl);
2290
2291                elsif
2292                  Present (Corresponding_Body (Unit_Declaration_Node (Proc)))
2293                then
2294                   Append_Elmt (Proc, Intra_Procs);
2295                end if;
2296
2297             else
2298                --  No need for multiple entries of the same type
2299
2300                Elmt := First_Elmt (Inter_Procs);
2301                while Present (Elmt) loop
2302                   if Node (Elmt) = Proc then
2303                      return;
2304                   end if;
2305
2306                   Next_Elmt (Elmt);
2307                end loop;
2308
2309                Append_Elmt (Proc, Inter_Procs);
2310             end if;
2311          end if;
2312       end Add_Task_Proc;
2313
2314       -------------------
2315       -- Collect_Tasks --
2316       -------------------
2317
2318       procedure Collect_Tasks (Decls : List_Id) is
2319       begin
2320          if Present (Decls) then
2321             Decl := First (Decls);
2322             while Present (Decl) loop
2323                if Nkind (Decl) = N_Object_Declaration
2324                  and then Has_Task (Etype (Defining_Identifier (Decl)))
2325                then
2326                   Add_Task_Proc (Etype (Defining_Identifier (Decl)));
2327                end if;
2328
2329                Next (Decl);
2330             end loop;
2331          end if;
2332       end Collect_Tasks;
2333
2334       ----------------
2335       -- Outer_Unit --
2336       ----------------
2337
2338       function Outer_Unit (E : Entity_Id) return Entity_Id is
2339          Outer : Entity_Id;
2340
2341       begin
2342          Outer := E;
2343          while Present (Outer) loop
2344             if Elaboration_Checks_Suppressed (Outer) then
2345                Cunit_SC := True;
2346             end if;
2347
2348             exit when Is_Child_Unit (Outer)
2349               or else Scope (Outer) = Standard_Standard
2350               or else Ekind (Outer) /= E_Package;
2351             Outer := Scope (Outer);
2352          end loop;
2353
2354          return Outer;
2355       end Outer_Unit;
2356
2357    --  Start of processing for Check_Task_Activation
2358
2359    begin
2360       Enclosing := Outer_Unit (Current_Scope);
2361
2362       --  Find all tasks declared in the current unit
2363
2364       if Nkind (N) = N_Package_Body then
2365          P := Unit_Declaration_Node (Corresponding_Spec (N));
2366
2367          Collect_Tasks (Declarations (N));
2368          Collect_Tasks (Visible_Declarations (Specification (P)));
2369          Collect_Tasks (Private_Declarations (Specification (P)));
2370
2371       elsif Nkind (N) = N_Package_Declaration then
2372          Collect_Tasks (Visible_Declarations (Specification (N)));
2373          Collect_Tasks (Private_Declarations (Specification (N)));
2374
2375       else
2376          Collect_Tasks (Declarations (N));
2377       end if;
2378
2379       --  We only perform detailed checks in all tasks are library level
2380       --  entities. If the master is a subprogram or task, activation will
2381       --  depend on the activation of the master itself.
2382
2383       --  Should dynamic checks be added in the more general case???
2384
2385       if Ekind (Enclosing) /= E_Package then
2386          return;
2387       end if;
2388
2389       --  For task types defined in other units, we want the unit containing
2390       --  the task body to be elaborated before the current one.
2391
2392       Elmt := First_Elmt (Inter_Procs);
2393       while Present (Elmt) loop
2394          Ent := Node (Elmt);
2395          Task_Scope := Outer_Unit (Scope (Ent));
2396
2397          if not Is_Compilation_Unit (Task_Scope) then
2398             null;
2399
2400          elsif Suppress_Elaboration_Warnings (Task_Scope)
2401            or else Elaboration_Checks_Suppressed (Task_Scope)
2402          then
2403             null;
2404
2405          elsif Dynamic_Elaboration_Checks then
2406             if not Elaboration_Checks_Suppressed (Ent)
2407               and then not Cunit_SC
2408               and then
2409                 not Restriction_Active (No_Entry_Calls_In_Elaboration_Code)
2410             then
2411                --  Runtime elaboration check required. Generate check of the
2412                --  elaboration Boolean for the unit containing the entity.
2413
2414                Insert_Elab_Check (N,
2415                  Make_Attribute_Reference (Loc,
2416                    Attribute_Name => Name_Elaborated,
2417                    Prefix =>
2418                      New_Occurrence_Of
2419                        (Spec_Entity (Task_Scope), Loc)));
2420             end if;
2421
2422          else
2423             --  Force the binder to elaborate other unit first
2424
2425             if not Suppress_Elaboration_Warnings (Ent)
2426               and then not Elaboration_Checks_Suppressed (Ent)
2427               and then Elab_Warnings
2428               and then not Suppress_Elaboration_Warnings (Task_Scope)
2429               and then not Elaboration_Checks_Suppressed (Task_Scope)
2430             then
2431                Error_Msg_Node_2 := Task_Scope;
2432                Error_Msg_NE ("activation of an instance of task type&" &
2433                   " requires pragma Elaborate_All on &?", N, Ent);
2434             end if;
2435
2436             Activate_Elaborate_All_Desirable (N, Task_Scope);
2437             Set_Suppress_Elaboration_Warnings (Task_Scope);
2438          end if;
2439
2440          Next_Elmt (Elmt);
2441       end loop;
2442
2443       --  For tasks declared in the current unit, trace other calls within
2444       --  the task procedure bodies, which are available.
2445
2446       In_Task_Activation := True;
2447
2448       Elmt := First_Elmt (Intra_Procs);
2449       while Present (Elmt) loop
2450          Ent := Node (Elmt);
2451          Check_Internal_Call_Continue (N, Ent, Enclosing, Ent);
2452          Next_Elmt (Elmt);
2453       end loop;
2454
2455       In_Task_Activation := False;
2456    end Check_Task_Activation;
2457
2458    --------------------------------
2459    -- Set_Elaboration_Constraint --
2460    --------------------------------
2461
2462    procedure Set_Elaboration_Constraint
2463     (Call : Node_Id;
2464      Subp : Entity_Id;
2465      Scop : Entity_Id)
2466    is
2467       Elab_Unit  : Entity_Id;
2468       Init_Call  : constant Boolean :=
2469                      Chars (Subp) = Name_Initialize
2470                        and then Comes_From_Source (Subp)
2471                        and then Present (Parameter_Associations (Call))
2472                        and then Is_Controlled (Etype (First_Actual (Call)));
2473    begin
2474       --  If the unit is mentioned in a with_clause of the current unit, it is
2475       --  visible, and we can set the elaboration flag.
2476
2477       if Is_Immediately_Visible (Scop)
2478         or else (Is_Child_Unit (Scop) and then Is_Visible_Child_Unit (Scop))
2479       then
2480          Activate_Elaborate_All_Desirable (Call, Scop);
2481          Set_Suppress_Elaboration_Warnings (Scop, True);
2482          return;
2483       end if;
2484
2485       --  If this is not an initialization call or a call using object notation
2486       --  we know that the unit of the called entity is in the context, and
2487       --  we can set the flag as well. The unit need not be visible if the call
2488       --  occurs within an instantiation.
2489
2490       if Is_Init_Proc (Subp)
2491         or else Init_Call
2492         or else Nkind (Original_Node (Call)) = N_Selected_Component
2493       then
2494          null;  --  detailed processing follows.
2495
2496       else
2497          Activate_Elaborate_All_Desirable (Call, Scop);
2498          Set_Suppress_Elaboration_Warnings (Scop, True);
2499          return;
2500       end if;
2501
2502       --  If the unit is not in the context, there must be an intermediate unit
2503       --  that is, on which we need to place to elaboration flag. This happens
2504       --  with init proc calls.
2505
2506       if Is_Init_Proc (Subp)
2507         or else Init_Call
2508       then
2509          --  The initialization call is on an object whose type is not declared
2510          --  in the same scope as the subprogram. The type of the object must
2511          --  be a subtype of the type of operation. This object is the first
2512          --  actual in the call.
2513
2514          declare
2515             Typ : constant Entity_Id :=
2516                     Etype (First (Parameter_Associations (Call)));
2517          begin
2518             Elab_Unit := Scope (Typ);
2519             while (Present (Elab_Unit))
2520               and then not Is_Compilation_Unit (Elab_Unit)
2521             loop
2522                Elab_Unit := Scope (Elab_Unit);
2523             end loop;
2524          end;
2525
2526       --  If original node uses selected component notation, the prefix is
2527       --  visible and determines the scope that must be elaborated. After
2528       --  rewriting, the prefix is the first actual in the call.
2529
2530       elsif Nkind (Original_Node (Call)) = N_Selected_Component then
2531          Elab_Unit := Scope (Etype (First (Parameter_Associations (Call))));
2532
2533       --  Not one of special cases above
2534
2535       else
2536          --  Using previously computed scope. If the elaboration check is
2537          --  done after analysis, the scope is not visible any longer, but
2538          --  must still be in the context.
2539
2540          Elab_Unit := Scop;
2541       end if;
2542
2543       Activate_Elaborate_All_Desirable (Call, Elab_Unit);
2544       Set_Suppress_Elaboration_Warnings (Elab_Unit, True);
2545    end Set_Elaboration_Constraint;
2546
2547    ----------------------
2548    -- Has_Generic_Body --
2549    ----------------------
2550
2551    function Has_Generic_Body (N : Node_Id) return Boolean is
2552       Ent  : constant Entity_Id := Get_Generic_Entity (N);
2553       Decl : constant Node_Id   := Unit_Declaration_Node (Ent);
2554       Scop : Entity_Id;
2555
2556       function Find_Body_In (E : Entity_Id; N : Node_Id) return Node_Id;
2557       --  Determine if the list of nodes headed by N and linked by Next
2558       --  contains a package body for the package spec entity E, and if so
2559       --  return the package body. If not, then returns Empty.
2560
2561       function Load_Package_Body (Nam : Unit_Name_Type) return Node_Id;
2562       --  This procedure is called load the unit whose name is given by Nam.
2563       --  This unit is being loaded to see whether it contains an optional
2564       --  generic body. The returned value is the loaded unit, which is always
2565       --  a package body (only package bodies can contain other entities in the
2566       --  sense in which Has_Generic_Body is interested). We only attempt to
2567       --  load bodies if we are generating code. If we are in semantics check
2568       --  only mode, then it would be wrong to load bodies that are not
2569       --  required from a semantic point of view, so in this case we return
2570       --  Empty. The result is that the caller may incorrectly decide that a
2571       --  generic spec does not have a body when in fact it does, but the only
2572       --  harm in this is that some warnings on elaboration problems may be
2573       --  lost in semantic checks only mode, which is not big loss. We also
2574       --  return Empty if we go for a body and it is not there.
2575
2576       function Locate_Corresponding_Body (PE : Entity_Id) return Node_Id;
2577       --  PE is the entity for a package spec. This function locates the
2578       --  corresponding package body, returning Empty if none is found. The
2579       --  package body returned is fully parsed but may not yet be analyzed,
2580       --  so only syntactic fields should be referenced.
2581
2582       ------------------
2583       -- Find_Body_In --
2584       ------------------
2585
2586       function Find_Body_In (E : Entity_Id; N : Node_Id) return Node_Id is
2587          Nod : Node_Id;
2588
2589       begin
2590          Nod := N;
2591          while Present (Nod) loop
2592
2593             --  If we found the package body we are looking for, return it
2594
2595             if Nkind (Nod) = N_Package_Body
2596               and then Chars (Defining_Unit_Name (Nod)) = Chars (E)
2597             then
2598                return Nod;
2599
2600             --  If we found the stub for the body, go after the subunit,
2601             --  loading it if necessary.
2602
2603             elsif Nkind (Nod) = N_Package_Body_Stub
2604               and then Chars (Defining_Identifier (Nod)) = Chars (E)
2605             then
2606                if Present (Library_Unit (Nod)) then
2607                   return Unit (Library_Unit (Nod));
2608
2609                else
2610                   return Load_Package_Body (Get_Unit_Name (Nod));
2611                end if;
2612
2613             --  If neither package body nor stub, keep looking on chain
2614
2615             else
2616                Next (Nod);
2617             end if;
2618          end loop;
2619
2620          return Empty;
2621       end Find_Body_In;
2622
2623       -----------------------
2624       -- Load_Package_Body --
2625       -----------------------
2626
2627       function Load_Package_Body (Nam : Unit_Name_Type) return Node_Id is
2628          U : Unit_Number_Type;
2629
2630       begin
2631          if Operating_Mode /= Generate_Code then
2632             return Empty;
2633          else
2634             U :=
2635               Load_Unit
2636                 (Load_Name  => Nam,
2637                  Required   => False,
2638                  Subunit    => False,
2639                  Error_Node => N);
2640
2641             if U = No_Unit then
2642                return Empty;
2643             else
2644                return Unit (Cunit (U));
2645             end if;
2646          end if;
2647       end Load_Package_Body;
2648
2649       -------------------------------
2650       -- Locate_Corresponding_Body --
2651       -------------------------------
2652
2653       function Locate_Corresponding_Body (PE : Entity_Id) return Node_Id is
2654          Spec  : constant Node_Id   := Declaration_Node (PE);
2655          Decl  : constant Node_Id   := Parent (Spec);
2656          Scop  : constant Entity_Id := Scope (PE);
2657          PBody : Node_Id;
2658
2659       begin
2660          if Is_Library_Level_Entity (PE) then
2661
2662             --  If package is a library unit that requires a body, we have no
2663             --  choice but to go after that body because it might contain an
2664             --  optional body for the original generic package.
2665
2666             if Unit_Requires_Body (PE) then
2667
2668                --  Load the body. Note that we are a little careful here to use
2669                --  Spec to get the unit number, rather than PE or Decl, since
2670                --  in the case where the package is itself a library level
2671                --  instantiation, Spec will properly reference the generic
2672                --  template, which is what we really want.
2673
2674                return
2675                  Load_Package_Body
2676                    (Get_Body_Name (Unit_Name (Get_Source_Unit (Spec))));
2677
2678             --  But if the package is a library unit that does NOT require
2679             --  a body, then no body is permitted, so we are sure that there
2680             --  is no body for the original generic package.
2681
2682             else
2683                return Empty;
2684             end if;
2685
2686          --  Otherwise look and see if we are embedded in a further package
2687
2688          elsif Is_Package_Or_Generic_Package (Scop) then
2689
2690             --  If so, get the body of the enclosing package, and look in
2691             --  its package body for the package body we are looking for.
2692
2693             PBody := Locate_Corresponding_Body (Scop);
2694
2695             if No (PBody) then
2696                return Empty;
2697             else
2698                return Find_Body_In (PE, First (Declarations (PBody)));
2699             end if;
2700
2701          --  If we are not embedded in a further package, then the body
2702          --  must be in the same declarative part as we are.
2703
2704          else
2705             return Find_Body_In (PE, Next (Decl));
2706          end if;
2707       end Locate_Corresponding_Body;
2708
2709    --  Start of processing for Has_Generic_Body
2710
2711    begin
2712       if Present (Corresponding_Body (Decl)) then
2713          return True;
2714
2715       elsif Unit_Requires_Body (Ent) then
2716          return True;
2717
2718       --  Compilation units cannot have optional bodies
2719
2720       elsif Is_Compilation_Unit (Ent) then
2721          return False;
2722
2723       --  Otherwise look at what scope we are in
2724
2725       else
2726          Scop := Scope (Ent);
2727
2728          --  Case of entity is in other than a package spec, in this case
2729          --  the body, if present, must be in the same declarative part.
2730
2731          if not Is_Package_Or_Generic_Package (Scop) then
2732             declare
2733                P : Node_Id;
2734
2735             begin
2736                --  Declaration node may get us a spec, so if so, go to
2737                --  the parent declaration.
2738
2739                P := Declaration_Node (Ent);
2740                while not Is_List_Member (P) loop
2741                   P := Parent (P);
2742                end loop;
2743
2744                return Present (Find_Body_In (Ent, Next (P)));
2745             end;
2746
2747          --  If the entity is in a package spec, then we have to locate
2748          --  the corresponding package body, and look there.
2749
2750          else
2751             declare
2752                PBody : constant Node_Id := Locate_Corresponding_Body (Scop);
2753
2754             begin
2755                if No (PBody) then
2756                   return False;
2757                else
2758                   return
2759                     Present
2760                       (Find_Body_In (Ent, (First (Declarations (PBody)))));
2761                end if;
2762             end;
2763          end if;
2764       end if;
2765    end Has_Generic_Body;
2766
2767    -----------------------
2768    -- Insert_Elab_Check --
2769    -----------------------
2770
2771    procedure Insert_Elab_Check (N : Node_Id; C : Node_Id := Empty) is
2772       Nod : Node_Id;
2773       Loc : constant Source_Ptr := Sloc (N);
2774
2775    begin
2776       --  If expansion is disabled, do not generate any checks. Also
2777       --  skip checks if any subunits are missing because in either
2778       --  case we lack the full information that we need, and no object
2779       --  file will be created in any case.
2780
2781       if not Expander_Active or else Subunits_Missing then
2782          return;
2783       end if;
2784
2785       --  If we have a generic instantiation, where Instance_Spec is set,
2786       --  then this field points to a generic instance spec that has
2787       --  been inserted before the instantiation node itself, so that
2788       --  is where we want to insert a check.
2789
2790       if Nkind (N) in N_Generic_Instantiation
2791         and then Present (Instance_Spec (N))
2792       then
2793          Nod := Instance_Spec (N);
2794       else
2795          Nod := N;
2796       end if;
2797
2798       --  If we are inserting at the top level, insert in Aux_Decls
2799
2800       if Nkind (Parent (Nod)) = N_Compilation_Unit then
2801          declare
2802             ADN : constant Node_Id := Aux_Decls_Node (Parent (Nod));
2803             R   : Node_Id;
2804
2805          begin
2806             if No (C) then
2807                R :=
2808                  Make_Raise_Program_Error (Loc,
2809                    Reason => PE_Access_Before_Elaboration);
2810             else
2811                R :=
2812                  Make_Raise_Program_Error (Loc,
2813                    Condition => Make_Op_Not (Loc, C),
2814                    Reason    => PE_Access_Before_Elaboration);
2815             end if;
2816
2817             if No (Declarations (ADN)) then
2818                Set_Declarations (ADN, New_List (R));
2819             else
2820                Append_To (Declarations (ADN), R);
2821             end if;
2822
2823             Analyze (R);
2824          end;
2825
2826       --  Otherwise just insert before the node in question. However, if
2827       --  the context of the call has already been analyzed, an insertion
2828       --  will not work if it depends on subsequent expansion (e.g. a call in
2829       --  a branch of a short-circuit). In that case we replace the call with
2830       --  a conditional expression, or with a Raise if it is unconditional.
2831       --  Unfortunately this does not work if the call has a dynamic size,
2832       --  because gigi regards it as a dynamic-sized temporary. If such a call
2833       --  appears in a short-circuit expression, the elaboration check will be
2834       --  missed (rare enough ???). Otherwise, the code below inserts the check
2835       --  at the appropriate place before the call. Same applies in the even
2836       --  rarer case the return type has a known size but is unconstrained.
2837
2838       else
2839          if Nkind (N) = N_Function_Call
2840            and then Analyzed (Parent (N))
2841            and then Size_Known_At_Compile_Time (Etype (N))
2842            and then
2843             (not Has_Discriminants (Etype (N))
2844               or else Is_Constrained (Etype (N)))
2845
2846          then
2847             declare
2848                Typ : constant Entity_Id := Etype (N);
2849                Chk : constant Boolean   := Do_Range_Check (N);
2850
2851                R   : constant Node_Id :=
2852                        Make_Raise_Program_Error (Loc,
2853                          Reason => PE_Access_Before_Elaboration);
2854
2855             begin
2856                Set_Etype (R, Typ);
2857
2858                if No (C) then
2859                   Rewrite (N, R);
2860
2861                else
2862                   Rewrite (N,
2863                     Make_Conditional_Expression (Loc,
2864                       Expressions => New_List (C, Relocate_Node (N), R)));
2865                end if;
2866
2867                Analyze_And_Resolve (N, Typ);
2868
2869                --  If the original call requires a range check, so does the
2870                --  conditional expression.
2871
2872                if Chk then
2873                   Enable_Range_Check (N);
2874                else
2875                   Set_Do_Range_Check (N, False);
2876                end if;
2877             end;
2878
2879          else
2880             if No (C) then
2881                Insert_Action (Nod,
2882                   Make_Raise_Program_Error (Loc,
2883                     Reason => PE_Access_Before_Elaboration));
2884             else
2885                Insert_Action (Nod,
2886                   Make_Raise_Program_Error (Loc,
2887                     Condition =>
2888                       Make_Op_Not (Loc,
2889                         Right_Opnd => C),
2890                     Reason => PE_Access_Before_Elaboration));
2891             end if;
2892          end if;
2893       end if;
2894    end Insert_Elab_Check;
2895
2896    ------------------
2897    -- Output_Calls --
2898    ------------------
2899
2900    procedure Output_Calls (N : Node_Id) is
2901       Ent : Entity_Id;
2902
2903       function Is_Printable_Error_Name (Nm : Name_Id) return Boolean;
2904       --  An internal function, used to determine if a name, Nm, is either
2905       --  a non-internal name, or is an internal name that is printable
2906       --  by the error message circuits (i.e. it has a single upper
2907       --  case letter at the end).
2908
2909       function Is_Printable_Error_Name (Nm : Name_Id) return Boolean is
2910       begin
2911          if not Is_Internal_Name (Nm) then
2912             return True;
2913
2914          elsif Name_Len = 1 then
2915             return False;
2916
2917          else
2918             Name_Len := Name_Len - 1;
2919             return not Is_Internal_Name;
2920          end if;
2921       end Is_Printable_Error_Name;
2922
2923    --  Start of processing for Output_Calls
2924
2925    begin
2926       for J in reverse 1 .. Elab_Call.Last loop
2927          Error_Msg_Sloc := Elab_Call.Table (J).Cloc;
2928
2929          Ent := Elab_Call.Table (J).Ent;
2930
2931          if Is_Generic_Unit (Ent) then
2932             Error_Msg_NE ("\?& instantiated #", N, Ent);
2933
2934          elsif Is_Init_Proc (Ent) then
2935             Error_Msg_N ("\?initialization procedure called #", N);
2936
2937          elsif Is_Printable_Error_Name (Chars (Ent)) then
2938             Error_Msg_NE ("\?& called #", N, Ent);
2939
2940          else
2941             Error_Msg_N ("\? called #", N);
2942          end if;
2943       end loop;
2944    end Output_Calls;
2945
2946    ----------------------------
2947    -- Same_Elaboration_Scope --
2948    ----------------------------
2949
2950    function Same_Elaboration_Scope (Scop1, Scop2 : Entity_Id) return Boolean is
2951       S1 : Entity_Id;
2952       S2 : Entity_Id;
2953
2954    begin
2955       --  Find elaboration scope for Scop1
2956       --  This is either a subprogram or a compilation unit.
2957
2958       S1 := Scop1;
2959       while S1 /= Standard_Standard
2960         and then not Is_Compilation_Unit (S1)
2961         and then (Ekind (S1) = E_Package
2962                     or else
2963                   Ekind (S1) = E_Protected_Type
2964                     or else
2965                   Ekind (S1) = E_Block)
2966       loop
2967          S1 := Scope (S1);
2968       end loop;
2969
2970       --  Find elaboration scope for Scop2
2971
2972       S2 := Scop2;
2973       while S2 /= Standard_Standard
2974         and then not Is_Compilation_Unit (S2)
2975         and then (Ekind (S2) = E_Package
2976                     or else
2977                   Ekind (S2) = E_Protected_Type
2978                     or else
2979                   Ekind (S2) = E_Block)
2980       loop
2981          S2 := Scope (S2);
2982       end loop;
2983
2984       return S1 = S2;
2985    end Same_Elaboration_Scope;
2986
2987    -----------------
2988    -- Set_C_Scope --
2989    -----------------
2990
2991    procedure Set_C_Scope is
2992    begin
2993       while not Is_Compilation_Unit (C_Scope) loop
2994          C_Scope := Scope (C_Scope);
2995       end loop;
2996    end Set_C_Scope;
2997
2998    -----------------
2999    -- Spec_Entity --
3000    -----------------
3001
3002    function Spec_Entity (E : Entity_Id) return Entity_Id is
3003       Decl : Node_Id;
3004
3005    begin
3006       --  Check for case of body entity
3007       --  Why is the check for E_Void needed???
3008
3009       if Ekind (E) = E_Void
3010         or else Ekind (E) = E_Subprogram_Body
3011         or else Ekind (E) = E_Package_Body
3012       then
3013          Decl := E;
3014
3015          loop
3016             Decl := Parent (Decl);
3017             exit when Nkind (Decl) in N_Proper_Body;
3018          end loop;
3019
3020          return Corresponding_Spec (Decl);
3021
3022       else
3023          return E;
3024       end if;
3025    end Spec_Entity;
3026
3027    -------------------
3028    -- Supply_Bodies --
3029    -------------------
3030
3031    procedure Supply_Bodies (N : Node_Id) is
3032    begin
3033       if Nkind (N) = N_Subprogram_Declaration then
3034          declare
3035             Ent : constant Entity_Id := Defining_Unit_Name (Specification (N));
3036          begin
3037
3038             --  Internal subprograms will already have a generated body, so
3039             --  there is no need to provide a stub for them.
3040
3041             if No (Corresponding_Body (N)) then
3042                declare
3043                   Loc : constant Source_Ptr := Sloc (N);
3044                   B : Node_Id;
3045                   Formals : constant List_Id :=
3046                      Copy_Parameter_List (Ent);
3047                   Nam  : constant Entity_Id :=
3048                     Make_Defining_Identifier (Loc, Chars (Ent));
3049                   Spec : Node_Id;
3050                   Stats : constant List_Id :=
3051                     New_List
3052                       (Make_Raise_Program_Error (Loc,
3053                          Reason => PE_Access_Before_Elaboration));
3054                begin
3055                   if Ekind (Ent) = E_Function then
3056                      Spec :=
3057                         Make_Function_Specification (Loc,
3058                           Defining_Unit_Name => Nam,
3059                           Parameter_Specifications => Formals,
3060                           Result_Definition =>
3061                             New_Copy_Tree
3062                               (Result_Definition (Specification (N))));
3063
3064                      --  We cannot reliably make a return statement for this
3065                      --  body, but none is needed because the call raises
3066                      --  program error.
3067
3068                      Set_Return_Present (Ent);
3069
3070                   else
3071                      Spec :=
3072                         Make_Procedure_Specification (Loc,
3073                           Defining_Unit_Name => Nam,
3074                           Parameter_Specifications => Formals);
3075                   end if;
3076
3077                   B := Make_Subprogram_Body (Loc,
3078                           Specification => Spec,
3079                           Declarations => New_List,
3080                           Handled_Statement_Sequence =>
3081                             Make_Handled_Sequence_Of_Statements (Loc,  Stats));
3082                   Insert_After (N, B);
3083                   Analyze (B);
3084                end;
3085             end if;
3086          end;
3087
3088       elsif Nkind (N) = N_Package_Declaration then
3089          declare
3090             Spec : constant Node_Id := Specification (N);
3091          begin
3092             Push_Scope (Defining_Unit_Name (Spec));
3093             Supply_Bodies (Visible_Declarations (Spec));
3094             Supply_Bodies (Private_Declarations (Spec));
3095             Pop_Scope;
3096          end;
3097       end if;
3098    end Supply_Bodies;
3099
3100    procedure Supply_Bodies (L : List_Id) is
3101       Elmt : Node_Id;
3102    begin
3103       if Present (L) then
3104          Elmt := First (L);
3105          while Present (Elmt) loop
3106             Supply_Bodies (Elmt);
3107             Next (Elmt);
3108          end loop;
3109       end if;
3110    end Supply_Bodies;
3111
3112    ------------
3113    -- Within --
3114    ------------
3115
3116    function Within (E1, E2 : Entity_Id) return Boolean is
3117       Scop : Entity_Id;
3118    begin
3119       Scop := E1;
3120       loop
3121          if Scop = E2 then
3122             return True;
3123          elsif Scop = Standard_Standard then
3124             return False;
3125          else
3126             Scop := Scope (Scop);
3127          end if;
3128       end loop;
3129    end Within;
3130
3131    --------------------------
3132    -- Within_Elaborate_All --
3133    --------------------------
3134
3135    function Within_Elaborate_All (E : Entity_Id) return Boolean is
3136       Item    : Node_Id;
3137       Item2   : Node_Id;
3138       Elab_Id : Entity_Id;
3139       Par     : Node_Id;
3140
3141    begin
3142       Item := First (Context_Items (Cunit (Current_Sem_Unit)));
3143       while Present (Item) loop
3144          if Nkind (Item) = N_Pragma
3145            and then Pragma_Name (Item) = Name_Elaborate_All
3146          then
3147             --  Return if some previous error on the pragma itself
3148
3149             if Error_Posted (Item) then
3150                return False;
3151             end if;
3152
3153             Elab_Id :=
3154               Entity
3155                 (Expression (First (Pragma_Argument_Associations (Item))));
3156
3157             Par := Parent (Unit_Declaration_Node (Elab_Id));
3158
3159             Item2 := First (Context_Items (Par));
3160             while Present (Item2) loop
3161                if Nkind (Item2) = N_With_Clause
3162                  and then Entity (Name (Item2)) = E
3163                then
3164                   return True;
3165                end if;
3166
3167                Next (Item2);
3168             end loop;
3169          end if;
3170
3171          Next (Item);
3172       end loop;
3173
3174       return False;
3175    end Within_Elaborate_All;
3176
3177 end Sem_Elab;