OSDN Git Service

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