OSDN Git Service

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