OSDN Git Service

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