OSDN Git Service

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