Merge form mainline (hopefully)
[official-gcc.git] / gcc / ada / sem_ch10.adb
blobb752eb495aa38c643d05248a0404cf2fcafa5449
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 1 0 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2005 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 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Util; use Exp_Util;
32 with Fname; use Fname;
33 with Fname.UF; use Fname.UF;
34 with Freeze; use Freeze;
35 with Impunit; use Impunit;
36 with Inline; use Inline;
37 with Lib; use Lib;
38 with Lib.Load; use Lib.Load;
39 with Lib.Xref; use Lib.Xref;
40 with Namet; use Namet;
41 with Nlists; use Nlists;
42 with Nmake; use Nmake;
43 with Opt; use Opt;
44 with Output; use Output;
45 with Restrict; use Restrict;
46 with Rtsfind; use Rtsfind;
47 with Sem; use Sem;
48 with Sem_Ch6; use Sem_Ch6;
49 with Sem_Ch7; use Sem_Ch7;
50 with Sem_Ch8; use Sem_Ch8;
51 with Sem_Dist; use Sem_Dist;
52 with Sem_Prag; use Sem_Prag;
53 with Sem_Util; use Sem_Util;
54 with Sem_Warn; use Sem_Warn;
55 with Stand; use Stand;
56 with Sinfo; use Sinfo;
57 with Sinfo.CN; use Sinfo.CN;
58 with Sinput; use Sinput;
59 with Snames; use Snames;
60 with Style; use Style;
61 with Stylesw; use Stylesw;
62 with Tbuild; use Tbuild;
63 with Ttypes; use Ttypes;
64 with Uname; use Uname;
66 package body Sem_Ch10 is
68 -----------------------
69 -- Local Subprograms --
70 -----------------------
72 procedure Analyze_Context (N : Node_Id);
73 -- Analyzes items in the context clause of compilation unit
75 procedure Build_Limited_Views (N : Node_Id);
76 -- Build and decorate the list of shadow entities for a package mentioned
77 -- in a limited_with clause. If the package was not previously analyzed
78 -- then it also performs a basic decoration of the real entities; this
79 -- is required to do not pass non-decorated entities to the back-end.
80 -- Implements Ada 2005 (AI-50217).
82 procedure Check_Body_Needed_For_SAL (Unit_Name : Entity_Id);
83 -- Check whether the source for the body of a compilation unit must
84 -- be included in a standalone library.
86 procedure Check_With_Type_Clauses (N : Node_Id);
87 -- If N is a body, verify that any with_type clauses on the spec, or
88 -- on the spec of any parent, have a matching with_clause.
90 procedure Check_Private_Child_Unit (N : Node_Id);
91 -- If a with_clause mentions a private child unit, the compilation
92 -- unit must be a member of the same family, as described in 10.1.2 (8).
94 procedure Check_Stub_Level (N : Node_Id);
95 -- Verify that a stub is declared immediately within a compilation unit,
96 -- and not in an inner frame.
98 procedure Expand_With_Clause (Nam : Node_Id; N : Node_Id);
99 -- When a child unit appears in a context clause, the implicit withs on
100 -- parents are made explicit, and with clauses are inserted in the context
101 -- clause before the one for the child. If a parent in the with_clause
102 -- is a renaming, the implicit with_clause is on the renaming whose name
103 -- is mentioned in the with_clause, and not on the package it renames.
104 -- N is the compilation unit whose list of context items receives the
105 -- implicit with_clauses.
107 function Get_Parent_Entity (Unit : Node_Id) return Entity_Id;
108 -- Get defining entity of parent unit of a child unit. In most cases this
109 -- is the defining entity of the unit, but for a child instance whose
110 -- parent needs a body for inlining, the instantiation node of the parent
111 -- has not yet been rewritten as a package declaration, and the entity has
112 -- to be retrieved from the Instance_Spec of the unit.
114 procedure Implicit_With_On_Parent (Child_Unit : Node_Id; N : Node_Id);
115 -- If the main unit is a child unit, implicit withs are also added for
116 -- all its ancestors.
118 function In_Chain (E : Entity_Id) return Boolean;
119 -- Check that the shadow entity is not already in the homonym chain, for
120 -- example through a limited_with clause in a parent unit.
122 procedure Install_Context_Clauses (N : Node_Id);
123 -- Subsidiary to Install_Context and Install_Parents. Process only with_
124 -- and use_clauses for current unit and its library unit if any.
126 procedure Install_Limited_Context_Clauses (N : Node_Id);
127 -- Subsidiary to Install_Context. Process only limited with_clauses
128 -- for current unit. Implements Ada 2005 (AI-50217).
130 procedure Install_Limited_Withed_Unit (N : Node_Id);
131 -- Place shadow entities for a limited_with package in the visibility
132 -- structures for the current compilation. Implements Ada 2005 (AI-50217).
134 procedure Install_Withed_Unit
135 (With_Clause : Node_Id;
136 Private_With_OK : Boolean := False);
137 -- If the unit is not a child unit, make unit immediately visible.
138 -- The caller ensures that the unit is not already currently installed.
139 -- The flag Private_With_OK is set true in Install_Private_With_Clauses,
140 -- which is called when compiling the private part of a package, or
141 -- installing the private declarations of a parent unit.
143 procedure Install_Parents (Lib_Unit : Node_Id; Is_Private : Boolean);
144 -- This procedure establishes the context for the compilation of a child
145 -- unit. If Lib_Unit is a child library spec then the context of the parent
146 -- is installed, and the parent itself made immediately visible, so that
147 -- the child unit is processed in the declarative region of the parent.
148 -- Install_Parents makes a recursive call to itself to ensure that all
149 -- parents are loaded in the nested case. If Lib_Unit is a library body,
150 -- the only effect of Install_Parents is to install the private decls of
151 -- the parents, because the visible parent declarations will have been
152 -- installed as part of the context of the corresponding spec.
154 procedure Install_Siblings (U_Name : Entity_Id; N : Node_Id);
155 -- In the compilation of a child unit, a child of any of the ancestor
156 -- units is directly visible if it is visible, because the parent is in
157 -- an enclosing scope. Iterate over context to find child units of U_Name
158 -- or of some ancestor of it.
160 function Is_Child_Spec (Lib_Unit : Node_Id) return Boolean;
161 -- Lib_Unit is a library unit which may be a spec or a body. Is_Child_Spec
162 -- returns True if Lib_Unit is a library spec which is a child spec, i.e.
163 -- a library spec that has a parent. If the call to Is_Child_Spec returns
164 -- True, then Parent_Spec (Lib_Unit) is non-Empty and points to the
165 -- compilation unit for the parent spec.
167 -- Lib_Unit can also be a subprogram body that acts as its own spec. If
168 -- the Parent_Spec is non-empty, this is also a child unit.
170 procedure Remove_With_Type_Clause (Name : Node_Id);
171 -- Remove imported type and its enclosing package from visibility, and
172 -- remove attributes of imported type so they don't interfere with its
173 -- analysis (should it appear otherwise in the context).
175 procedure Remove_Context_Clauses (N : Node_Id);
176 -- Subsidiary of previous one. Remove use_ and with_clauses
178 procedure Remove_Limited_With_Clause (N : Node_Id);
179 -- Remove from visibility the shadow entities introduced for a package
180 -- mentioned in a limited_with clause. Implements Ada 2005 (AI-50217).
182 procedure Remove_Parents (Lib_Unit : Node_Id);
183 -- Remove_Parents checks if Lib_Unit is a child spec. If so then the parent
184 -- contexts established by the corresponding call to Install_Parents are
185 -- removed. Remove_Parents contains a recursive call to itself to ensure
186 -- that all parents are removed in the nested case.
188 procedure Remove_Unit_From_Visibility (Unit_Name : Entity_Id);
189 -- Reset all visibility flags on unit after compiling it, either as a
190 -- main unit or as a unit in the context.
192 procedure Unchain (E : Entity_Id);
193 -- Remove single entity from visibility list
195 procedure Analyze_Proper_Body (N : Node_Id; Nam : Entity_Id);
196 -- Common processing for all stubs (subprograms, tasks, packages, and
197 -- protected cases). N is the stub to be analyzed. Once the subunit
198 -- name is established, load and analyze. Nam is the non-overloadable
199 -- entity for which the proper body provides a completion. Subprogram
200 -- stubs are handled differently because they can be declarations.
202 --------------------------
203 -- Limited_With_Clauses --
204 --------------------------
206 -- Limited_With clauses are the mechanism chosen for Ada05 to support
207 -- mutually recursive types declared in different units. A limited_with
208 -- clause that names package P in the context of unit U makes the types
209 -- declared in the visible part of P available within U, but with the
210 -- restriction that these types can only be used as incomplete types.
211 -- The limited_with clause does not impose a semantic dependence on P,
212 -- and it is possible for two packages to have limited_with_clauses on
213 -- each other without creating an elaboration circularity.
215 -- To support this feature, the analysis of a limited_with clause must
216 -- create an abbreviated view of the package, without performing any
217 -- semantic analysis on it. This "package abstract" contains shadow
218 -- types that are in one-one correspondence with the real types in the
219 -- package, and that have the properties of incomplete types.
221 -- The implementation creates two element lists: one to chain the shadow
222 -- entities, and one to chain the corresponding type entities in the tree
223 -- of the package. Links between corresponding entities in both chains
224 -- allow the compiler to select the proper view of a given type, depending
225 -- on the context. Note that in contrast with the handling of private
226 -- types, the limited view and the non-limited view of a type are treated
227 -- as separate entities, and no entity exchange needs to take place, which
228 -- makes the implementation must simpler than could be feared.
230 ------------------------------
231 -- Analyze_Compilation_Unit --
232 ------------------------------
234 procedure Analyze_Compilation_Unit (N : Node_Id) is
235 Unit_Node : constant Node_Id := Unit (N);
236 Lib_Unit : Node_Id := Library_Unit (N);
237 Spec_Id : Node_Id;
238 Main_Cunit : constant Node_Id := Cunit (Main_Unit);
239 Par_Spec_Name : Unit_Name_Type;
240 Unum : Unit_Number_Type;
242 procedure Generate_Parent_References (N : Node_Id; P_Id : Entity_Id);
243 -- Generate cross-reference information for the parents of child units.
244 -- N is a defining_program_unit_name, and P_Id is the immediate parent.
246 --------------------------------
247 -- Generate_Parent_References --
248 --------------------------------
250 procedure Generate_Parent_References (N : Node_Id; P_Id : Entity_Id) is
251 Pref : Node_Id;
252 P_Name : Entity_Id := P_Id;
254 begin
255 Pref := Name (Parent (Defining_Entity (N)));
257 if Nkind (Pref) = N_Expanded_Name then
259 -- Done already, if the unit has been compiled indirectly as
260 -- part of the closure of its context because of inlining.
262 return;
263 end if;
265 while Nkind (Pref) = N_Selected_Component loop
266 Change_Selected_Component_To_Expanded_Name (Pref);
267 Set_Entity (Pref, P_Name);
268 Set_Etype (Pref, Etype (P_Name));
269 Generate_Reference (P_Name, Pref, 'r');
270 Pref := Prefix (Pref);
271 P_Name := Scope (P_Name);
272 end loop;
274 -- The guard here on P_Name is to handle the error condition where
275 -- the parent unit is missing because the file was not found.
277 if Present (P_Name) then
278 Set_Entity (Pref, P_Name);
279 Set_Etype (Pref, Etype (P_Name));
280 Generate_Reference (P_Name, Pref, 'r');
281 Style.Check_Identifier (Pref, P_Name);
282 end if;
283 end Generate_Parent_References;
285 -- Start of processing for Analyze_Compilation_Unit
287 begin
288 Process_Compilation_Unit_Pragmas (N);
290 -- If the unit is a subunit whose parent has not been analyzed (which
291 -- indicates that the main unit is a subunit, either the current one or
292 -- one of its descendents) then the subunit is compiled as part of the
293 -- analysis of the parent, which we proceed to do. Basically this gets
294 -- handled from the top down and we don't want to do anything at this
295 -- level (i.e. this subunit will be handled on the way down from the
296 -- parent), so at this level we immediately return. If the subunit
297 -- ends up not analyzed, it means that the parent did not contain a
298 -- stub for it, or that there errors were dectected in some ancestor.
300 if Nkind (Unit_Node) = N_Subunit
301 and then not Analyzed (Lib_Unit)
302 then
303 Semantics (Lib_Unit);
305 if not Analyzed (Proper_Body (Unit_Node)) then
306 if Serious_Errors_Detected > 0 then
307 Error_Msg_N ("subunit not analyzed (errors in parent unit)", N);
308 else
309 Error_Msg_N ("missing stub for subunit", N);
310 end if;
311 end if;
313 return;
314 end if;
316 -- Analyze context (this will call Sem recursively for with'ed units)
318 Analyze_Context (N);
320 -- If the unit is a package body, the spec is already loaded and must
321 -- be analyzed first, before we analyze the body.
323 if Nkind (Unit_Node) = N_Package_Body then
325 -- If no Lib_Unit, then there was a serious previous error, so
326 -- just ignore the entire analysis effort
328 if No (Lib_Unit) then
329 return;
331 else
332 Semantics (Lib_Unit);
333 Check_Unused_Withs (Get_Cunit_Unit_Number (Lib_Unit));
335 -- Verify that the library unit is a package declaration
337 if Nkind (Unit (Lib_Unit)) /= N_Package_Declaration
338 and then
339 Nkind (Unit (Lib_Unit)) /= N_Generic_Package_Declaration
340 then
341 Error_Msg_N
342 ("no legal package declaration for package body", N);
343 return;
345 -- Otherwise, the entity in the declaration is visible. Update
346 -- the version to reflect dependence of this body on the spec.
348 else
349 Spec_Id := Defining_Entity (Unit (Lib_Unit));
350 Set_Is_Immediately_Visible (Spec_Id, True);
351 Version_Update (N, Lib_Unit);
353 if Nkind (Defining_Unit_Name (Unit_Node))
354 = N_Defining_Program_Unit_Name
355 then
356 Generate_Parent_References (Unit_Node, Scope (Spec_Id));
357 end if;
358 end if;
359 end if;
361 -- If the unit is a subprogram body, then we similarly need to analyze
362 -- its spec. However, things are a little simpler in this case, because
363 -- here, this analysis is done only for error checking and consistency
364 -- purposes, so there's nothing else to be done.
366 elsif Nkind (Unit_Node) = N_Subprogram_Body then
367 if Acts_As_Spec (N) then
369 -- If the subprogram body is a child unit, we must create a
370 -- declaration for it, in order to properly load the parent(s).
371 -- After this, the original unit does not acts as a spec, because
372 -- there is an explicit one. If this unit appears in a context
373 -- clause, then an implicit with on the parent will be added when
374 -- installing the context. If this is the main unit, there is no
375 -- Unit_Table entry for the declaration, (It has the unit number
376 -- of the main unit) and code generation is unaffected.
378 Unum := Get_Cunit_Unit_Number (N);
379 Par_Spec_Name := Get_Parent_Spec_Name (Unit_Name (Unum));
381 if Par_Spec_Name /= No_Name then
382 Unum :=
383 Load_Unit
384 (Load_Name => Par_Spec_Name,
385 Required => True,
386 Subunit => False,
387 Error_Node => N);
389 if Unum /= No_Unit then
391 -- Build subprogram declaration and attach parent unit to it
392 -- This subprogram declaration does not come from source,
393 -- Nevertheless the backend must generate debugging info for
394 -- it, and this must be indicated explicitly.
396 declare
397 Loc : constant Source_Ptr := Sloc (N);
398 SCS : constant Boolean :=
399 Get_Comes_From_Source_Default;
401 begin
402 Set_Comes_From_Source_Default (False);
403 Lib_Unit :=
404 Make_Compilation_Unit (Loc,
405 Context_Items => New_Copy_List (Context_Items (N)),
406 Unit =>
407 Make_Subprogram_Declaration (Sloc (N),
408 Specification =>
409 Copy_Separate_Tree
410 (Specification (Unit_Node))),
411 Aux_Decls_Node =>
412 Make_Compilation_Unit_Aux (Loc));
414 Set_Library_Unit (N, Lib_Unit);
415 Set_Parent_Spec (Unit (Lib_Unit), Cunit (Unum));
416 Semantics (Lib_Unit);
417 Set_Acts_As_Spec (N, False);
418 Set_Needs_Debug_Info (Defining_Entity (Unit (Lib_Unit)));
419 Set_Comes_From_Source_Default (SCS);
420 end;
421 end if;
422 end if;
424 -- Here for subprogram with separate declaration
426 else
427 Semantics (Lib_Unit);
428 Check_Unused_Withs (Get_Cunit_Unit_Number (Lib_Unit));
429 Version_Update (N, Lib_Unit);
430 end if;
432 if Nkind (Defining_Unit_Name (Specification (Unit_Node))) =
433 N_Defining_Program_Unit_Name
434 then
435 Generate_Parent_References (
436 Specification (Unit_Node),
437 Scope (Defining_Entity (Unit (Lib_Unit))));
438 end if;
439 end if;
441 -- If it is a child unit, the parent must be elaborated first
442 -- and we update version, since we are dependent on our parent.
444 if Is_Child_Spec (Unit_Node) then
446 -- The analysis of the parent is done with style checks off
448 declare
449 Save_Style_Check : constant Boolean := Style_Check;
450 Save_C_Restrict : constant Save_Cunit_Boolean_Restrictions :=
451 Cunit_Boolean_Restrictions_Save;
453 begin
454 if not GNAT_Mode then
455 Style_Check := False;
456 end if;
458 Semantics (Parent_Spec (Unit_Node));
459 Version_Update (N, Parent_Spec (Unit_Node));
460 Style_Check := Save_Style_Check;
461 Cunit_Boolean_Restrictions_Restore (Save_C_Restrict);
462 end;
463 end if;
465 -- With the analysis done, install the context. Note that we can't
466 -- install the context from the with clauses as we analyze them,
467 -- because each with clause must be analyzed in a clean visibility
468 -- context, so we have to wait and install them all at once.
470 Install_Context (N);
472 if Is_Child_Spec (Unit_Node) then
474 -- Set the entities of all parents in the program_unit_name
476 Generate_Parent_References (
477 Unit_Node, Get_Parent_Entity (Unit (Parent_Spec (Unit_Node))));
478 end if;
480 -- All components of the context: with-clauses, library unit, ancestors
481 -- if any, (and their context) are analyzed and installed. Now analyze
482 -- the unit itself, which is either a package, subprogram spec or body.
484 Analyze (Unit_Node);
486 -- The above call might have made Unit_Node an N_Subprogram_Body
487 -- from something else, so propagate any Acts_As_Spec flag.
489 if Nkind (Unit_Node) = N_Subprogram_Body
490 and then Acts_As_Spec (Unit_Node)
491 then
492 Set_Acts_As_Spec (N);
493 end if;
495 -- Register predefined units in Rtsfind
497 declare
498 Unum : constant Unit_Number_Type := Get_Source_Unit (Sloc (N));
499 begin
500 if Is_Predefined_File_Name (Unit_File_Name (Unum)) then
501 Set_RTU_Loaded (Unit_Node);
502 end if;
503 end;
505 -- Treat compilation unit pragmas that appear after the library unit
507 if Present (Pragmas_After (Aux_Decls_Node (N))) then
508 declare
509 Prag_Node : Node_Id := First (Pragmas_After (Aux_Decls_Node (N)));
511 begin
512 while Present (Prag_Node) loop
513 Analyze (Prag_Node);
514 Next (Prag_Node);
515 end loop;
516 end;
517 end if;
519 -- Generate distribution stubs if requested and no error
521 if N = Main_Cunit
522 and then (Distribution_Stub_Mode = Generate_Receiver_Stub_Body
523 or else
524 Distribution_Stub_Mode = Generate_Caller_Stub_Body)
525 and then not Fatal_Error (Main_Unit)
526 then
527 if Is_RCI_Pkg_Spec_Or_Body (N) then
529 -- Regular RCI package
531 Add_Stub_Constructs (N);
533 elsif (Nkind (Unit_Node) = N_Package_Declaration
534 and then Is_Shared_Passive (Defining_Entity
535 (Specification (Unit_Node))))
536 or else (Nkind (Unit_Node) = N_Package_Body
537 and then
538 Is_Shared_Passive (Corresponding_Spec (Unit_Node)))
539 then
540 -- Shared passive package
542 Add_Stub_Constructs (N);
544 elsif Nkind (Unit_Node) = N_Package_Instantiation
545 and then
546 Is_Remote_Call_Interface
547 (Defining_Entity (Specification (Instance_Spec (Unit_Node))))
548 then
549 -- Instantiation of a RCI generic package
551 Add_Stub_Constructs (N);
552 end if;
554 end if;
556 if Nkind (Unit_Node) = N_Package_Declaration
557 or else Nkind (Unit_Node) in N_Generic_Declaration
558 or else Nkind (Unit_Node) = N_Package_Renaming_Declaration
559 or else Nkind (Unit_Node) = N_Subprogram_Declaration
560 then
561 Remove_Unit_From_Visibility (Defining_Entity (Unit_Node));
563 -- If the unit is an instantiation whose body will be elaborated
564 -- for inlining purposes, use the the proper entity of the instance.
566 elsif Nkind (Unit_Node) = N_Package_Instantiation
567 and then not Error_Posted (Unit_Node)
568 then
569 Remove_Unit_From_Visibility
570 (Defining_Entity (Instance_Spec (Unit_Node)));
572 elsif Nkind (Unit_Node) = N_Package_Body
573 or else (Nkind (Unit_Node) = N_Subprogram_Body
574 and then not Acts_As_Spec (Unit_Node))
575 then
576 -- Bodies that are not the main unit are compiled if they
577 -- are generic or contain generic or inlined units. Their
578 -- analysis brings in the context of the corresponding spec
579 -- (unit declaration) which must be removed as well, to
580 -- return the compilation environment to its proper state.
582 Remove_Context (Lib_Unit);
583 Set_Is_Immediately_Visible (Defining_Entity (Unit (Lib_Unit)), False);
584 end if;
586 -- Last step is to deinstall the context we just installed
587 -- as well as the unit just compiled.
589 Remove_Context (N);
591 -- If this is the main unit and we are generating code, we must
592 -- check that all generic units in the context have a body if they
593 -- need it, even if they have not been instantiated. In the absence
594 -- of .ali files for generic units, we must force the load of the body,
595 -- just to produce the proper error if the body is absent. We skip this
596 -- verification if the main unit itself is generic.
598 if Get_Cunit_Unit_Number (N) = Main_Unit
599 and then Operating_Mode = Generate_Code
600 and then Expander_Active
601 then
602 -- Check whether the source for the body of the unit must be
603 -- included in a standalone library.
605 Check_Body_Needed_For_SAL (Cunit_Entity (Main_Unit));
607 -- Indicate that the main unit is now analyzed, to catch possible
608 -- circularities between it and generic bodies. Remove main unit
609 -- from visibility. This might seem superfluous, but the main unit
610 -- must not be visible in the generic body expansions that follow.
612 Set_Analyzed (N, True);
613 Set_Is_Immediately_Visible (Cunit_Entity (Main_Unit), False);
615 declare
616 Item : Node_Id;
617 Nam : Entity_Id;
618 Un : Unit_Number_Type;
620 Save_Style_Check : constant Boolean := Style_Check;
621 Save_C_Restrict : constant Save_Cunit_Boolean_Restrictions :=
622 Cunit_Boolean_Restrictions_Save;
624 begin
625 Item := First (Context_Items (N));
626 while Present (Item) loop
628 -- Ada 2005 (AI-50217): Do not consider limited-withed units
630 if Nkind (Item) = N_With_Clause
631 and then not Implicit_With (Item)
632 and then not Limited_Present (Item)
633 then
634 Nam := Entity (Name (Item));
636 if (Is_Generic_Subprogram (Nam)
637 and then not Is_Intrinsic_Subprogram (Nam))
638 or else (Ekind (Nam) = E_Generic_Package
639 and then Unit_Requires_Body (Nam))
640 then
641 Style_Check := False;
643 if Present (Renamed_Object (Nam)) then
644 Un :=
645 Load_Unit
646 (Load_Name => Get_Body_Name
647 (Get_Unit_Name
648 (Unit_Declaration_Node
649 (Renamed_Object (Nam)))),
650 Required => False,
651 Subunit => False,
652 Error_Node => N,
653 Renamings => True);
654 else
655 Un :=
656 Load_Unit
657 (Load_Name => Get_Body_Name
658 (Get_Unit_Name (Item)),
659 Required => False,
660 Subunit => False,
661 Error_Node => N,
662 Renamings => True);
663 end if;
665 if Un = No_Unit then
666 Error_Msg_NE
667 ("body of generic unit& not found", Item, Nam);
668 exit;
670 elsif not Analyzed (Cunit (Un))
671 and then Un /= Main_Unit
672 and then not Fatal_Error (Un)
673 then
674 Style_Check := False;
675 Semantics (Cunit (Un));
676 end if;
677 end if;
678 end if;
680 Next (Item);
681 end loop;
683 Style_Check := Save_Style_Check;
684 Cunit_Boolean_Restrictions_Restore (Save_C_Restrict);
685 end;
686 end if;
688 -- Deal with creating elaboration Boolean if needed. We create an
689 -- elaboration boolean only for units that come from source since
690 -- units manufactured by the compiler never need elab checks.
692 if Comes_From_Source (N)
693 and then
694 (Nkind (Unit (N)) = N_Package_Declaration or else
695 Nkind (Unit (N)) = N_Generic_Package_Declaration or else
696 Nkind (Unit (N)) = N_Subprogram_Declaration or else
697 Nkind (Unit (N)) = N_Generic_Subprogram_Declaration)
698 then
699 declare
700 Loc : constant Source_Ptr := Sloc (N);
701 Unum : constant Unit_Number_Type := Get_Source_Unit (Loc);
703 begin
704 Spec_Id := Defining_Entity (Unit (N));
705 Generate_Definition (Spec_Id);
707 -- See if an elaboration entity is required for possible
708 -- access before elaboration checking. Note that we must
709 -- allow for this even if -gnatE is not set, since a client
710 -- may be compiled in -gnatE mode and reference the entity.
712 -- Case of units which do not require elaboration checks
715 -- Pure units do not need checks
717 Is_Pure (Spec_Id)
719 -- Preelaborated units do not need checks
721 or else Is_Preelaborated (Spec_Id)
723 -- No checks needed if pagma Elaborate_Body present
725 or else Has_Pragma_Elaborate_Body (Spec_Id)
727 -- No checks needed if unit does not require a body
729 or else not Unit_Requires_Body (Spec_Id)
731 -- No checks needed for predefined files
733 or else Is_Predefined_File_Name (Unit_File_Name (Unum))
735 -- No checks required if no separate spec
737 or else Acts_As_Spec (N)
738 then
739 -- This is a case where we only need the entity for
740 -- checking to prevent multiple elaboration checks.
742 Set_Elaboration_Entity_Required (Spec_Id, False);
744 -- Case of elaboration entity is required for access before
745 -- elaboration checking (so certainly we must build it!)
747 else
748 Set_Elaboration_Entity_Required (Spec_Id, True);
749 end if;
751 Build_Elaboration_Entity (N, Spec_Id);
752 end;
753 end if;
755 -- Finally, freeze the compilation unit entity. This for sure is needed
756 -- because of some warnings that can be output (see Freeze_Subprogram),
757 -- but may in general be required. If freezing actions result, place
758 -- them in the compilation unit actions list, and analyze them.
760 declare
761 Loc : constant Source_Ptr := Sloc (N);
762 L : constant List_Id :=
763 Freeze_Entity (Cunit_Entity (Current_Sem_Unit), Loc);
765 begin
766 while Is_Non_Empty_List (L) loop
767 Insert_Library_Level_Action (Remove_Head (L));
768 end loop;
769 end;
771 Set_Analyzed (N);
773 if Nkind (Unit_Node) = N_Package_Declaration
774 and then Get_Cunit_Unit_Number (N) /= Main_Unit
775 and then Expander_Active
776 then
777 declare
778 Save_Style_Check : constant Boolean := Style_Check;
779 Save_Warning : constant Warning_Mode_Type := Warning_Mode;
780 Options : Style_Check_Options;
782 begin
783 Save_Style_Check_Options (Options);
784 Reset_Style_Check_Options;
785 Opt.Warning_Mode := Suppress;
786 Check_Body_For_Inlining (N, Defining_Entity (Unit_Node));
788 Reset_Style_Check_Options;
789 Set_Style_Check_Options (Options);
790 Style_Check := Save_Style_Check;
791 Warning_Mode := Save_Warning;
792 end;
793 end if;
794 end Analyze_Compilation_Unit;
796 ---------------------
797 -- Analyze_Context --
798 ---------------------
800 procedure Analyze_Context (N : Node_Id) is
801 Ukind : constant Node_Kind := Nkind (Unit (N));
802 Item : Node_Id;
804 begin
805 -- Loop through context items. This is done in two:
806 -- a) The first pass analyzes non-limited with-clauses
807 -- b) The second pass analyzes limited_with clauses (Ada 2005: AI-50217)
809 Item := First (Context_Items (N));
810 while Present (Item) loop
812 -- For with clause, analyze the with clause, and then update
813 -- the version, since we are dependent on a unit that we with.
815 if Nkind (Item) = N_With_Clause
816 and then not Limited_Present (Item)
817 then
818 -- Skip analyzing with clause if no unit, nothing to do (this
819 -- happens for a with that references a non-existant unit)
821 if Present (Library_Unit (Item)) then
822 Analyze (Item);
823 end if;
825 if not Implicit_With (Item) then
826 Version_Update (N, Library_Unit (Item));
827 end if;
829 -- But skip use clauses at this stage, since we don't want to do
830 -- any installing of potentially use visible entities until we
831 -- we actually install the complete context (in Install_Context).
832 -- Otherwise things can get installed in the wrong context.
833 -- Similarly, pragmas are analyzed in Install_Context, after all
834 -- the implicit with's on parent units are generated.
836 else
837 null;
838 end if;
840 Next (Item);
841 end loop;
843 -- Second pass: examine all limited_with clauses
845 Item := First (Context_Items (N));
846 while Present (Item) loop
847 if Nkind (Item) = N_With_Clause
848 and then Limited_Present (Item)
849 then
850 -- No need to check errors on implicitly generated limited-with
851 -- clauses.
853 if not Implicit_With (Item) then
855 -- Check compilation unit containing the limited-with clause
857 if Ukind /= N_Package_Declaration
858 and then Ukind /= N_Subprogram_Declaration
859 and then Ukind /= N_Package_Renaming_Declaration
860 and then Ukind /= N_Subprogram_Renaming_Declaration
861 and then Ukind not in N_Generic_Declaration
862 and then Ukind not in N_Generic_Renaming_Declaration
863 and then Ukind not in N_Generic_Instantiation
864 then
865 Error_Msg_N ("limited with_clause not allowed here", Item);
867 -- Check wrong use of a limited with clause applied to the
868 -- compilation unit containing the limited-with clause.
870 -- limited with P.Q;
871 -- package P.Q is ...
873 elsif Unit (Library_Unit (Item)) = Unit (N) then
874 Error_Msg_N ("wrong use of limited-with clause", Item);
876 -- Check wrong use of limited-with clause applied to some
877 -- immediate ancestor.
879 elsif Is_Child_Spec (Unit (N)) then
880 declare
881 Lib_U : constant Entity_Id := Unit (Library_Unit (Item));
882 P : Node_Id;
884 begin
885 P := Parent_Spec (Unit (N));
886 loop
887 if Unit (P) = Lib_U then
888 Error_Msg_N ("limited with_clause of immediate "
889 & "ancestor not allowed", Item);
890 exit;
891 end if;
893 exit when not Is_Child_Spec (Unit (P));
894 P := Parent_Spec (Unit (P));
895 end loop;
896 end;
897 end if;
899 -- Check if the limited-withed unit is already visible through
900 -- some context clause of the current compilation unit or some
901 -- ancestor of the current compilation unit.
903 declare
904 Lim_Unit_Name : constant Node_Id := Name (Item);
905 Comp_Unit : Node_Id;
906 It : Node_Id;
907 Unit_Name : Node_Id;
909 begin
910 Comp_Unit := N;
911 loop
912 It := First (Context_Items (Comp_Unit));
913 while Present (It) loop
914 if Item /= It
915 and then Nkind (It) = N_With_Clause
916 and then not Limited_Present (It)
917 and then
918 (Nkind (Unit (Library_Unit (It)))
919 = N_Package_Declaration
920 or else
921 Nkind (Unit (Library_Unit (It)))
922 = N_Package_Renaming_Declaration)
923 then
924 if Nkind (Unit (Library_Unit (It)))
925 = N_Package_Declaration
926 then
927 Unit_Name := Name (It);
928 else
929 Unit_Name := Name (Unit (Library_Unit (It)));
930 end if;
932 -- Check if the named package (or some ancestor)
933 -- leaves visible the full-view of the unit given
934 -- in the limited-with clause
936 loop
937 if Designate_Same_Unit (Lim_Unit_Name,
938 Unit_Name)
939 then
940 Error_Msg_Sloc := Sloc (It);
941 Error_Msg_NE
942 ("unlimited view visible through the"
943 & " context clause found #",
944 Item, It);
945 Error_Msg_N
946 ("simultaneous visibility of the limited"
947 & " and unlimited views not allowed"
948 , Item);
949 exit;
951 elsif Nkind (Unit_Name) = N_Identifier then
952 exit;
953 end if;
955 Unit_Name := Prefix (Unit_Name);
956 end loop;
957 end if;
959 Next (It);
960 end loop;
962 exit when not Is_Child_Spec (Unit (Comp_Unit));
964 Comp_Unit := Parent_Spec (Unit (Comp_Unit));
965 end loop;
966 end;
967 end if;
969 -- Skip analyzing with clause if no unit, see above
971 if Present (Library_Unit (Item)) then
972 Analyze (Item);
973 end if;
975 -- A limited_with does not impose an elaboration order, but
976 -- there is a semantic dependency for recompilation purposes.
978 if not Implicit_With (Item) then
979 Version_Update (N, Library_Unit (Item));
980 end if;
981 end if;
983 Next (Item);
984 end loop;
985 end Analyze_Context;
987 -------------------------------
988 -- Analyze_Package_Body_Stub --
989 -------------------------------
991 procedure Analyze_Package_Body_Stub (N : Node_Id) is
992 Id : constant Entity_Id := Defining_Identifier (N);
993 Nam : Entity_Id;
995 begin
996 -- The package declaration must be in the current declarative part
998 Check_Stub_Level (N);
999 Nam := Current_Entity_In_Scope (Id);
1001 if No (Nam) or else not Is_Package (Nam) then
1002 Error_Msg_N ("missing specification for package stub", N);
1004 elsif Has_Completion (Nam)
1005 and then Present (Corresponding_Body (Unit_Declaration_Node (Nam)))
1006 then
1007 Error_Msg_N ("duplicate or redundant stub for package", N);
1009 else
1010 -- Indicate that the body of the package exists. If we are doing
1011 -- only semantic analysis, the stub stands for the body. If we are
1012 -- generating code, the existence of the body will be confirmed
1013 -- when we load the proper body.
1015 Set_Has_Completion (Nam);
1016 Set_Scope (Defining_Entity (N), Current_Scope);
1017 Generate_Reference (Nam, Id, 'b');
1018 Analyze_Proper_Body (N, Nam);
1019 end if;
1020 end Analyze_Package_Body_Stub;
1022 -------------------------
1023 -- Analyze_Proper_Body --
1024 -------------------------
1026 procedure Analyze_Proper_Body (N : Node_Id; Nam : Entity_Id) is
1027 Subunit_Name : constant Unit_Name_Type := Get_Unit_Name (N);
1028 Unum : Unit_Number_Type;
1030 procedure Optional_Subunit;
1031 -- This procedure is called when the main unit is a stub, or when we
1032 -- are not generating code. In such a case, we analyze the subunit if
1033 -- present, which is user-friendly and in fact required for ASIS, but
1034 -- we don't complain if the subunit is missing.
1036 ----------------------
1037 -- Optional_Subunit --
1038 ----------------------
1040 procedure Optional_Subunit is
1041 Comp_Unit : Node_Id;
1043 begin
1044 -- Try to load subunit, but ignore any errors that occur during
1045 -- the loading of the subunit, by using the special feature in
1046 -- Errout to ignore all errors. Note that Fatal_Error will still
1047 -- be set, so we will be able to check for this case below.
1049 if not ASIS_Mode then
1050 Ignore_Errors_Enable := Ignore_Errors_Enable + 1;
1051 end if;
1053 Unum :=
1054 Load_Unit
1055 (Load_Name => Subunit_Name,
1056 Required => False,
1057 Subunit => True,
1058 Error_Node => N);
1060 if not ASIS_Mode then
1061 Ignore_Errors_Enable := Ignore_Errors_Enable - 1;
1062 end if;
1064 -- All done if we successfully loaded the subunit
1066 if Unum /= No_Unit
1067 and then (not Fatal_Error (Unum) or else Try_Semantics)
1068 then
1069 Comp_Unit := Cunit (Unum);
1071 -- If the file was empty or seriously mangled, the unit
1072 -- itself may be missing.
1074 if No (Unit (Comp_Unit)) then
1075 Error_Msg_N
1076 ("subunit does not contain expected proper body", N);
1078 elsif Nkind (Unit (Comp_Unit)) /= N_Subunit then
1079 Error_Msg_N
1080 ("expected SEPARATE subunit, found child unit",
1081 Cunit_Entity (Unum));
1082 else
1083 Set_Corresponding_Stub (Unit (Comp_Unit), N);
1084 Analyze_Subunit (Comp_Unit);
1085 Set_Library_Unit (N, Comp_Unit);
1086 end if;
1088 elsif Unum = No_Unit
1089 and then Present (Nam)
1090 then
1091 if Is_Protected_Type (Nam) then
1092 Set_Corresponding_Body (Parent (Nam), Defining_Identifier (N));
1093 else
1094 Set_Corresponding_Body (
1095 Unit_Declaration_Node (Nam), Defining_Identifier (N));
1096 end if;
1097 end if;
1098 end Optional_Subunit;
1100 -- Start of processing for Analyze_Proper_Body
1102 begin
1103 -- If the subunit is already loaded, it means that the main unit
1104 -- is a subunit, and that the current unit is one of its parents
1105 -- which was being analyzed to provide the needed context for the
1106 -- analysis of the subunit. In this case we analyze the subunit and
1107 -- continue with the parent, without looking a subsequent subunits.
1109 if Is_Loaded (Subunit_Name) then
1111 -- If the proper body is already linked to the stub node,
1112 -- the stub is in a generic unit and just needs analyzing.
1114 if Present (Library_Unit (N)) then
1115 Set_Corresponding_Stub (Unit (Library_Unit (N)), N);
1116 Analyze_Subunit (Library_Unit (N));
1118 -- Otherwise we must load the subunit and link to it
1120 else
1121 -- Load the subunit, this must work, since we originally
1122 -- loaded the subunit earlier on. So this will not really
1123 -- load it, just give access to it.
1125 Unum :=
1126 Load_Unit
1127 (Load_Name => Subunit_Name,
1128 Required => True,
1129 Subunit => False,
1130 Error_Node => N);
1132 -- And analyze the subunit in the parent context (note that we
1133 -- do not call Semantics, since that would remove the parent
1134 -- context). Because of this, we have to manually reset the
1135 -- compiler state to Analyzing since it got destroyed by Load.
1137 if Unum /= No_Unit then
1138 Compiler_State := Analyzing;
1140 -- Check that the proper body is a subunit and not a child
1141 -- unit. If the unit was previously loaded, the error will
1142 -- have been emitted when copying the generic node, so we
1143 -- just return to avoid cascaded errors.
1145 if Nkind (Unit (Cunit (Unum))) /= N_Subunit then
1146 return;
1147 end if;
1149 Set_Corresponding_Stub (Unit (Cunit (Unum)), N);
1150 Analyze_Subunit (Cunit (Unum));
1151 Set_Library_Unit (N, Cunit (Unum));
1152 end if;
1153 end if;
1155 -- If the main unit is a subunit, then we are just performing semantic
1156 -- analysis on that subunit, and any other subunits of any parent unit
1157 -- should be ignored, except that if we are building trees for ASIS
1158 -- usage we want to annotate the stub properly.
1160 elsif Nkind (Unit (Cunit (Main_Unit))) = N_Subunit
1161 and then Subunit_Name /= Unit_Name (Main_Unit)
1162 then
1163 if ASIS_Mode then
1164 Optional_Subunit;
1165 end if;
1167 -- But before we return, set the flag for unloaded subunits. This
1168 -- will suppress junk warnings of variables in the same declarative
1169 -- part (or a higher level one) that are in danger of looking unused
1170 -- when in fact there might be a declaration in the subunit that we
1171 -- do not intend to load.
1173 Unloaded_Subunits := True;
1174 return;
1176 -- If the subunit is not already loaded, and we are generating code,
1177 -- then this is the case where compilation started from the parent,
1178 -- and we are generating code for an entire subunit tree. In that
1179 -- case we definitely need to load the subunit.
1181 -- In order to continue the analysis with the rest of the parent,
1182 -- and other subunits, we load the unit without requiring its
1183 -- presence, and emit a warning if not found, rather than terminating
1184 -- the compilation abruptly, as for other missing file problems.
1186 elsif Original_Operating_Mode = Generate_Code then
1188 -- If the proper body is already linked to the stub node,
1189 -- the stub is in a generic unit and just needs analyzing.
1191 -- We update the version. Although we are not technically
1192 -- semantically dependent on the subunit, given our approach
1193 -- of macro substitution of subunits, it makes sense to
1194 -- include it in the version identification.
1196 if Present (Library_Unit (N)) then
1197 Set_Corresponding_Stub (Unit (Library_Unit (N)), N);
1198 Analyze_Subunit (Library_Unit (N));
1199 Version_Update (Cunit (Main_Unit), Library_Unit (N));
1201 -- Otherwise we must load the subunit and link to it
1203 else
1204 Unum :=
1205 Load_Unit
1206 (Load_Name => Subunit_Name,
1207 Required => False,
1208 Subunit => True,
1209 Error_Node => N);
1211 if Original_Operating_Mode = Generate_Code
1212 and then Unum = No_Unit
1213 then
1214 Error_Msg_Name_1 := Subunit_Name;
1215 Error_Msg_Name_2 :=
1216 Get_File_Name (Subunit_Name, Subunit => True);
1217 Error_Msg_N
1218 ("subunit% in file{ not found!?", N);
1219 Subunits_Missing := True;
1220 end if;
1222 -- Load_Unit may reset Compiler_State, since it may have been
1223 -- necessary to parse an additional units, so we make sure
1224 -- that we reset it to the Analyzing state.
1226 Compiler_State := Analyzing;
1228 if Unum /= No_Unit
1229 and then (not Fatal_Error (Unum) or else Try_Semantics)
1230 then
1231 if Debug_Flag_L then
1232 Write_Str ("*** Loaded subunit from stub. Analyze");
1233 Write_Eol;
1234 end if;
1236 declare
1237 Comp_Unit : constant Node_Id := Cunit (Unum);
1239 begin
1240 -- Check for child unit instead of subunit
1242 if Nkind (Unit (Comp_Unit)) /= N_Subunit then
1243 Error_Msg_N
1244 ("expected SEPARATE subunit, found child unit",
1245 Cunit_Entity (Unum));
1247 -- OK, we have a subunit, so go ahead and analyze it,
1248 -- and set Scope of entity in stub, for ASIS use.
1250 else
1251 Set_Corresponding_Stub (Unit (Comp_Unit), N);
1252 Analyze_Subunit (Comp_Unit);
1253 Set_Library_Unit (N, Comp_Unit);
1255 -- We update the version. Although we are not technically
1256 -- semantically dependent on the subunit, given our
1257 -- approach of macro substitution of subunits, it makes
1258 -- sense to include it in the version identification.
1260 Version_Update (Cunit (Main_Unit), Comp_Unit);
1261 end if;
1262 end;
1263 end if;
1264 end if;
1266 -- The remaining case is when the subunit is not already loaded and
1267 -- we are not generating code. In this case we are just performing
1268 -- semantic analysis on the parent, and we are not interested in
1269 -- the subunit. For subprograms, analyze the stub as a body. For
1270 -- other entities the stub has already been marked as completed.
1272 else
1273 Optional_Subunit;
1274 end if;
1276 end Analyze_Proper_Body;
1278 ----------------------------------
1279 -- Analyze_Protected_Body_Stub --
1280 ----------------------------------
1282 procedure Analyze_Protected_Body_Stub (N : Node_Id) is
1283 Nam : Entity_Id := Current_Entity_In_Scope (Defining_Identifier (N));
1285 begin
1286 Check_Stub_Level (N);
1288 -- First occurence of name may have been as an incomplete type
1290 if Present (Nam) and then Ekind (Nam) = E_Incomplete_Type then
1291 Nam := Full_View (Nam);
1292 end if;
1294 if No (Nam)
1295 or else not Is_Protected_Type (Etype (Nam))
1296 then
1297 Error_Msg_N ("missing specification for Protected body", N);
1298 else
1299 Set_Scope (Defining_Entity (N), Current_Scope);
1300 Set_Has_Completion (Etype (Nam));
1301 Generate_Reference (Nam, Defining_Identifier (N), 'b');
1302 Analyze_Proper_Body (N, Etype (Nam));
1303 end if;
1304 end Analyze_Protected_Body_Stub;
1306 ----------------------------------
1307 -- Analyze_Subprogram_Body_Stub --
1308 ----------------------------------
1310 -- A subprogram body stub can appear with or without a previous
1311 -- specification. If there is one, the analysis of the body will
1312 -- find it and verify conformance. The formals appearing in the
1313 -- specification of the stub play no role, except for requiring an
1314 -- additional conformance check. If there is no previous subprogram
1315 -- declaration, the stub acts as a spec, and provides the defining
1316 -- entity for the subprogram.
1318 procedure Analyze_Subprogram_Body_Stub (N : Node_Id) is
1319 Decl : Node_Id;
1321 begin
1322 Check_Stub_Level (N);
1324 -- Verify that the identifier for the stub is unique within this
1325 -- declarative part.
1327 if Nkind (Parent (N)) = N_Block_Statement
1328 or else Nkind (Parent (N)) = N_Package_Body
1329 or else Nkind (Parent (N)) = N_Subprogram_Body
1330 then
1331 Decl := First (Declarations (Parent (N)));
1332 while Present (Decl)
1333 and then Decl /= N
1334 loop
1335 if Nkind (Decl) = N_Subprogram_Body_Stub
1336 and then (Chars (Defining_Unit_Name (Specification (Decl)))
1337 = Chars (Defining_Unit_Name (Specification (N))))
1338 then
1339 Error_Msg_N ("identifier for stub is not unique", N);
1340 end if;
1342 Next (Decl);
1343 end loop;
1344 end if;
1346 -- Treat stub as a body, which checks conformance if there is a previous
1347 -- declaration, or else introduces entity and its signature.
1349 Analyze_Subprogram_Body (N);
1350 Analyze_Proper_Body (N, Empty);
1351 end Analyze_Subprogram_Body_Stub;
1353 ---------------------
1354 -- Analyze_Subunit --
1355 ---------------------
1357 -- A subunit is compiled either by itself (for semantic checking)
1358 -- or as part of compiling the parent (for code generation). In
1359 -- either case, by the time we actually process the subunit, the
1360 -- parent has already been installed and analyzed. The node N is
1361 -- a compilation unit, whose context needs to be treated here,
1362 -- because we come directly here from the parent without calling
1363 -- Analyze_Compilation_Unit.
1365 -- The compilation context includes the explicit context of the
1366 -- subunit, and the context of the parent, together with the parent
1367 -- itself. In order to compile the current context, we remove the
1368 -- one inherited from the parent, in order to have a clean visibility
1369 -- table. We restore the parent context before analyzing the proper
1370 -- body itself. On exit, we remove only the explicit context of the
1371 -- subunit.
1373 procedure Analyze_Subunit (N : Node_Id) is
1374 Lib_Unit : constant Node_Id := Library_Unit (N);
1375 Par_Unit : constant Entity_Id := Current_Scope;
1377 Lib_Spec : Node_Id := Library_Unit (Lib_Unit);
1378 Num_Scopes : Int := 0;
1379 Use_Clauses : array (1 .. Scope_Stack.Last) of Node_Id;
1380 Enclosing_Child : Entity_Id := Empty;
1381 Svg : constant Suppress_Array := Scope_Suppress;
1383 procedure Analyze_Subunit_Context;
1384 -- Capture names in use clauses of the subunit. This must be done
1385 -- before re-installing parent declarations, because items in the
1386 -- context must not be hidden by declarations local to the parent.
1388 procedure Re_Install_Parents (L : Node_Id; Scop : Entity_Id);
1389 -- Recursive procedure to restore scope of all ancestors of subunit,
1390 -- from outermost in. If parent is not a subunit, the call to install
1391 -- context installs context of spec and (if parent is a child unit)
1392 -- the context of its parents as well. It is confusing that parents
1393 -- should be treated differently in both cases, but the semantics are
1394 -- just not identical.
1396 procedure Re_Install_Use_Clauses;
1397 -- As part of the removal of the parent scope, the use clauses are
1398 -- removed, to be reinstalled when the context of the subunit has
1399 -- been analyzed. Use clauses may also have been affected by the
1400 -- analysis of the context of the subunit, so they have to be applied
1401 -- again, to insure that the compilation environment of the rest of
1402 -- the parent unit is identical.
1404 procedure Remove_Scope;
1405 -- Remove current scope from scope stack, and preserve the list
1406 -- of use clauses in it, to be reinstalled after context is analyzed.
1408 -----------------------------
1409 -- Analyze_Subunit_Context --
1410 -----------------------------
1412 procedure Analyze_Subunit_Context is
1413 Item : Node_Id;
1414 Nam : Node_Id;
1415 Unit_Name : Entity_Id;
1417 begin
1418 Analyze_Context (N);
1420 -- Make withed units immediately visible. If child unit, make the
1421 -- ultimate parent immediately visible.
1423 Item := First (Context_Items (N));
1424 while Present (Item) loop
1425 if Nkind (Item) = N_With_Clause then
1427 -- Protect frontend against previous errors in context clauses
1429 if Nkind (Name (Item)) /= N_Selected_Component then
1430 Unit_Name := Entity (Name (Item));
1431 while Is_Child_Unit (Unit_Name) loop
1432 Set_Is_Visible_Child_Unit (Unit_Name);
1433 Unit_Name := Scope (Unit_Name);
1434 end loop;
1436 if not Is_Immediately_Visible (Unit_Name) then
1437 Set_Is_Immediately_Visible (Unit_Name);
1438 Set_Context_Installed (Item);
1439 end if;
1440 end if;
1442 elsif Nkind (Item) = N_Use_Package_Clause then
1443 Nam := First (Names (Item));
1444 while Present (Nam) loop
1445 Analyze (Nam);
1446 Next (Nam);
1447 end loop;
1449 elsif Nkind (Item) = N_Use_Type_Clause then
1450 Nam := First (Subtype_Marks (Item));
1451 while Present (Nam) loop
1452 Analyze (Nam);
1453 Next (Nam);
1454 end loop;
1455 end if;
1457 Next (Item);
1458 end loop;
1460 -- Reset visibility of withed units. They will be made visible
1461 -- again when we install the subunit context.
1463 Item := First (Context_Items (N));
1464 while Present (Item) loop
1465 if Nkind (Item) = N_With_Clause
1467 -- Protect frontend against previous errors in context clauses
1469 and then Nkind (Name (Item)) /= N_Selected_Component
1470 then
1471 Unit_Name := Entity (Name (Item));
1472 while Is_Child_Unit (Unit_Name) loop
1473 Set_Is_Visible_Child_Unit (Unit_Name, False);
1474 Unit_Name := Scope (Unit_Name);
1475 end loop;
1477 if Context_Installed (Item) then
1478 Set_Is_Immediately_Visible (Unit_Name, False);
1479 Set_Context_Installed (Item, False);
1480 end if;
1481 end if;
1483 Next (Item);
1484 end loop;
1485 end Analyze_Subunit_Context;
1487 ------------------------
1488 -- Re_Install_Parents --
1489 ------------------------
1491 procedure Re_Install_Parents (L : Node_Id; Scop : Entity_Id) is
1492 E : Entity_Id;
1494 begin
1495 if Nkind (Unit (L)) = N_Subunit then
1496 Re_Install_Parents (Library_Unit (L), Scope (Scop));
1497 end if;
1499 Install_Context (L);
1501 -- If the subunit occurs within a child unit, we must restore the
1502 -- immediate visibility of any siblings that may occur in context.
1504 if Present (Enclosing_Child) then
1505 Install_Siblings (Enclosing_Child, L);
1506 end if;
1508 New_Scope (Scop);
1510 if Scop /= Par_Unit then
1511 Set_Is_Immediately_Visible (Scop);
1512 end if;
1514 -- Make entities in scope visible again. For child units, restore
1515 -- visibility only if they are actually in context.
1517 E := First_Entity (Current_Scope);
1518 while Present (E) loop
1519 if not Is_Child_Unit (E)
1520 or else Is_Visible_Child_Unit (E)
1521 then
1522 Set_Is_Immediately_Visible (E);
1523 end if;
1525 Next_Entity (E);
1526 end loop;
1528 -- A subunit appears within a body, and for a nested subunits
1529 -- all the parents are bodies. Restore full visibility of their
1530 -- private entities.
1532 if Ekind (Scop) = E_Package then
1533 Set_In_Package_Body (Scop);
1534 Install_Private_Declarations (Scop);
1535 end if;
1536 end Re_Install_Parents;
1538 ----------------------------
1539 -- Re_Install_Use_Clauses --
1540 ----------------------------
1542 procedure Re_Install_Use_Clauses is
1543 U : Node_Id;
1544 begin
1545 for J in reverse 1 .. Num_Scopes loop
1546 U := Use_Clauses (J);
1547 Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause := U;
1548 Install_Use_Clauses (U, Force_Installation => True);
1549 end loop;
1550 end Re_Install_Use_Clauses;
1552 ------------------
1553 -- Remove_Scope --
1554 ------------------
1556 procedure Remove_Scope is
1557 E : Entity_Id;
1559 begin
1560 Num_Scopes := Num_Scopes + 1;
1561 Use_Clauses (Num_Scopes) :=
1562 Scope_Stack.Table (Scope_Stack.Last).First_Use_Clause;
1564 E := First_Entity (Current_Scope);
1565 while Present (E) loop
1566 Set_Is_Immediately_Visible (E, False);
1567 Next_Entity (E);
1568 end loop;
1570 if Is_Child_Unit (Current_Scope) then
1571 Enclosing_Child := Current_Scope;
1572 end if;
1574 Pop_Scope;
1575 end Remove_Scope;
1577 -- Start of processing for Analyze_Subunit
1579 begin
1580 if not Is_Empty_List (Context_Items (N)) then
1582 -- Save current use clauses
1584 Remove_Scope;
1585 Remove_Context (Lib_Unit);
1587 -- Now remove parents and their context, including enclosing
1588 -- subunits and the outer parent body which is not a subunit.
1590 if Present (Lib_Spec) then
1591 Remove_Context (Lib_Spec);
1593 while Nkind (Unit (Lib_Spec)) = N_Subunit loop
1594 Lib_Spec := Library_Unit (Lib_Spec);
1595 Remove_Scope;
1596 Remove_Context (Lib_Spec);
1597 end loop;
1599 if Nkind (Unit (Lib_Unit)) = N_Subunit then
1600 Remove_Scope;
1601 end if;
1603 if Nkind (Unit (Lib_Spec)) = N_Package_Body then
1604 Remove_Context (Library_Unit (Lib_Spec));
1605 end if;
1606 end if;
1608 Set_Is_Immediately_Visible (Par_Unit, False);
1610 Analyze_Subunit_Context;
1612 Re_Install_Parents (Lib_Unit, Par_Unit);
1613 Set_Is_Immediately_Visible (Par_Unit);
1615 -- If the context includes a child unit of the parent of the
1616 -- subunit, the parent will have been removed from visibility,
1617 -- after compiling that cousin in the context. The visibility
1618 -- of the parent must be restored now. This also applies if the
1619 -- context includes another subunit of the same parent which in
1620 -- turn includes a child unit in its context.
1622 if Ekind (Par_Unit) = E_Package then
1623 if not Is_Immediately_Visible (Par_Unit)
1624 or else (Present (First_Entity (Par_Unit))
1625 and then not Is_Immediately_Visible
1626 (First_Entity (Par_Unit)))
1627 then
1628 Set_Is_Immediately_Visible (Par_Unit);
1629 Install_Visible_Declarations (Par_Unit);
1630 Install_Private_Declarations (Par_Unit);
1631 end if;
1632 end if;
1634 Re_Install_Use_Clauses;
1635 Install_Context (N);
1637 -- Restore state of suppress flags for current body
1639 Scope_Suppress := Svg;
1641 -- If the subunit is within a child unit, then siblings of any
1642 -- parent unit that appear in the context clause of the subunit
1643 -- must also be made immediately visible.
1645 if Present (Enclosing_Child) then
1646 Install_Siblings (Enclosing_Child, N);
1647 end if;
1649 end if;
1651 Analyze (Proper_Body (Unit (N)));
1652 Remove_Context (N);
1653 end Analyze_Subunit;
1655 ----------------------------
1656 -- Analyze_Task_Body_Stub --
1657 ----------------------------
1659 procedure Analyze_Task_Body_Stub (N : Node_Id) is
1660 Nam : Entity_Id := Current_Entity_In_Scope (Defining_Identifier (N));
1661 Loc : constant Source_Ptr := Sloc (N);
1663 begin
1664 Check_Stub_Level (N);
1666 -- First occurence of name may have been as an incomplete type
1668 if Present (Nam) and then Ekind (Nam) = E_Incomplete_Type then
1669 Nam := Full_View (Nam);
1670 end if;
1672 if No (Nam)
1673 or else not Is_Task_Type (Etype (Nam))
1674 then
1675 Error_Msg_N ("missing specification for task body", N);
1676 else
1677 Set_Scope (Defining_Entity (N), Current_Scope);
1678 Generate_Reference (Nam, Defining_Identifier (N), 'b');
1679 Set_Has_Completion (Etype (Nam));
1680 Analyze_Proper_Body (N, Etype (Nam));
1682 -- Set elaboration flag to indicate that entity is callable.
1683 -- This cannot be done in the expansion of the body itself,
1684 -- because the proper body is not in a declarative part. This
1685 -- is only done if expansion is active, because the context
1686 -- may be generic and the flag not defined yet.
1688 if Expander_Active then
1689 Insert_After (N,
1690 Make_Assignment_Statement (Loc,
1691 Name =>
1692 Make_Identifier (Loc,
1693 New_External_Name (Chars (Etype (Nam)), 'E')),
1694 Expression => New_Reference_To (Standard_True, Loc)));
1695 end if;
1697 end if;
1698 end Analyze_Task_Body_Stub;
1700 -------------------------
1701 -- Analyze_With_Clause --
1702 -------------------------
1704 -- Analyze the declaration of a unit in a with clause. At end,
1705 -- label the with clause with the defining entity for the unit.
1707 procedure Analyze_With_Clause (N : Node_Id) is
1709 -- Retrieve the original kind of the unit node, before analysis.
1710 -- If it is a subprogram instantiation, its analysis below will
1711 -- rewrite as the declaration of the wrapper package. If the same
1712 -- instantiation appears indirectly elsewhere in the context, it
1713 -- will have been analyzed already.
1715 Unit_Kind : constant Node_Kind :=
1716 Nkind (Original_Node (Unit (Library_Unit (N))));
1718 E_Name : Entity_Id;
1719 Par_Name : Entity_Id;
1720 Pref : Node_Id;
1721 U : Node_Id;
1723 Intunit : Boolean;
1724 -- Set True if the unit currently being compiled is an internal unit
1726 Save_Style_Check : constant Boolean := Opt.Style_Check;
1727 Save_C_Restrict : constant Save_Cunit_Boolean_Restrictions :=
1728 Cunit_Boolean_Restrictions_Save;
1730 begin
1731 if Limited_Present (N) then
1733 -- Ada 2005 (AI-50217): Build visibility structures but do not
1734 -- analyze unit
1736 Build_Limited_Views (N);
1737 return;
1738 end if;
1740 -- We reset ordinary style checking during the analysis of a with'ed
1741 -- unit, but we do NOT reset GNAT special analysis mode (the latter
1742 -- definitely *does* apply to with'ed units).
1744 if not GNAT_Mode then
1745 Style_Check := False;
1746 end if;
1748 -- If the library unit is a predefined unit, and we are in high
1749 -- integrity mode, then temporarily reset Configurable_Run_Time_Mode
1750 -- for the analysis of the with'ed unit. This mode does not prevent
1751 -- explicit with'ing of run-time units.
1753 if Configurable_Run_Time_Mode
1754 and then
1755 Is_Predefined_File_Name
1756 (Unit_File_Name (Get_Source_Unit (Unit (Library_Unit (N)))))
1757 then
1758 Configurable_Run_Time_Mode := False;
1759 Semantics (Library_Unit (N));
1760 Configurable_Run_Time_Mode := True;
1762 else
1763 Semantics (Library_Unit (N));
1764 end if;
1766 U := Unit (Library_Unit (N));
1767 Check_Restriction_No_Dependence (Name (N), N);
1768 Intunit := Is_Internal_File_Name (Unit_File_Name (Current_Sem_Unit));
1770 -- Following checks are skipped for dummy packages (those supplied
1771 -- for with's where no matching file could be found). Such packages
1772 -- are identified by the Sloc value being set to No_Location
1774 if Sloc (U) /= No_Location then
1776 -- Check restrictions, except that we skip the check if this
1777 -- is an internal unit unless we are compiling the internal
1778 -- unit as the main unit. We also skip this for dummy packages.
1780 if not Intunit or else Current_Sem_Unit = Main_Unit then
1781 Check_Restricted_Unit (Unit_Name (Get_Source_Unit (U)), N);
1782 end if;
1784 -- Check for inappropriate with of internal implementation unit
1785 -- if we are currently compiling the main unit and the main unit
1786 -- is itself not an internal unit. We do not issue this message
1787 -- for implicit with's generated by the compiler itself.
1789 if Implementation_Unit_Warnings
1790 and then Current_Sem_Unit = Main_Unit
1791 and then not Intunit
1792 and then not Implicit_With (N)
1793 and then not GNAT_Mode
1794 then
1795 declare
1796 U_Kind : constant Kind_Of_Unit :=
1797 Get_Kind_Of_Unit (Get_Source_Unit (U));
1799 begin
1800 if U_Kind = Implementation_Unit then
1801 Error_Msg_N ("& is an internal 'G'N'A'T unit?", Name (N));
1802 Error_Msg_N
1803 ("\use of this unit is non-portable " &
1804 "and version-dependent?",
1805 Name (N));
1807 elsif U_Kind = Ada_05_Unit
1808 and then Ada_Version < Ada_05
1809 and then Warn_On_Ada_2005_Compatibility
1810 then
1811 Error_Msg_N ("& is an Ada 2005 unit?", Name (N));
1812 end if;
1813 end;
1814 end if;
1815 end if;
1817 -- Semantic analysis of a generic unit is performed on a copy of
1818 -- the original tree. Retrieve the entity on which semantic info
1819 -- actually appears.
1821 if Unit_Kind in N_Generic_Declaration then
1822 E_Name := Defining_Entity (U);
1824 -- Note: in the following test, Unit_Kind is the original Nkind, but
1825 -- in the case of an instantiation, semantic analysis above will
1826 -- have replaced the unit by its instantiated version. If the instance
1827 -- body has been generated, the instance now denotes the body entity.
1828 -- For visibility purposes we need the entity of its spec.
1830 elsif (Unit_Kind = N_Package_Instantiation
1831 or else Nkind (Original_Node (Unit (Library_Unit (N)))) =
1832 N_Package_Instantiation)
1833 and then Nkind (U) = N_Package_Body
1834 then
1835 E_Name := Corresponding_Spec (U);
1837 elsif Unit_Kind = N_Package_Instantiation
1838 and then Nkind (U) = N_Package_Instantiation
1839 then
1840 -- If the instance has not been rewritten as a package declaration,
1841 -- then it appeared already in a previous with clause. Retrieve
1842 -- the entity from the previous instance.
1844 E_Name := Defining_Entity (Specification (Instance_Spec (U)));
1846 elsif Unit_Kind = N_Procedure_Instantiation
1847 or else Unit_Kind = N_Function_Instantiation
1848 then
1849 -- Instantiation node is replaced with a package that contains
1850 -- renaming declarations and instance itself. The subprogram
1851 -- Instance is declared in the visible part of the wrapper package.
1853 E_Name := First_Entity (Defining_Entity (U));
1854 while Present (E_Name) loop
1855 exit when Is_Subprogram (E_Name)
1856 and then Is_Generic_Instance (E_Name);
1857 E_Name := Next_Entity (E_Name);
1858 end loop;
1860 elsif Unit_Kind = N_Package_Renaming_Declaration
1861 or else Unit_Kind in N_Generic_Renaming_Declaration
1862 then
1863 E_Name := Defining_Entity (U);
1865 elsif Unit_Kind = N_Subprogram_Body
1866 and then Nkind (Name (N)) = N_Selected_Component
1867 and then not Acts_As_Spec (Library_Unit (N))
1868 then
1869 -- For a child unit that has no spec, one has been created and
1870 -- analyzed. The entity required is that of the spec.
1872 E_Name := Corresponding_Spec (U);
1874 else
1875 E_Name := Defining_Entity (U);
1876 end if;
1878 if Nkind (Name (N)) = N_Selected_Component then
1880 -- Child unit in a with clause
1882 Change_Selected_Component_To_Expanded_Name (Name (N));
1883 end if;
1885 -- Restore style checks and restrictions
1887 Style_Check := Save_Style_Check;
1888 Cunit_Boolean_Restrictions_Restore (Save_C_Restrict);
1890 -- Record the reference, but do NOT set the unit as referenced, we want
1891 -- to consider the unit as unreferenced if this is the only reference
1892 -- that occurs.
1894 Set_Entity_With_Style_Check (Name (N), E_Name);
1895 Generate_Reference (E_Name, Name (N), 'w', Set_Ref => False);
1897 if Is_Child_Unit (E_Name) then
1898 Pref := Prefix (Name (N));
1899 Par_Name := Scope (E_Name);
1900 while Nkind (Pref) = N_Selected_Component loop
1901 Change_Selected_Component_To_Expanded_Name (Pref);
1902 Set_Entity_With_Style_Check (Pref, Par_Name);
1904 Generate_Reference (Par_Name, Pref);
1905 Pref := Prefix (Pref);
1907 -- If E_Name is the dummy entity for a nonexistent unit, its scope
1908 -- is set to Standard_Standard, and no attempt should be made to
1909 -- further unwind scopes.
1911 if Par_Name /= Standard_Standard then
1912 Par_Name := Scope (Par_Name);
1913 end if;
1914 end loop;
1916 if Present (Entity (Pref))
1917 and then not Analyzed (Parent (Parent (Entity (Pref))))
1918 then
1919 -- If the entity is set without its unit being compiled, the
1920 -- original parent is a renaming, and Par_Name is the renamed
1921 -- entity. For visibility purposes, we need the original entity,
1922 -- which must be analyzed now because Load_Unit directly retrieves
1923 -- the renamed unit, and the renaming declaration itself has not
1924 -- been analyzed.
1926 Analyze (Parent (Parent (Entity (Pref))));
1927 pragma Assert (Renamed_Object (Entity (Pref)) = Par_Name);
1928 Par_Name := Entity (Pref);
1929 end if;
1931 Set_Entity_With_Style_Check (Pref, Par_Name);
1932 Generate_Reference (Par_Name, Pref);
1933 end if;
1935 -- If the withed unit is System, and a system extension pragma is
1936 -- present, compile the extension now, rather than waiting for a
1937 -- visibility check on a specific entity.
1939 if Chars (E_Name) = Name_System
1940 and then Scope (E_Name) = Standard_Standard
1941 and then Present (System_Extend_Unit)
1942 and then Present_System_Aux (N)
1943 then
1944 -- If the extension is not present, an error will have been emitted
1946 null;
1947 end if;
1949 -- Ada 2005 (AI-262): Remove from visibility the entity corresponding
1950 -- to private_with units; they will be made visible later (just before
1951 -- the private part is analyzed)
1953 if Private_Present (N) then
1954 Set_Is_Immediately_Visible (E_Name, False);
1955 end if;
1956 end Analyze_With_Clause;
1958 ------------------------------
1959 -- Analyze_With_Type_Clause --
1960 ------------------------------
1962 procedure Analyze_With_Type_Clause (N : Node_Id) is
1963 Loc : constant Source_Ptr := Sloc (N);
1964 Nam : constant Node_Id := Name (N);
1965 Pack : Node_Id;
1966 Decl : Node_Id;
1967 P : Entity_Id;
1968 Unum : Unit_Number_Type;
1969 Sel : Node_Id;
1971 procedure Decorate_Tagged_Type (T : Entity_Id);
1972 -- Set basic attributes of type, including its class_wide type
1974 function In_Chain (E : Entity_Id) return Boolean;
1975 -- Check that the imported type is not already in the homonym chain,
1976 -- for example through a with_type clause in a parent unit.
1978 --------------------------
1979 -- Decorate_Tagged_Type --
1980 --------------------------
1982 procedure Decorate_Tagged_Type (T : Entity_Id) is
1983 CW : Entity_Id;
1985 begin
1986 Set_Ekind (T, E_Record_Type);
1987 Set_Is_Tagged_Type (T);
1988 Set_Etype (T, T);
1989 Set_From_With_Type (T);
1990 Set_Scope (T, P);
1992 if not In_Chain (T) then
1993 Set_Homonym (T, Current_Entity (T));
1994 Set_Current_Entity (T);
1995 end if;
1997 -- Build bogus class_wide type, if not previously done
1999 if No (Class_Wide_Type (T)) then
2000 CW := Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
2002 Set_Ekind (CW, E_Class_Wide_Type);
2003 Set_Etype (CW, T);
2004 Set_Scope (CW, P);
2005 Set_Is_Tagged_Type (CW);
2006 Set_Is_First_Subtype (CW, True);
2007 Init_Size_Align (CW);
2008 Set_Has_Unknown_Discriminants
2009 (CW, True);
2010 Set_Class_Wide_Type (CW, CW);
2011 Set_Equivalent_Type (CW, Empty);
2012 Set_From_With_Type (CW);
2014 Set_Class_Wide_Type (T, CW);
2015 end if;
2016 end Decorate_Tagged_Type;
2018 --------------
2019 -- In_Chain --
2020 --------------
2022 function In_Chain (E : Entity_Id) return Boolean is
2023 H : Entity_Id;
2025 begin
2026 H := Current_Entity (E);
2027 while Present (H) loop
2028 if H = E then
2029 return True;
2030 else
2031 H := Homonym (H);
2032 end if;
2033 end loop;
2035 return False;
2036 end In_Chain;
2038 -- Start of processing for Analyze_With_Type_Clause
2040 begin
2041 if Nkind (Nam) = N_Selected_Component then
2042 Pack := New_Copy_Tree (Prefix (Nam));
2043 Sel := Selector_Name (Nam);
2045 else
2046 Error_Msg_N ("illegal name for imported type", Nam);
2047 return;
2048 end if;
2050 Decl :=
2051 Make_Package_Declaration (Loc,
2052 Specification =>
2053 (Make_Package_Specification (Loc,
2054 Defining_Unit_Name => Pack,
2055 Visible_Declarations => New_List,
2056 End_Label => Empty)));
2058 Unum :=
2059 Load_Unit
2060 (Load_Name => Get_Unit_Name (Decl),
2061 Required => True,
2062 Subunit => False,
2063 Error_Node => Nam);
2065 if Unum = No_Unit
2066 or else Nkind (Unit (Cunit (Unum))) /= N_Package_Declaration
2067 then
2068 Error_Msg_N ("imported type must be declared in package", Nam);
2069 return;
2071 elsif Unum = Current_Sem_Unit then
2073 -- If type is defined in unit being analyzed, then the clause
2074 -- is redundant.
2076 return;
2078 else
2079 P := Cunit_Entity (Unum);
2080 end if;
2082 -- Find declaration for imported type, and set its basic attributes
2083 -- if it has not been analyzed (which will be the case if there is
2084 -- circular dependence).
2086 declare
2087 Decl : Node_Id;
2088 Typ : Entity_Id;
2090 begin
2091 if not Analyzed (Cunit (Unum))
2092 and then not From_With_Type (P)
2093 then
2094 Set_Ekind (P, E_Package);
2095 Set_Etype (P, Standard_Void_Type);
2096 Set_From_With_Type (P);
2097 Set_Scope (P, Standard_Standard);
2098 Set_Homonym (P, Current_Entity (P));
2099 Set_Current_Entity (P);
2101 elsif Analyzed (Cunit (Unum))
2102 and then Is_Child_Unit (P)
2103 then
2104 -- If the child unit is already in scope, indicate that it is
2105 -- visible, and remains so after intervening calls to rtsfind.
2107 Set_Is_Visible_Child_Unit (P);
2108 end if;
2110 if Nkind (Parent (P)) = N_Defining_Program_Unit_Name then
2112 -- Make parent packages visible
2114 declare
2115 Parent_Comp : Node_Id;
2116 Parent_Id : Entity_Id;
2117 Child : Entity_Id;
2119 begin
2120 Child := P;
2121 Parent_Comp := Parent_Spec (Unit (Cunit (Unum)));
2123 loop
2124 Parent_Id := Defining_Entity (Unit (Parent_Comp));
2125 Set_Scope (Child, Parent_Id);
2127 -- The type may be imported from a child unit, in which
2128 -- case the current compilation appears in the name. Do
2129 -- not change its visibility here because it will conflict
2130 -- with the subsequent normal processing.
2132 if not Analyzed (Unit_Declaration_Node (Parent_Id))
2133 and then Parent_Id /= Cunit_Entity (Current_Sem_Unit)
2134 then
2135 Set_Ekind (Parent_Id, E_Package);
2136 Set_Etype (Parent_Id, Standard_Void_Type);
2138 -- The same package may appear is several with_type
2139 -- clauses.
2141 if not From_With_Type (Parent_Id) then
2142 Set_Homonym (Parent_Id, Current_Entity (Parent_Id));
2143 Set_Current_Entity (Parent_Id);
2144 Set_From_With_Type (Parent_Id);
2145 end if;
2146 end if;
2148 Set_Is_Immediately_Visible (Parent_Id);
2150 Child := Parent_Id;
2151 Parent_Comp := Parent_Spec (Unit (Parent_Comp));
2152 exit when No (Parent_Comp);
2153 end loop;
2155 Set_Scope (Parent_Id, Standard_Standard);
2156 end;
2157 end if;
2159 -- Even if analyzed, the package may not be currently visible. It
2160 -- must be while the with_type clause is active.
2162 Set_Is_Immediately_Visible (P);
2164 Decl :=
2165 First (Visible_Declarations (Specification (Unit (Cunit (Unum)))));
2166 while Present (Decl) loop
2167 if Nkind (Decl) = N_Full_Type_Declaration
2168 and then Chars (Defining_Identifier (Decl)) = Chars (Sel)
2169 then
2170 Typ := Defining_Identifier (Decl);
2172 if Tagged_Present (N) then
2174 -- The declaration must indicate that this is a tagged
2175 -- type or a type extension.
2177 if (Nkind (Type_Definition (Decl)) = N_Record_Definition
2178 and then Tagged_Present (Type_Definition (Decl)))
2179 or else
2180 (Nkind (Type_Definition (Decl))
2181 = N_Derived_Type_Definition
2182 and then Present
2183 (Record_Extension_Part (Type_Definition (Decl))))
2184 then
2185 null;
2186 else
2187 Error_Msg_N ("imported type is not a tagged type", Nam);
2188 return;
2189 end if;
2191 if not Analyzed (Decl) then
2193 -- Unit is not currently visible. Add basic attributes
2194 -- to type and build its class-wide type.
2196 Init_Size_Align (Typ);
2197 Decorate_Tagged_Type (Typ);
2198 end if;
2200 else
2201 if Nkind (Type_Definition (Decl))
2202 /= N_Access_To_Object_Definition
2203 then
2204 Error_Msg_N
2205 ("imported type is not an access type", Nam);
2207 elsif not Analyzed (Decl) then
2208 Set_Ekind (Typ, E_Access_Type);
2209 Set_Etype (Typ, Typ);
2210 Set_Scope (Typ, P);
2211 Init_Size (Typ, System_Address_Size);
2212 Init_Alignment (Typ);
2213 Set_Directly_Designated_Type (Typ, Standard_Integer);
2214 Set_From_With_Type (Typ);
2216 if not In_Chain (Typ) then
2217 Set_Homonym (Typ, Current_Entity (Typ));
2218 Set_Current_Entity (Typ);
2219 end if;
2220 end if;
2221 end if;
2223 Set_Entity (Sel, Typ);
2224 return;
2226 elsif ((Nkind (Decl) = N_Private_Type_Declaration
2227 and then Tagged_Present (Decl))
2228 or else (Nkind (Decl) = N_Private_Extension_Declaration))
2229 and then Chars (Defining_Identifier (Decl)) = Chars (Sel)
2230 then
2231 Typ := Defining_Identifier (Decl);
2233 if not Tagged_Present (N) then
2234 Error_Msg_N ("type must be declared tagged", N);
2236 elsif not Analyzed (Decl) then
2237 Decorate_Tagged_Type (Typ);
2238 end if;
2240 Set_Entity (Sel, Typ);
2241 Set_From_With_Type (Typ);
2242 return;
2243 end if;
2245 Decl := Next (Decl);
2246 end loop;
2248 Error_Msg_NE ("not a visible access or tagged type in&", Nam, P);
2249 end;
2250 end Analyze_With_Type_Clause;
2252 -----------------------------
2253 -- Check_With_Type_Clauses --
2254 -----------------------------
2256 procedure Check_With_Type_Clauses (N : Node_Id) is
2257 Lib_Unit : constant Node_Id := Unit (N);
2259 procedure Check_Parent_Context (U : Node_Id);
2260 -- Examine context items of parent unit to locate with_type clauses
2262 --------------------------
2263 -- Check_Parent_Context --
2264 --------------------------
2266 procedure Check_Parent_Context (U : Node_Id) is
2267 Item : Node_Id;
2269 begin
2270 Item := First (Context_Items (U));
2271 while Present (Item) loop
2272 if Nkind (Item) = N_With_Type_Clause
2273 and then not Error_Posted (Item)
2274 and then
2275 From_With_Type (Scope (Entity (Selector_Name (Name (Item)))))
2276 then
2277 Error_Msg_Sloc := Sloc (Item);
2278 Error_Msg_N ("missing With_Clause for With_Type_Clause#", N);
2279 end if;
2281 Next (Item);
2282 end loop;
2283 end Check_Parent_Context;
2285 -- Start of processing for Check_With_Type_Clauses
2287 begin
2288 if Extensions_Allowed
2289 and then (Nkind (Lib_Unit) = N_Package_Body
2290 or else Nkind (Lib_Unit) = N_Subprogram_Body)
2291 then
2292 Check_Parent_Context (Library_Unit (N));
2294 if Is_Child_Spec (Unit (Library_Unit (N))) then
2295 Check_Parent_Context (Parent_Spec (Unit (Library_Unit (N))));
2296 end if;
2297 end if;
2298 end Check_With_Type_Clauses;
2300 ------------------------------
2301 -- Check_Private_Child_Unit --
2302 ------------------------------
2304 procedure Check_Private_Child_Unit (N : Node_Id) is
2305 Lib_Unit : constant Node_Id := Unit (N);
2306 Item : Node_Id;
2307 Curr_Unit : Entity_Id;
2308 Sub_Parent : Node_Id;
2309 Priv_Child : Entity_Id;
2310 Par_Lib : Entity_Id;
2311 Par_Spec : Node_Id;
2313 function Is_Private_Library_Unit (Unit : Entity_Id) return Boolean;
2314 -- Returns true if and only if the library unit is declared with
2315 -- an explicit designation of private.
2317 function Is_Private_Library_Unit (Unit : Entity_Id) return Boolean is
2318 Comp_Unit : constant Node_Id := Parent (Unit_Declaration_Node (Unit));
2320 begin
2321 return Private_Present (Comp_Unit);
2322 end Is_Private_Library_Unit;
2324 -- Start of processing for Check_Private_Child_Unit
2326 begin
2327 if Nkind (Lib_Unit) = N_Package_Body
2328 or else Nkind (Lib_Unit) = N_Subprogram_Body
2329 then
2330 Curr_Unit := Defining_Entity (Unit (Library_Unit (N)));
2331 Par_Lib := Curr_Unit;
2333 elsif Nkind (Lib_Unit) = N_Subunit then
2335 -- The parent is itself a body. The parent entity is to be found
2336 -- in the corresponding spec.
2338 Sub_Parent := Library_Unit (N);
2339 Curr_Unit := Defining_Entity (Unit (Library_Unit (Sub_Parent)));
2341 -- If the parent itself is a subunit, Curr_Unit is the entity
2342 -- of the enclosing body, retrieve the spec entity which is
2343 -- the proper ancestor we need for the following tests.
2345 if Ekind (Curr_Unit) = E_Package_Body then
2346 Curr_Unit := Spec_Entity (Curr_Unit);
2347 end if;
2349 Par_Lib := Curr_Unit;
2351 else
2352 Curr_Unit := Defining_Entity (Lib_Unit);
2354 Par_Lib := Curr_Unit;
2355 Par_Spec := Parent_Spec (Lib_Unit);
2357 if No (Par_Spec) then
2358 Par_Lib := Empty;
2359 else
2360 Par_Lib := Defining_Entity (Unit (Par_Spec));
2361 end if;
2362 end if;
2364 -- Loop through context items
2366 Item := First (Context_Items (N));
2367 while Present (Item) loop
2369 -- Ada 2005 (AI-262): Allow private_with of a private child package
2370 -- in public siblings
2372 if Nkind (Item) = N_With_Clause
2373 and then not Implicit_With (Item)
2374 and then not Private_Present (Item)
2375 and then Is_Private_Descendant (Entity (Name (Item)))
2376 then
2377 Priv_Child := Entity (Name (Item));
2379 declare
2380 Curr_Parent : Entity_Id := Par_Lib;
2381 Child_Parent : Entity_Id := Scope (Priv_Child);
2382 Prv_Ancestor : Entity_Id := Child_Parent;
2383 Curr_Private : Boolean := Is_Private_Library_Unit (Curr_Unit);
2385 begin
2386 -- If the child unit is a public child then locate
2387 -- the nearest private ancestor; Child_Parent will
2388 -- then be set to the parent of that ancestor.
2390 if not Is_Private_Library_Unit (Priv_Child) then
2391 while Present (Prv_Ancestor)
2392 and then not Is_Private_Library_Unit (Prv_Ancestor)
2393 loop
2394 Prv_Ancestor := Scope (Prv_Ancestor);
2395 end loop;
2397 if Present (Prv_Ancestor) then
2398 Child_Parent := Scope (Prv_Ancestor);
2399 end if;
2400 end if;
2402 while Present (Curr_Parent)
2403 and then Curr_Parent /= Standard_Standard
2404 and then Curr_Parent /= Child_Parent
2405 loop
2406 Curr_Private :=
2407 Curr_Private or else Is_Private_Library_Unit (Curr_Parent);
2408 Curr_Parent := Scope (Curr_Parent);
2409 end loop;
2411 if not Present (Curr_Parent) then
2412 Curr_Parent := Standard_Standard;
2413 end if;
2415 if Curr_Parent /= Child_Parent then
2417 if Ekind (Priv_Child) = E_Generic_Package
2418 and then Chars (Priv_Child) in Text_IO_Package_Name
2419 and then Chars (Scope (Scope (Priv_Child))) = Name_Ada
2420 then
2421 Error_Msg_NE
2422 ("& is a nested package, not a compilation unit",
2423 Name (Item), Priv_Child);
2425 else
2426 Error_Msg_N
2427 ("unit in with clause is private child unit!", Item);
2428 Error_Msg_NE
2429 ("current unit must also have parent&!",
2430 Item, Child_Parent);
2431 end if;
2433 elsif not Curr_Private
2434 and then Nkind (Lib_Unit) /= N_Package_Body
2435 and then Nkind (Lib_Unit) /= N_Subprogram_Body
2436 and then Nkind (Lib_Unit) /= N_Subunit
2437 then
2438 Error_Msg_NE
2439 ("current unit must also be private descendant of&",
2440 Item, Child_Parent);
2441 end if;
2442 end;
2443 end if;
2445 Next (Item);
2446 end loop;
2448 end Check_Private_Child_Unit;
2450 ----------------------
2451 -- Check_Stub_Level --
2452 ----------------------
2454 procedure Check_Stub_Level (N : Node_Id) is
2455 Par : constant Node_Id := Parent (N);
2456 Kind : constant Node_Kind := Nkind (Par);
2458 begin
2459 if (Kind = N_Package_Body
2460 or else Kind = N_Subprogram_Body
2461 or else Kind = N_Task_Body
2462 or else Kind = N_Protected_Body)
2463 and then (Nkind (Parent (Par)) = N_Compilation_Unit
2464 or else Nkind (Parent (Par)) = N_Subunit)
2465 then
2466 null;
2468 -- In an instance, a missing stub appears at any level. A warning
2469 -- message will have been emitted already for the missing file.
2471 elsif not In_Instance then
2472 Error_Msg_N ("stub cannot appear in an inner scope", N);
2474 elsif Expander_Active then
2475 Error_Msg_N ("missing proper body", N);
2476 end if;
2477 end Check_Stub_Level;
2479 ------------------------
2480 -- Expand_With_Clause --
2481 ------------------------
2483 procedure Expand_With_Clause (Nam : Node_Id; N : Node_Id) is
2484 Loc : constant Source_Ptr := Sloc (Nam);
2485 Ent : constant Entity_Id := Entity (Nam);
2486 Withn : Node_Id;
2487 P : Node_Id;
2489 function Build_Unit_Name (Nam : Node_Id) return Node_Id;
2491 ---------------------
2492 -- Build_Unit_Name --
2493 ---------------------
2495 function Build_Unit_Name (Nam : Node_Id) return Node_Id is
2496 Result : Node_Id;
2498 begin
2499 if Nkind (Nam) = N_Identifier then
2500 return New_Occurrence_Of (Entity (Nam), Loc);
2502 else
2503 Result :=
2504 Make_Expanded_Name (Loc,
2505 Chars => Chars (Entity (Nam)),
2506 Prefix => Build_Unit_Name (Prefix (Nam)),
2507 Selector_Name => New_Occurrence_Of (Entity (Nam), Loc));
2508 Set_Entity (Result, Entity (Nam));
2509 return Result;
2510 end if;
2511 end Build_Unit_Name;
2513 -- Start of processing for Expand_With_Clause
2515 begin
2516 New_Nodes_OK := New_Nodes_OK + 1;
2517 Withn :=
2518 Make_With_Clause (Loc, Name => Build_Unit_Name (Nam));
2520 P := Parent (Unit_Declaration_Node (Ent));
2521 Set_Library_Unit (Withn, P);
2522 Set_Corresponding_Spec (Withn, Ent);
2523 Set_First_Name (Withn, True);
2524 Set_Implicit_With (Withn, True);
2526 Prepend (Withn, Context_Items (N));
2527 Mark_Rewrite_Insertion (Withn);
2528 Install_Withed_Unit (Withn);
2530 if Nkind (Nam) = N_Expanded_Name then
2531 Expand_With_Clause (Prefix (Nam), N);
2532 end if;
2534 New_Nodes_OK := New_Nodes_OK - 1;
2535 end Expand_With_Clause;
2537 -----------------------
2538 -- Get_Parent_Entity --
2539 -----------------------
2541 function Get_Parent_Entity (Unit : Node_Id) return Entity_Id is
2542 begin
2543 if Nkind (Unit) = N_Package_Body
2544 and then Nkind (Original_Node (Unit)) = N_Package_Instantiation
2545 then
2546 return
2547 Defining_Entity
2548 (Specification (Instance_Spec (Original_Node (Unit))));
2550 elsif Nkind (Unit) = N_Package_Instantiation then
2551 return Defining_Entity (Specification (Instance_Spec (Unit)));
2553 else
2554 return Defining_Entity (Unit);
2555 end if;
2556 end Get_Parent_Entity;
2558 -----------------------------
2559 -- Implicit_With_On_Parent --
2560 -----------------------------
2562 procedure Implicit_With_On_Parent
2563 (Child_Unit : Node_Id;
2564 N : Node_Id)
2566 Loc : constant Source_Ptr := Sloc (N);
2567 P : constant Node_Id := Parent_Spec (Child_Unit);
2569 P_Unit : Node_Id := Unit (P);
2571 P_Name : constant Entity_Id := Get_Parent_Entity (P_Unit);
2572 Withn : Node_Id;
2574 function Build_Ancestor_Name (P : Node_Id) return Node_Id;
2575 -- Build prefix of child unit name. Recurse if needed
2577 function Build_Unit_Name return Node_Id;
2578 -- If the unit is a child unit, build qualified name with all
2579 -- ancestors.
2581 -------------------------
2582 -- Build_Ancestor_Name --
2583 -------------------------
2585 function Build_Ancestor_Name (P : Node_Id) return Node_Id is
2586 P_Ref : constant Node_Id :=
2587 New_Reference_To (Defining_Entity (P), Loc);
2588 P_Spec : Node_Id := P;
2590 begin
2591 -- Ancestor may have been rewritten as a package body. Retrieve
2592 -- the original spec to trace earlier ancestors.
2594 if Nkind (P) = N_Package_Body
2595 and then Nkind (Original_Node (P)) = N_Package_Instantiation
2596 then
2597 P_Spec := Original_Node (P);
2598 end if;
2600 if No (Parent_Spec (P_Spec)) then
2601 return P_Ref;
2602 else
2603 return
2604 Make_Selected_Component (Loc,
2605 Prefix => Build_Ancestor_Name (Unit (Parent_Spec (P_Spec))),
2606 Selector_Name => P_Ref);
2607 end if;
2608 end Build_Ancestor_Name;
2610 ---------------------
2611 -- Build_Unit_Name --
2612 ---------------------
2614 function Build_Unit_Name return Node_Id is
2615 Result : Node_Id;
2616 begin
2617 if No (Parent_Spec (P_Unit)) then
2618 return New_Reference_To (P_Name, Loc);
2619 else
2620 Result :=
2621 Make_Expanded_Name (Loc,
2622 Chars => Chars (P_Name),
2623 Prefix => Build_Ancestor_Name (Unit (Parent_Spec (P_Unit))),
2624 Selector_Name => New_Reference_To (P_Name, Loc));
2625 Set_Entity (Result, P_Name);
2626 return Result;
2627 end if;
2628 end Build_Unit_Name;
2630 -- Start of processing for Implicit_With_On_Parent
2632 begin
2633 -- The unit of the current compilation may be a package body
2634 -- that replaces an instance node. In this case we need the
2635 -- original instance node to construct the proper parent name.
2637 if Nkind (P_Unit) = N_Package_Body
2638 and then Nkind (Original_Node (P_Unit)) = N_Package_Instantiation
2639 then
2640 P_Unit := Original_Node (P_Unit);
2641 end if;
2643 New_Nodes_OK := New_Nodes_OK + 1;
2644 Withn := Make_With_Clause (Loc, Name => Build_Unit_Name);
2646 Set_Library_Unit (Withn, P);
2647 Set_Corresponding_Spec (Withn, P_Name);
2648 Set_First_Name (Withn, True);
2649 Set_Implicit_With (Withn, True);
2651 -- Node is placed at the beginning of the context items, so that
2652 -- subsequent use clauses on the parent can be validated.
2654 Prepend (Withn, Context_Items (N));
2655 Mark_Rewrite_Insertion (Withn);
2656 Install_Withed_Unit (Withn);
2658 if Is_Child_Spec (P_Unit) then
2659 Implicit_With_On_Parent (P_Unit, N);
2660 end if;
2662 New_Nodes_OK := New_Nodes_OK - 1;
2663 end Implicit_With_On_Parent;
2665 --------------
2666 -- In_Chain --
2667 --------------
2669 function In_Chain (E : Entity_Id) return Boolean is
2670 H : Entity_Id;
2672 begin
2673 H := Current_Entity (E);
2674 while Present (H) loop
2675 if H = E then
2676 return True;
2677 else
2678 H := Homonym (H);
2679 end if;
2680 end loop;
2682 return False;
2683 end In_Chain;
2685 ---------------------
2686 -- Install_Context --
2687 ---------------------
2689 procedure Install_Context (N : Node_Id) is
2690 Lib_Unit : constant Node_Id := Unit (N);
2692 begin
2693 Install_Context_Clauses (N);
2695 if Is_Child_Spec (Lib_Unit) then
2696 Install_Parents (Lib_Unit, Private_Present (Parent (Lib_Unit)));
2697 end if;
2699 Install_Limited_Context_Clauses (N);
2701 Check_With_Type_Clauses (N);
2702 end Install_Context;
2704 -----------------------------
2705 -- Install_Context_Clauses --
2706 -----------------------------
2708 procedure Install_Context_Clauses (N : Node_Id) is
2709 Lib_Unit : constant Node_Id := Unit (N);
2710 Item : Node_Id;
2711 Uname_Node : Entity_Id;
2712 Check_Private : Boolean := False;
2713 Decl_Node : Node_Id;
2714 Lib_Parent : Entity_Id;
2716 begin
2717 -- Loop through context clauses to find the with/use clauses.
2718 -- This is done twice, first for everything except limited_with
2719 -- clauses, and then for those, if any are present.
2721 Item := First (Context_Items (N));
2722 while Present (Item) loop
2724 -- Case of explicit WITH clause
2726 if Nkind (Item) = N_With_Clause
2727 and then not Implicit_With (Item)
2728 then
2729 if Limited_Present (Item) then
2731 -- Limited withed units will be installed later
2733 goto Continue;
2735 -- If Name (Item) is not an entity name, something is wrong, and
2736 -- this will be detected in due course, for now ignore the item
2738 elsif not Is_Entity_Name (Name (Item)) then
2739 goto Continue;
2741 elsif No (Entity (Name (Item))) then
2742 Set_Entity (Name (Item), Any_Id);
2743 goto Continue;
2744 end if;
2746 Uname_Node := Entity (Name (Item));
2748 if Is_Private_Descendant (Uname_Node) then
2749 Check_Private := True;
2750 end if;
2752 Install_Withed_Unit (Item);
2754 Decl_Node := Unit_Declaration_Node (Uname_Node);
2756 -- If the unit is a subprogram instance, it appears nested
2757 -- within a package that carries the parent information.
2759 if Is_Generic_Instance (Uname_Node)
2760 and then Ekind (Uname_Node) /= E_Package
2761 then
2762 Decl_Node := Parent (Parent (Decl_Node));
2763 end if;
2765 if Is_Child_Spec (Decl_Node) then
2766 if Nkind (Name (Item)) = N_Expanded_Name then
2767 Expand_With_Clause (Prefix (Name (Item)), N);
2768 else
2769 -- if not an expanded name, the child unit must be a
2770 -- renaming, nothing to do.
2772 null;
2773 end if;
2775 elsif Nkind (Decl_Node) = N_Subprogram_Body
2776 and then not Acts_As_Spec (Parent (Decl_Node))
2777 and then Is_Child_Spec (Unit (Library_Unit (Parent (Decl_Node))))
2778 then
2779 Implicit_With_On_Parent
2780 (Unit (Library_Unit (Parent (Decl_Node))), N);
2781 end if;
2783 -- Check license conditions unless this is a dummy unit
2785 if Sloc (Library_Unit (Item)) /= No_Location then
2786 License_Check : declare
2787 Withl : constant License_Type :=
2788 License (Source_Index
2789 (Get_Source_Unit
2790 (Library_Unit (Item))));
2792 Unitl : constant License_Type :=
2793 License (Source_Index (Current_Sem_Unit));
2795 procedure License_Error;
2796 -- Signal error of bad license
2798 -------------------
2799 -- License_Error --
2800 -------------------
2802 procedure License_Error is
2803 begin
2804 Error_Msg_N
2805 ("?license of with'ed unit & is incompatible",
2806 Name (Item));
2807 end License_Error;
2809 -- Start of processing for License_Check
2811 begin
2812 case Unitl is
2813 when Unknown =>
2814 null;
2816 when Restricted =>
2817 if Withl = GPL then
2818 License_Error;
2819 end if;
2821 when GPL =>
2822 if Withl = Restricted then
2823 License_Error;
2824 end if;
2826 when Modified_GPL =>
2827 if Withl = Restricted or else Withl = GPL then
2828 License_Error;
2829 end if;
2831 when Unrestricted =>
2832 null;
2833 end case;
2834 end License_Check;
2835 end if;
2837 -- Case of USE PACKAGE clause
2839 elsif Nkind (Item) = N_Use_Package_Clause then
2840 Analyze_Use_Package (Item);
2842 -- Case of USE TYPE clause
2844 elsif Nkind (Item) = N_Use_Type_Clause then
2845 Analyze_Use_Type (Item);
2847 -- Case of WITH TYPE clause
2849 -- A With_Type_Clause is processed when installing the context,
2850 -- because it is a visibility mechanism and does not create a
2851 -- semantic dependence on other units, as a With_Clause does.
2853 elsif Nkind (Item) = N_With_Type_Clause then
2854 Analyze_With_Type_Clause (Item);
2856 -- case of PRAGMA
2858 elsif Nkind (Item) = N_Pragma then
2859 Analyze (Item);
2860 end if;
2862 <<Continue>>
2863 Next (Item);
2864 end loop;
2866 if Is_Child_Spec (Lib_Unit) then
2868 -- The unit also has implicit withs on its own parents
2870 if No (Context_Items (N)) then
2871 Set_Context_Items (N, New_List);
2872 end if;
2874 Implicit_With_On_Parent (Lib_Unit, N);
2875 end if;
2877 -- If the unit is a body, the context of the specification must also
2878 -- be installed.
2880 if Nkind (Lib_Unit) = N_Package_Body
2881 or else (Nkind (Lib_Unit) = N_Subprogram_Body
2882 and then not Acts_As_Spec (N))
2883 then
2884 Install_Context (Library_Unit (N));
2886 if Is_Child_Spec (Unit (Library_Unit (N))) then
2888 -- If the unit is the body of a public child unit, the private
2889 -- declarations of the parent must be made visible. If the child
2890 -- unit is private, the private declarations have been installed
2891 -- already in the call to Install_Parents for the spec. Installing
2892 -- private declarations must be done for all ancestors of public
2893 -- child units. In addition, sibling units mentioned in the
2894 -- context clause of the body are directly visible.
2896 declare
2897 Lib_Spec : Node_Id;
2898 P : Node_Id;
2899 P_Name : Entity_Id;
2901 begin
2902 Lib_Spec := Unit (Library_Unit (N));
2903 while Is_Child_Spec (Lib_Spec) loop
2904 P := Unit (Parent_Spec (Lib_Spec));
2906 if not (Private_Present (Parent (Lib_Spec))) then
2907 P_Name := Defining_Entity (P);
2908 Install_Private_Declarations (P_Name);
2909 Install_Private_With_Clauses (P_Name);
2910 Set_Use (Private_Declarations (Specification (P)));
2911 end if;
2913 Lib_Spec := P;
2914 end loop;
2915 end;
2916 end if;
2918 -- For a package body, children in context are immediately visible
2920 Install_Siblings (Defining_Entity (Unit (Library_Unit (N))), N);
2921 end if;
2923 if Nkind (Lib_Unit) = N_Generic_Package_Declaration
2924 or else Nkind (Lib_Unit) = N_Generic_Subprogram_Declaration
2925 or else Nkind (Lib_Unit) = N_Package_Declaration
2926 or else Nkind (Lib_Unit) = N_Subprogram_Declaration
2927 then
2928 if Is_Child_Spec (Lib_Unit) then
2929 Lib_Parent := Defining_Entity (Unit (Parent_Spec (Lib_Unit)));
2930 Set_Is_Private_Descendant
2931 (Defining_Entity (Lib_Unit),
2932 Is_Private_Descendant (Lib_Parent)
2933 or else Private_Present (Parent (Lib_Unit)));
2935 else
2936 Set_Is_Private_Descendant
2937 (Defining_Entity (Lib_Unit),
2938 Private_Present (Parent (Lib_Unit)));
2939 end if;
2940 end if;
2942 if Check_Private then
2943 Check_Private_Child_Unit (N);
2944 end if;
2945 end Install_Context_Clauses;
2947 -------------------------------------
2948 -- Install_Limited_Context_Clauses --
2949 -------------------------------------
2951 procedure Install_Limited_Context_Clauses (N : Node_Id) is
2952 Item : Node_Id;
2954 procedure Check_Renamings (P : Node_Id; W : Node_Id);
2955 -- Check that the unlimited view of a given compilation_unit is not
2956 -- already visible through "use + renamings".
2958 procedure Check_Private_Limited_Withed_Unit (N : Node_Id);
2959 -- Check that if a limited_with clause of a given compilation_unit
2960 -- mentions a private child of some library unit, then the given
2961 -- compilation_unit shall be the declaration of a private descendant
2962 -- of that library unit.
2964 procedure Expand_Limited_With_Clause
2965 (Comp_Unit : Node_Id; Nam : Node_Id; N : Node_Id);
2966 -- If a child unit appears in a limited_with clause, there are implicit
2967 -- limited_with clauses on all parents that are not already visible
2968 -- through a regular with clause. This procedure creates the implicit
2969 -- limited with_clauses for the parents and loads the corresponding
2970 -- units. The shadow entities are created when the inserted clause is
2971 -- analyzed. Implements Ada 2005 (AI-50217).
2973 ---------------------
2974 -- Check_Renamings --
2975 ---------------------
2977 procedure Check_Renamings (P : Node_Id; W : Node_Id) is
2978 Item : Node_Id;
2979 Spec : Node_Id;
2980 WEnt : Entity_Id;
2981 Nam : Node_Id;
2982 E : Entity_Id;
2983 E2 : Entity_Id;
2985 begin
2986 pragma Assert (Nkind (W) = N_With_Clause);
2988 -- Protect the frontend against previous critical errors
2990 case Nkind (Unit (Library_Unit (W))) is
2991 when N_Subprogram_Declaration |
2992 N_Package_Declaration |
2993 N_Generic_Subprogram_Declaration |
2994 N_Generic_Package_Declaration =>
2995 null;
2997 when others =>
2998 return;
2999 end case;
3001 -- Check "use + renamings"
3003 WEnt := Defining_Unit_Name (Specification (Unit (Library_Unit (W))));
3004 Spec := Specification (Unit (P));
3006 Item := First (Visible_Declarations (Spec));
3007 while Present (Item) loop
3009 if Nkind (Item) = N_Use_Package_Clause then
3011 -- Traverse the list of packages
3013 Nam := First (Names (Item));
3014 while Present (Nam) loop
3015 E := Entity (Nam);
3017 pragma Assert (Present (Parent (E)));
3019 if Nkind (Parent (E)) = N_Package_Renaming_Declaration
3020 and then Renamed_Entity (E) = WEnt
3021 then
3022 Error_Msg_N ("unlimited view visible through " &
3023 "use clause and renamings", W);
3024 return;
3026 elsif Nkind (Parent (E)) = N_Package_Specification then
3028 -- The use clause may refer to a local package.
3029 -- Check all the enclosing scopes.
3031 E2 := E;
3032 while E2 /= Standard_Standard
3033 and then E2 /= WEnt loop
3034 E2 := Scope (E2);
3035 end loop;
3037 if E2 = WEnt then
3038 Error_Msg_N
3039 ("unlimited view visible through use clause ", W);
3040 return;
3041 end if;
3043 end if;
3044 Next (Nam);
3045 end loop;
3047 end if;
3049 Next (Item);
3050 end loop;
3052 -- Recursive call to check all the ancestors
3054 if Is_Child_Spec (Unit (P)) then
3055 Check_Renamings (P => Parent_Spec (Unit (P)), W => W);
3056 end if;
3057 end Check_Renamings;
3059 ---------------------------------------
3060 -- Check_Private_Limited_Withed_Unit --
3061 ---------------------------------------
3063 procedure Check_Private_Limited_Withed_Unit (N : Node_Id) is
3064 C : Node_Id;
3065 P : Node_Id;
3066 Found : Boolean := False;
3068 begin
3069 -- If the current compilation unit is not private we don't
3070 -- need to check anything else.
3072 if not Private_Present (Parent (N)) then
3073 Found := False;
3075 else
3076 -- Compilation unit of the parent of the withed library unit
3078 P := Parent_Spec (Unit (Library_Unit (N)));
3080 -- Traverse all the ancestors of the current compilation
3081 -- unit to check if it is a descendant of named library unit.
3083 C := Parent (N);
3084 while Present (Parent_Spec (Unit (C))) loop
3085 C := Parent_Spec (Unit (C));
3087 if C = P then
3088 Found := True;
3089 exit;
3090 end if;
3091 end loop;
3092 end if;
3094 if not Found then
3095 Error_Msg_N ("current unit is not a private descendant"
3096 & " of the withed unit ('R'M 10.1.2(8)", N);
3097 end if;
3098 end Check_Private_Limited_Withed_Unit;
3100 --------------------------------
3101 -- Expand_Limited_With_Clause --
3102 --------------------------------
3104 procedure Expand_Limited_With_Clause
3105 (Comp_Unit : Node_Id;
3106 Nam : Node_Id;
3107 N : Node_Id)
3109 Loc : constant Source_Ptr := Sloc (Nam);
3110 Unum : Unit_Number_Type;
3111 Withn : Node_Id;
3113 function Previous_Withed_Unit (W : Node_Id) return Boolean;
3114 -- Returns true if the context already includes a with_clause for
3115 -- this unit. If the with_clause is non-limited, the unit is fully
3116 -- visible and an implicit limited_with should not be created. If
3117 -- there is already a limited_with clause for W, a second one is
3118 -- simply redundant.
3120 --------------------------
3121 -- Previous_Withed_Unit --
3122 --------------------------
3124 function Previous_Withed_Unit (W : Node_Id) return Boolean is
3125 Item : Node_Id;
3127 begin
3128 -- A limited with_clause can not appear in the same context_clause
3129 -- as a nonlimited with_clause which mentions the same library.
3131 Item := First (Context_Items (Comp_Unit));
3132 while Present (Item) loop
3133 if Nkind (Item) = N_With_Clause
3134 and then Library_Unit (Item) = Library_Unit (W)
3135 then
3136 return True;
3137 end if;
3139 Next (Item);
3140 end loop;
3142 return False;
3143 end Previous_Withed_Unit;
3145 -- Start of processing for Expand_Limited_With_Clause
3147 begin
3148 New_Nodes_OK := New_Nodes_OK + 1;
3150 if Nkind (Nam) = N_Identifier then
3151 Withn :=
3152 Make_With_Clause (Loc,
3153 Name => Nam);
3155 else pragma Assert (Nkind (Nam) = N_Selected_Component);
3156 Withn :=
3157 Make_With_Clause (Loc,
3158 Name => Make_Selected_Component (Loc,
3159 Prefix => Prefix (Nam),
3160 Selector_Name => Selector_Name (Nam)));
3161 Set_Parent (Withn, Parent (N));
3162 end if;
3164 Set_Limited_Present (Withn);
3165 Set_First_Name (Withn);
3166 Set_Implicit_With (Withn);
3168 Unum :=
3169 Load_Unit
3170 (Load_Name => Get_Spec_Name (Get_Unit_Name (Nam)),
3171 Required => True,
3172 Subunit => False,
3173 Error_Node => Nam);
3175 -- Do not generate a limited_with_clause on the current unit.
3176 -- This path is taken when a unit has a limited_with clause on
3177 -- one of its child units.
3179 if Unum = Current_Sem_Unit then
3180 return;
3181 end if;
3183 Set_Library_Unit (Withn, Cunit (Unum));
3184 Set_Corresponding_Spec
3185 (Withn, Specification (Unit (Cunit (Unum))));
3187 if not Previous_Withed_Unit (Withn) then
3188 Prepend (Withn, Context_Items (Parent (N)));
3189 Mark_Rewrite_Insertion (Withn);
3191 -- Add implicit limited_with_clauses for parents of child units
3192 -- mentioned in limited_with clauses.
3194 if Nkind (Nam) = N_Selected_Component then
3195 Expand_Limited_With_Clause (Comp_Unit, Prefix (Nam), N);
3196 end if;
3198 Analyze (Withn);
3200 if not Limited_View_Installed (Withn) then
3201 Install_Limited_Withed_Unit (Withn);
3202 end if;
3203 end if;
3205 New_Nodes_OK := New_Nodes_OK - 1;
3206 end Expand_Limited_With_Clause;
3208 -- Start of processing for Install_Limited_Context_Clauses
3210 begin
3211 Item := First (Context_Items (N));
3212 while Present (Item) loop
3213 if Nkind (Item) = N_With_Clause
3214 and then Limited_Present (Item)
3215 then
3216 if Nkind (Name (Item)) = N_Selected_Component then
3217 Expand_Limited_With_Clause
3218 (Comp_Unit => N, Nam => Prefix (Name (Item)), N => Item);
3219 end if;
3221 if Private_Present (Library_Unit (Item)) then
3222 Check_Private_Limited_Withed_Unit (Item);
3223 end if;
3225 if not Implicit_With (Item)
3226 and then Is_Child_Spec (Unit (N))
3227 then
3228 Check_Renamings (Parent_Spec (Unit (N)), Item);
3229 end if;
3231 -- A unit may have a limited with on itself if it has a
3232 -- limited with_clause on one of its child units. In that
3233 -- case it is already being compiled and it makes no sense
3234 -- to install its limited view.
3236 if Library_Unit (Item) /= Cunit (Current_Sem_Unit)
3237 and then not Limited_View_Installed (Item)
3238 then
3239 Install_Limited_Withed_Unit (Item);
3240 end if;
3241 end if;
3243 Next (Item);
3244 end loop;
3245 end Install_Limited_Context_Clauses;
3247 ---------------------
3248 -- Install_Parents --
3249 ---------------------
3251 procedure Install_Parents (Lib_Unit : Node_Id; Is_Private : Boolean) is
3252 P : Node_Id;
3253 E_Name : Entity_Id;
3254 P_Name : Entity_Id;
3255 P_Spec : Node_Id;
3257 begin
3258 P := Unit (Parent_Spec (Lib_Unit));
3259 P_Name := Get_Parent_Entity (P);
3261 if Etype (P_Name) = Any_Type then
3262 return;
3263 end if;
3265 if Ekind (P_Name) = E_Generic_Package
3266 and then Nkind (Lib_Unit) /= N_Generic_Subprogram_Declaration
3267 and then Nkind (Lib_Unit) /= N_Generic_Package_Declaration
3268 and then Nkind (Lib_Unit) not in N_Generic_Renaming_Declaration
3269 then
3270 Error_Msg_N
3271 ("child of a generic package must be a generic unit", Lib_Unit);
3273 elsif not Is_Package (P_Name) then
3274 Error_Msg_N
3275 ("parent unit must be package or generic package", Lib_Unit);
3276 raise Unrecoverable_Error;
3278 elsif Present (Renamed_Object (P_Name)) then
3279 Error_Msg_N ("parent unit cannot be a renaming", Lib_Unit);
3280 raise Unrecoverable_Error;
3282 -- Verify that a child of an instance is itself an instance, or
3283 -- the renaming of one. Given that an instance that is a unit is
3284 -- replaced with a package declaration, check against the original
3285 -- node. The parent may be currently being instantiated, in which
3286 -- case it appears as a declaration, but the generic_parent is
3287 -- already established indicating that we deal with an instance.
3289 elsif Nkind (Original_Node (P)) = N_Package_Instantiation then
3291 if Nkind (Lib_Unit) in N_Renaming_Declaration
3292 or else Nkind (Original_Node (Lib_Unit)) in N_Generic_Instantiation
3293 or else
3294 (Nkind (Lib_Unit) = N_Package_Declaration
3295 and then Present (Generic_Parent (Specification (Lib_Unit))))
3296 then
3297 null;
3298 else
3299 Error_Msg_N
3300 ("child of an instance must be an instance or renaming",
3301 Lib_Unit);
3302 end if;
3303 end if;
3305 -- This is the recursive call that ensures all parents are loaded
3307 if Is_Child_Spec (P) then
3308 Install_Parents (P,
3309 Is_Private or else Private_Present (Parent (Lib_Unit)));
3310 end if;
3312 -- Now we can install the context for this parent
3314 Install_Context_Clauses (Parent_Spec (Lib_Unit));
3315 Install_Siblings (P_Name, Parent (Lib_Unit));
3317 -- The child unit is in the declarative region of the parent. The
3318 -- parent must therefore appear in the scope stack and be visible,
3319 -- as when compiling the corresponding body. If the child unit is
3320 -- private or it is a package body, private declarations must be
3321 -- accessible as well. Use declarations in the parent must also
3322 -- be installed. Finally, other child units of the same parent that
3323 -- are in the context are immediately visible.
3325 -- Find entity for compilation unit, and set its private descendant
3326 -- status as needed.
3328 E_Name := Defining_Entity (Lib_Unit);
3330 Set_Is_Child_Unit (E_Name);
3332 Set_Is_Private_Descendant (E_Name,
3333 Is_Private_Descendant (P_Name)
3334 or else Private_Present (Parent (Lib_Unit)));
3336 P_Spec := Specification (Unit_Declaration_Node (P_Name));
3337 New_Scope (P_Name);
3339 -- Save current visibility of unit
3341 Scope_Stack.Table (Scope_Stack.Last).Previous_Visibility :=
3342 Is_Immediately_Visible (P_Name);
3343 Set_Is_Immediately_Visible (P_Name);
3344 Install_Visible_Declarations (P_Name);
3345 Set_Use (Visible_Declarations (P_Spec));
3347 -- If the parent is a generic unit, its formal part may contain
3348 -- formal packages and use clauses for them.
3350 if Ekind (P_Name) = E_Generic_Package then
3351 Set_Use (Generic_Formal_Declarations (Parent (P_Spec)));
3352 end if;
3354 if Is_Private
3355 or else Private_Present (Parent (Lib_Unit))
3356 then
3357 Install_Private_Declarations (P_Name);
3358 Install_Private_With_Clauses (P_Name);
3359 Set_Use (Private_Declarations (P_Spec));
3360 end if;
3361 end Install_Parents;
3363 ----------------------------------
3364 -- Install_Private_With_Clauses --
3365 ----------------------------------
3367 procedure Install_Private_With_Clauses (P : Entity_Id) is
3368 Decl : constant Node_Id := Unit_Declaration_Node (P);
3369 Item : Node_Id;
3371 begin
3372 if Debug_Flag_I then
3373 Write_Str ("install private with clauses of ");
3374 Write_Name (Chars (P));
3375 Write_Eol;
3376 end if;
3378 if Nkind (Parent (Decl)) = N_Compilation_Unit then
3379 Item := First (Context_Items (Parent (Decl)));
3380 while Present (Item) loop
3381 if Nkind (Item) = N_With_Clause
3382 and then Private_Present (Item)
3383 then
3384 if Limited_Present (Item) then
3385 if not Limited_View_Installed (Item) then
3386 Install_Limited_Withed_Unit (Item);
3387 end if;
3388 else
3389 Install_Withed_Unit (Item, Private_With_OK => True);
3390 end if;
3391 end if;
3393 Next (Item);
3394 end loop;
3395 end if;
3396 end Install_Private_With_Clauses;
3398 ----------------------
3399 -- Install_Siblings --
3400 ----------------------
3402 procedure Install_Siblings (U_Name : Entity_Id; N : Node_Id) is
3403 Item : Node_Id;
3404 Id : Entity_Id;
3405 Prev : Entity_Id;
3406 begin
3407 -- Iterate over explicit with clauses, and check whether the
3408 -- scope of each entity is an ancestor of the current unit.
3410 Item := First (Context_Items (N));
3411 while Present (Item) loop
3413 -- Do not install private_with_clauses if the unit is a package
3414 -- declaration, unless it is itself a private child unit.
3416 if Nkind (Item) = N_With_Clause
3417 and then not Implicit_With (Item)
3418 and then not Limited_Present (Item)
3419 and then
3420 (not Private_Present (Item)
3421 or else Nkind (Unit (N)) /= N_Package_Declaration
3422 or else Private_Present (N))
3423 then
3424 Id := Entity (Name (Item));
3426 if Is_Child_Unit (Id)
3427 and then Is_Ancestor_Package (Scope (Id), U_Name)
3428 then
3429 Set_Is_Immediately_Visible (Id);
3431 -- Check for the presence of another unit in the context,
3432 -- that may be inadvertently hidden by the child.
3434 Prev := Current_Entity (Id);
3436 if Present (Prev)
3437 and then Is_Immediately_Visible (Prev)
3438 and then not Is_Child_Unit (Prev)
3439 then
3440 declare
3441 Clause : Node_Id;
3443 begin
3444 Clause := First (Context_Items (N));
3445 while Present (Clause) loop
3446 if Nkind (Clause) = N_With_Clause
3447 and then Entity (Name (Clause)) = Prev
3448 then
3449 Error_Msg_NE
3450 ("child unit& hides compilation unit " &
3451 "with the same name?",
3452 Name (Item), Id);
3453 exit;
3454 end if;
3456 Next (Clause);
3457 end loop;
3458 end;
3459 end if;
3461 -- the With_Clause may be on a grand-child, which makes
3462 -- the child immediately visible.
3464 elsif Is_Child_Unit (Scope (Id))
3465 and then Is_Ancestor_Package (Scope (Scope (Id)), U_Name)
3466 then
3467 Set_Is_Immediately_Visible (Scope (Id));
3468 end if;
3469 end if;
3471 Next (Item);
3472 end loop;
3473 end Install_Siblings;
3475 -------------------------------
3476 -- Install_Limited_With_Unit --
3477 -------------------------------
3479 procedure Install_Limited_Withed_Unit (N : Node_Id) is
3480 P_Unit : constant Entity_Id := Unit (Library_Unit (N));
3481 P : Entity_Id;
3482 Is_Child_Package : Boolean := False;
3484 Lim_Header : Entity_Id;
3485 Lim_Typ : Entity_Id;
3487 function Is_Visible_Through_Renamings (P : Entity_Id) return Boolean;
3488 -- Check if some package installed though normal with-clauses has a
3489 -- renaming declaration of package P. AARM 10.1.2(21/2).
3491 ----------------------------------
3492 -- Is_Visible_Through_Renamings --
3493 ----------------------------------
3495 function Is_Visible_Through_Renamings (P : Entity_Id) return Boolean is
3496 Kind : constant Node_Kind :=
3497 Nkind (Unit (Cunit (Current_Sem_Unit)));
3498 Aux_Unit : Node_Id;
3499 Item : Node_Id;
3500 Decl : Entity_Id;
3502 begin
3503 -- Example of the error detected by this subprogram:
3505 -- package P is
3506 -- type T is ...
3507 -- end P;
3509 -- with P;
3510 -- package Q is
3511 -- package Ren_P renames P;
3512 -- end Q;
3514 -- with Q;
3515 -- package R is ...
3517 -- limited with P; -- ERROR
3518 -- package R.C is ...
3520 Aux_Unit := Cunit (Current_Sem_Unit);
3521 loop
3522 Item := First (Context_Items (Aux_Unit));
3523 while Present (Item) loop
3524 if Nkind (Item) = N_With_Clause
3525 and then not Limited_Present (Item)
3526 and then Nkind (Unit (Library_Unit (Item)))
3527 = N_Package_Declaration
3528 then
3529 Decl :=
3530 First (Visible_Declarations
3531 (Specification (Unit (Library_Unit (Item)))));
3532 while Present (Decl) loop
3533 if Nkind (Decl) = N_Package_Renaming_Declaration
3534 and then Entity (Name (Decl)) = P
3535 then
3536 -- Generate the error message only if the current unit
3537 -- is a package declaration; in case of subprogram
3538 -- bodies and package bodies we just return true to
3539 -- indicate that the limited view must not be
3540 -- installed.
3542 if Kind = N_Package_Declaration then
3543 Error_Msg_Sloc := Sloc (Item);
3544 Error_Msg_NE
3545 ("unlimited view of & visible through the context"
3546 & " clause found #", N, P);
3548 Error_Msg_Sloc := Sloc (Decl);
3549 Error_Msg_NE
3550 ("unlimited view of & visible through the"
3551 & " renaming found #", N, P);
3553 Error_Msg_N
3554 ("simultaneous visibility of the limited and"
3555 & " unlimited views not allowed", N);
3556 end if;
3558 return True;
3559 end if;
3561 Next (Decl);
3562 end loop;
3563 end if;
3565 Next (Item);
3566 end loop;
3568 if Present (Library_Unit (Aux_Unit)) then
3569 Aux_Unit := Library_Unit (Aux_Unit);
3570 else
3571 Aux_Unit := Parent_Spec (Unit (Aux_Unit));
3572 end if;
3574 exit when not Present (Aux_Unit);
3575 end loop;
3577 return False;
3578 end Is_Visible_Through_Renamings;
3580 -- Start of processing for Install_Limited_Withed_Unit
3582 begin
3583 pragma Assert (not Limited_View_Installed (N));
3585 -- In case of limited with_clause on subprograms, generics, instances,
3586 -- or renamings, the corresponding error was previously posted and we
3587 -- have nothing to do here.
3589 if Nkind (P_Unit) /= N_Package_Declaration then
3590 return;
3591 end if;
3593 P := Defining_Unit_Name (Specification (P_Unit));
3595 -- Handle child packages
3597 if Nkind (P) = N_Defining_Program_Unit_Name then
3598 Is_Child_Package := True;
3599 P := Defining_Identifier (P);
3600 end if;
3602 -- Do not install the limited-view if the full-view is already visible
3603 -- through renaming declarations.
3605 if Is_Visible_Through_Renamings (P) then
3606 return;
3607 end if;
3609 -- A common use of the limited-with is to have a limited-with
3610 -- in the package spec, and a normal with in its package body.
3611 -- For example:
3613 -- limited with X; -- [1]
3614 -- package A is ...
3616 -- with X; -- [2]
3617 -- package body A is ...
3619 -- The compilation of A's body installs the context clauses found at [2]
3620 -- and then the context clauses of its specification (found at [1]). As
3621 -- a consequence, at [1] the specification of X has been analyzed and it
3622 -- is immediately visible. According to the semantics of limited-with
3623 -- context clauses we don't install the limited view because the full
3624 -- view of X supersedes its limited view.
3626 if Analyzed (P_Unit)
3627 and then (Is_Immediately_Visible (P)
3628 or else (Is_Child_Package
3629 and then Is_Visible_Child_Unit (P)))
3630 then
3631 -- Ada 2005 (AI-262): Install the private declarations of P
3633 if Private_Present (N)
3634 and then not In_Private_Part (P)
3635 then
3636 declare
3637 Id : Entity_Id;
3639 begin
3640 Id := First_Private_Entity (P);
3641 while Present (Id) loop
3642 if not Is_Internal (Id)
3643 and then not Is_Child_Unit (Id)
3644 then
3645 if not In_Chain (Id) then
3646 Set_Homonym (Id, Current_Entity (Id));
3647 Set_Current_Entity (Id);
3648 end if;
3650 Set_Is_Immediately_Visible (Id);
3651 end if;
3653 Next_Entity (Id);
3654 end loop;
3656 Set_In_Private_Part (P);
3657 end;
3658 end if;
3660 return;
3661 end if;
3663 if Debug_Flag_I then
3664 Write_Str ("install limited view of ");
3665 Write_Name (Chars (P));
3666 Write_Eol;
3667 end if;
3669 -- If the unit has not been analyzed and the limited view has not been
3670 -- already installed then we install it.
3672 if not Analyzed (P_Unit) then
3673 if not In_Chain (P) then
3675 -- Minimum decoration
3677 Set_Ekind (P, E_Package);
3678 Set_Etype (P, Standard_Void_Type);
3679 Set_Scope (P, Standard_Standard);
3681 if Is_Child_Package then
3682 Set_Is_Child_Unit (P);
3683 Set_Is_Visible_Child_Unit (P);
3684 Set_Scope (P, Defining_Entity (Unit (Parent_Spec (P_Unit))));
3685 end if;
3687 -- Place entity on visibility structure
3689 Set_Homonym (P, Current_Entity (P));
3690 Set_Current_Entity (P);
3692 if Debug_Flag_I then
3693 Write_Str (" (homonym) chain ");
3694 Write_Name (Chars (P));
3695 Write_Eol;
3696 end if;
3698 -- Install the incomplete view. The first element of the limited
3699 -- view is a header (an E_Package entity) used to reference the
3700 -- first shadow entity in the private part of the package.
3702 Lim_Header := Limited_View (P);
3703 Lim_Typ := First_Entity (Lim_Header);
3705 while Present (Lim_Typ)
3706 and then Lim_Typ /= First_Private_Entity (Lim_Header)
3707 loop
3708 Set_Homonym (Lim_Typ, Current_Entity (Lim_Typ));
3709 Set_Current_Entity (Lim_Typ);
3711 if Debug_Flag_I then
3712 Write_Str (" (homonym) chain ");
3713 Write_Name (Chars (Lim_Typ));
3714 Write_Eol;
3715 end if;
3717 Next_Entity (Lim_Typ);
3718 end loop;
3719 end if;
3721 -- If the unit appears in a previous regular with_clause, the regular
3722 -- entities of the public part of the withed package must be replaced
3723 -- by the shadow ones.
3725 -- This code must be kept synchronized with the code that replaces the
3726 -- the shadow entities by the real entities (see body of Remove_Limited
3727 -- With_Clause); otherwise the contents of the homonym chains are not
3728 -- consistent.
3730 else
3731 -- Hide all the type entities of the public part of the package to
3732 -- avoid its usage. This is needed to cover all the subtype decla-
3733 -- rations because we do not remove them from the homonym chain.
3735 declare
3736 E : Entity_Id;
3738 begin
3739 E := First_Entity (P);
3740 while Present (E) and then E /= First_Private_Entity (P) loop
3741 if Is_Type (E) then
3742 Set_Was_Hidden (E, Is_Hidden (E));
3743 Set_Is_Hidden (E);
3744 end if;
3746 Next_Entity (E);
3747 end loop;
3748 end;
3750 -- Replace the real entities by the shadow entities of the limited
3751 -- view. The first element of the limited view is a header that is
3752 -- used to reference the first shadow entity in the private part
3753 -- of the package.
3755 Lim_Header := Limited_View (P);
3757 Lim_Typ := First_Entity (Lim_Header);
3758 while Present (Lim_Typ)
3759 and then Lim_Typ /= First_Private_Entity (Lim_Header)
3760 loop
3761 pragma Assert (not In_Chain (Lim_Typ));
3763 -- Do not unchain child units
3765 if not Is_Child_Unit (Lim_Typ) then
3766 declare
3767 Prev : Entity_Id;
3769 begin
3770 Set_Homonym (Lim_Typ, Homonym (Non_Limited_View (Lim_Typ)));
3771 Prev := Current_Entity (Lim_Typ);
3773 if Prev = Non_Limited_View (Lim_Typ) then
3774 Set_Current_Entity (Lim_Typ);
3775 else
3776 while Present (Prev)
3777 and then Homonym (Prev) /= Non_Limited_View (Lim_Typ)
3778 loop
3779 Prev := Homonym (Prev);
3780 end loop;
3782 Set_Homonym (Prev, Lim_Typ);
3783 end if;
3784 end;
3786 if Debug_Flag_I then
3787 Write_Str (" (homonym) chain ");
3788 Write_Name (Chars (Lim_Typ));
3789 Write_Eol;
3790 end if;
3791 end if;
3793 Next_Entity (Lim_Typ);
3794 end loop;
3795 end if;
3797 -- The package must be visible while the limited-with clause is active
3798 -- because references to the type P.T must resolve in the usual way.
3799 -- In addition, we remember that the limited-view has been installed to
3800 -- uninstall it at the point of context removal.
3802 Set_Is_Immediately_Visible (P);
3803 Set_Limited_View_Installed (N);
3804 Set_From_With_Type (P);
3805 end Install_Limited_Withed_Unit;
3807 -------------------------
3808 -- Install_Withed_Unit --
3809 -------------------------
3811 procedure Install_Withed_Unit
3812 (With_Clause : Node_Id;
3813 Private_With_OK : Boolean := False)
3815 Uname : constant Entity_Id := Entity (Name (With_Clause));
3816 P : constant Entity_Id := Scope (Uname);
3818 begin
3819 -- Ada 2005 (AI-262): Do not install the private withed unit if we are
3820 -- compiling a package declaration and the Private_With_OK flag was not
3821 -- set by the caller. These declarations will be installed later (before
3822 -- analyzing the private part of the package).
3824 if Private_Present (With_Clause)
3825 and then Nkind (Unit (Parent (With_Clause))) = N_Package_Declaration
3826 and then not (Private_With_OK)
3827 then
3828 return;
3829 end if;
3831 if Debug_Flag_I then
3832 if Private_Present (With_Clause) then
3833 Write_Str ("install private withed unit ");
3834 else
3835 Write_Str ("install withed unit ");
3836 end if;
3838 Write_Name (Chars (Uname));
3839 Write_Eol;
3840 end if;
3842 -- We do not apply the restrictions to an internal unit unless
3843 -- we are compiling the internal unit as a main unit. This check
3844 -- is also skipped for dummy units (for missing packages).
3846 if Sloc (Uname) /= No_Location
3847 and then (not Is_Internal_File_Name (Unit_File_Name (Current_Sem_Unit))
3848 or else Current_Sem_Unit = Main_Unit)
3849 then
3850 Check_Restricted_Unit
3851 (Unit_Name (Get_Source_Unit (Uname)), With_Clause);
3852 end if;
3854 if P /= Standard_Standard then
3856 -- If the unit is not analyzed after analysis of the with clause and
3857 -- it is an instantiation then it awaits a body and is the main unit.
3858 -- Its appearance in the context of some other unit indicates a
3859 -- circular dependency (DEC suite perversity).
3861 if not Analyzed (Uname)
3862 and then Nkind (Parent (Uname)) = N_Package_Instantiation
3863 then
3864 Error_Msg_N
3865 ("instantiation depends on itself", Name (With_Clause));
3867 elsif not Is_Visible_Child_Unit (Uname) then
3868 Set_Is_Visible_Child_Unit (Uname);
3870 -- If the child unit appears in the context of its parent, it is
3871 -- immediately visible.
3873 if In_Open_Scopes (Scope (Uname)) then
3874 Set_Is_Immediately_Visible (Uname);
3875 end if;
3877 if Is_Generic_Instance (Uname)
3878 and then Ekind (Uname) in Subprogram_Kind
3879 then
3880 -- Set flag as well on the visible entity that denotes the
3881 -- instance, which renames the current one.
3883 Set_Is_Visible_Child_Unit
3884 (Related_Instance
3885 (Defining_Entity (Unit (Library_Unit (With_Clause)))));
3886 end if;
3888 -- The parent unit may have been installed already, and may have
3889 -- appeared in a use clause.
3891 if In_Use (Scope (Uname)) then
3892 Set_Is_Potentially_Use_Visible (Uname);
3893 end if;
3895 Set_Context_Installed (With_Clause);
3896 end if;
3898 elsif not Is_Immediately_Visible (Uname) then
3899 if not Private_Present (With_Clause)
3900 or else Private_With_OK
3901 then
3902 Set_Is_Immediately_Visible (Uname);
3903 end if;
3905 Set_Context_Installed (With_Clause);
3906 end if;
3908 -- A with-clause overrides a with-type clause: there are no restric-
3909 -- tions on the use of package entities.
3911 if Ekind (Uname) = E_Package then
3912 Set_From_With_Type (Uname, False);
3913 end if;
3915 -- Ada 2005 (AI-377): it is illegal for a with_clause to name a child
3916 -- unit if there is a visible homograph for it declared in the same
3917 -- declarative region. This pathological case can only arise when an
3918 -- instance I1 of a generic unit G1 has an explicit child unit I1.G2,
3919 -- G1 has a generic child also named G2, and the context includes with_
3920 -- clauses for both I1.G2 and for G1.G2, making an implicit declaration
3921 -- of I1.G2 visible as well. If the child unit is named Standard, do
3922 -- not apply the check to the Standard package itself.
3924 if Is_Child_Unit (Uname)
3925 and then Is_Visible_Child_Unit (Uname)
3926 and then Ada_Version >= Ada_05
3927 then
3928 declare
3929 Decl1 : constant Node_Id := Unit_Declaration_Node (P);
3930 Decl2 : Node_Id;
3931 P2 : Entity_Id;
3932 U2 : Entity_Id;
3934 begin
3935 U2 := Homonym (Uname);
3936 while Present (U2)
3937 and U2 /= Standard_Standard
3938 loop
3939 P2 := Scope (U2);
3940 Decl2 := Unit_Declaration_Node (P2);
3942 if Is_Child_Unit (U2)
3943 and then Is_Visible_Child_Unit (U2)
3944 then
3945 if Is_Generic_Instance (P)
3946 and then Nkind (Decl1) = N_Package_Declaration
3947 and then Generic_Parent (Specification (Decl1)) = P2
3948 then
3949 Error_Msg_N ("illegal with_clause", With_Clause);
3950 Error_Msg_N
3951 ("\child unit has visible homograph" &
3952 " ('R'M 8.3(26), 10.1.1(19))",
3953 With_Clause);
3954 exit;
3956 elsif Is_Generic_Instance (P2)
3957 and then Nkind (Decl2) = N_Package_Declaration
3958 and then Generic_Parent (Specification (Decl2)) = P
3959 then
3960 -- With_clause for child unit of instance appears before
3961 -- in the context. We want to place the error message on
3962 -- it, not on the generic child unit itself.
3964 declare
3965 Prev_Clause : Node_Id;
3967 begin
3968 Prev_Clause := First (List_Containing (With_Clause));
3969 while Entity (Name (Prev_Clause)) /= U2 loop
3970 Next (Prev_Clause);
3971 end loop;
3973 pragma Assert (Present (Prev_Clause));
3974 Error_Msg_N ("illegal with_clause", Prev_Clause);
3975 Error_Msg_N
3976 ("\child unit has visible homograph" &
3977 " ('R'M 8.3(26), 10.1.1(19))",
3978 Prev_Clause);
3979 exit;
3980 end;
3981 end if;
3982 end if;
3984 U2 := Homonym (U2);
3985 end loop;
3986 end;
3987 end if;
3988 end Install_Withed_Unit;
3990 -------------------
3991 -- Is_Child_Spec --
3992 -------------------
3994 function Is_Child_Spec (Lib_Unit : Node_Id) return Boolean is
3995 K : constant Node_Kind := Nkind (Lib_Unit);
3997 begin
3998 return (K in N_Generic_Declaration or else
3999 K in N_Generic_Instantiation or else
4000 K in N_Generic_Renaming_Declaration or else
4001 K = N_Package_Declaration or else
4002 K = N_Package_Renaming_Declaration or else
4003 K = N_Subprogram_Declaration or else
4004 K = N_Subprogram_Renaming_Declaration)
4005 and then Present (Parent_Spec (Lib_Unit));
4006 end Is_Child_Spec;
4008 -----------------------
4009 -- Load_Needed_Body --
4010 -----------------------
4012 -- N is a generic unit named in a with clause, or else it is
4013 -- a unit that contains a generic unit or an inlined function.
4014 -- In order to perform an instantiation, the body of the unit
4015 -- must be present. If the unit itself is generic, we assume
4016 -- that an instantiation follows, and load and analyze the body
4017 -- unconditionally. This forces analysis of the spec as well.
4019 -- If the unit is not generic, but contains a generic unit, it
4020 -- is loaded on demand, at the point of instantiation (see ch12).
4022 procedure Load_Needed_Body (N : Node_Id; OK : out Boolean) is
4023 Body_Name : Unit_Name_Type;
4024 Unum : Unit_Number_Type;
4026 Save_Style_Check : constant Boolean := Opt.Style_Check;
4027 -- The loading and analysis is done with style checks off
4029 begin
4030 if not GNAT_Mode then
4031 Style_Check := False;
4032 end if;
4034 Body_Name := Get_Body_Name (Get_Unit_Name (Unit (N)));
4035 Unum :=
4036 Load_Unit
4037 (Load_Name => Body_Name,
4038 Required => False,
4039 Subunit => False,
4040 Error_Node => N,
4041 Renamings => True);
4043 if Unum = No_Unit then
4044 OK := False;
4046 else
4047 Compiler_State := Analyzing; -- reset after load
4049 if not Fatal_Error (Unum) or else Try_Semantics then
4050 if Debug_Flag_L then
4051 Write_Str ("*** Loaded generic body");
4052 Write_Eol;
4053 end if;
4055 Semantics (Cunit (Unum));
4056 end if;
4058 OK := True;
4059 end if;
4061 Style_Check := Save_Style_Check;
4062 end Load_Needed_Body;
4064 -------------------------
4065 -- Build_Limited_Views --
4066 -------------------------
4068 procedure Build_Limited_Views (N : Node_Id) is
4069 Unum : constant Unit_Number_Type := Get_Source_Unit (Library_Unit (N));
4070 P : constant Entity_Id := Cunit_Entity (Unum);
4072 Spec : Node_Id; -- To denote a package specification
4073 Lim_Typ : Entity_Id; -- To denote shadow entities
4074 Comp_Typ : Entity_Id; -- To denote real entities
4076 Lim_Header : Entity_Id; -- Package entity
4077 Last_Lim_E : Entity_Id := Empty; -- Last limited entity built
4078 Last_Pub_Lim_E : Entity_Id; -- To set the first private entity
4080 procedure Decorate_Incomplete_Type
4081 (E : Entity_Id;
4082 Scop : Entity_Id);
4083 -- Add attributes of an incomplete type to a shadow entity. The same
4084 -- attributes are placed on the real entity, so that gigi receives
4085 -- a consistent view.
4087 procedure Decorate_Package_Specification (P : Entity_Id);
4088 -- Add attributes of a package entity to the entity in a package
4089 -- declaration
4091 procedure Decorate_Tagged_Type
4092 (Loc : Source_Ptr;
4093 T : Entity_Id;
4094 Scop : Entity_Id);
4095 -- Set basic attributes of tagged type T, including its class_wide type.
4096 -- The parameters Loc, Scope are used to decorate the class_wide type.
4098 procedure Build_Chain
4099 (Scope : Entity_Id;
4100 First_Decl : Node_Id);
4101 -- Construct list of shadow entities and attach it to entity of
4102 -- package that is mentioned in a limited_with clause.
4104 function New_Internal_Shadow_Entity
4105 (Kind : Entity_Kind;
4106 Sloc_Value : Source_Ptr;
4107 Id_Char : Character) return Entity_Id;
4108 -- Build a new internal entity and append it to the list of shadow
4109 -- entities available through the limited-header
4111 ------------------------------
4112 -- Decorate_Incomplete_Type --
4113 ------------------------------
4115 procedure Decorate_Incomplete_Type
4116 (E : Entity_Id;
4117 Scop : Entity_Id)
4119 begin
4120 Set_Ekind (E, E_Incomplete_Type);
4121 Set_Scope (E, Scop);
4122 Set_Etype (E, E);
4123 Set_Is_First_Subtype (E, True);
4124 Set_Stored_Constraint (E, No_Elist);
4125 Set_Full_View (E, Empty);
4126 Init_Size_Align (E);
4127 end Decorate_Incomplete_Type;
4129 --------------------------
4130 -- Decorate_Tagged_Type --
4131 --------------------------
4133 procedure Decorate_Tagged_Type
4134 (Loc : Source_Ptr;
4135 T : Entity_Id;
4136 Scop : Entity_Id)
4138 CW : Entity_Id;
4140 begin
4141 Decorate_Incomplete_Type (T, Scop);
4142 Set_Is_Tagged_Type (T);
4144 -- Build corresponding class_wide type, if not previously done
4146 if No (Class_Wide_Type (T)) then
4147 CW := Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
4149 Set_Ekind (CW, E_Class_Wide_Type);
4150 Set_Etype (CW, T);
4151 Set_Scope (CW, Scop);
4152 Set_Is_Tagged_Type (CW);
4153 Set_Is_First_Subtype (CW, True);
4154 Init_Size_Align (CW);
4155 Set_Has_Unknown_Discriminants (CW, True);
4156 Set_Class_Wide_Type (CW, CW);
4157 Set_Equivalent_Type (CW, Empty);
4158 Set_From_With_Type (CW, From_With_Type (T));
4160 Set_Class_Wide_Type (T, CW);
4161 end if;
4162 end Decorate_Tagged_Type;
4164 ------------------------------------
4165 -- Decorate_Package_Specification --
4166 ------------------------------------
4168 procedure Decorate_Package_Specification (P : Entity_Id) is
4169 begin
4170 -- Place only the most basic attributes
4172 Set_Ekind (P, E_Package);
4173 Set_Etype (P, Standard_Void_Type);
4174 end Decorate_Package_Specification;
4176 -------------------------
4177 -- New_Internal_Entity --
4178 -------------------------
4180 function New_Internal_Shadow_Entity
4181 (Kind : Entity_Kind;
4182 Sloc_Value : Source_Ptr;
4183 Id_Char : Character) return Entity_Id
4185 E : constant Entity_Id :=
4186 Make_Defining_Identifier (Sloc_Value,
4187 Chars => New_Internal_Name (Id_Char));
4189 begin
4190 Set_Ekind (E, Kind);
4191 Set_Is_Internal (E, True);
4193 if Kind in Type_Kind then
4194 Init_Size_Align (E);
4195 end if;
4197 Append_Entity (E, Lim_Header);
4198 Last_Lim_E := E;
4199 return E;
4200 end New_Internal_Shadow_Entity;
4202 -----------------
4203 -- Build_Chain --
4204 -----------------
4206 procedure Build_Chain
4207 (Scope : Entity_Id;
4208 First_Decl : Node_Id)
4210 Analyzed_Unit : constant Boolean := Analyzed (Cunit (Unum));
4211 Is_Tagged : Boolean;
4212 Decl : Node_Id;
4214 begin
4215 Decl := First_Decl;
4216 while Present (Decl) loop
4218 -- For each library_package_declaration in the environment, there
4219 -- is an implicit declaration of a *limited view* of that library
4220 -- package. The limited view of a package contains:
4222 -- * For each nested package_declaration, a declaration of the
4223 -- limited view of that package, with the same defining-
4224 -- program-unit name.
4226 -- * For each type_declaration in the visible part, an incomplete
4227 -- type-declaration with the same defining_identifier, whose
4228 -- completion is the type_declaration. If the type_declaration
4229 -- is tagged, then the incomplete_type_declaration is tagged
4230 -- incomplete.
4232 if Nkind (Decl) = N_Full_Type_Declaration then
4233 Is_Tagged :=
4234 Nkind (Type_Definition (Decl)) = N_Record_Definition
4235 and then Tagged_Present (Type_Definition (Decl));
4237 Comp_Typ := Defining_Identifier (Decl);
4239 if not Analyzed_Unit then
4240 if Is_Tagged then
4241 Decorate_Tagged_Type (Sloc (Decl), Comp_Typ, Scope);
4242 else
4243 Decorate_Incomplete_Type (Comp_Typ, Scope);
4244 end if;
4245 end if;
4247 -- Create shadow entity for type
4249 Lim_Typ := New_Internal_Shadow_Entity
4250 (Kind => Ekind (Comp_Typ),
4251 Sloc_Value => Sloc (Comp_Typ),
4252 Id_Char => 'Z');
4254 Set_Chars (Lim_Typ, Chars (Comp_Typ));
4255 Set_Parent (Lim_Typ, Parent (Comp_Typ));
4256 Set_From_With_Type (Lim_Typ);
4258 if Is_Tagged then
4259 Decorate_Tagged_Type (Sloc (Decl), Lim_Typ, Scope);
4260 else
4261 Decorate_Incomplete_Type (Lim_Typ, Scope);
4262 end if;
4264 Set_Non_Limited_View (Lim_Typ, Comp_Typ);
4266 elsif Nkind (Decl) = N_Private_Type_Declaration then
4267 Comp_Typ := Defining_Identifier (Decl);
4269 if not Analyzed_Unit then
4270 if Tagged_Present (Decl) then
4271 Decorate_Tagged_Type (Sloc (Decl), Comp_Typ, Scope);
4272 else
4273 Decorate_Incomplete_Type (Comp_Typ, Scope);
4274 end if;
4275 end if;
4277 Lim_Typ := New_Internal_Shadow_Entity
4278 (Kind => Ekind (Comp_Typ),
4279 Sloc_Value => Sloc (Comp_Typ),
4280 Id_Char => 'Z');
4282 Set_Chars (Lim_Typ, Chars (Comp_Typ));
4283 Set_Parent (Lim_Typ, Parent (Comp_Typ));
4284 Set_From_With_Type (Lim_Typ);
4286 if Tagged_Present (Decl) then
4287 Decorate_Tagged_Type (Sloc (Decl), Lim_Typ, Scope);
4288 else
4289 Decorate_Incomplete_Type (Lim_Typ, Scope);
4290 end if;
4292 Set_Non_Limited_View (Lim_Typ, Comp_Typ);
4294 elsif Nkind (Decl) = N_Private_Extension_Declaration then
4295 Comp_Typ := Defining_Identifier (Decl);
4297 if not Analyzed_Unit then
4298 Decorate_Tagged_Type (Sloc (Decl), Comp_Typ, Scope);
4299 end if;
4301 -- Create shadow entity for type
4303 Lim_Typ := New_Internal_Shadow_Entity
4304 (Kind => Ekind (Comp_Typ),
4305 Sloc_Value => Sloc (Comp_Typ),
4306 Id_Char => 'Z');
4308 Set_Chars (Lim_Typ, Chars (Comp_Typ));
4309 Set_Parent (Lim_Typ, Parent (Comp_Typ));
4310 Set_From_With_Type (Lim_Typ);
4312 Decorate_Tagged_Type (Sloc (Decl), Lim_Typ, Scope);
4313 Set_Non_Limited_View (Lim_Typ, Comp_Typ);
4315 elsif Nkind (Decl) = N_Package_Declaration then
4317 -- Local package
4319 declare
4320 Spec : constant Node_Id := Specification (Decl);
4322 begin
4323 Comp_Typ := Defining_Unit_Name (Spec);
4325 if not Analyzed (Cunit (Unum)) then
4326 Decorate_Package_Specification (Comp_Typ);
4327 Set_Scope (Comp_Typ, Scope);
4328 end if;
4330 Lim_Typ := New_Internal_Shadow_Entity
4331 (Kind => Ekind (Comp_Typ),
4332 Sloc_Value => Sloc (Comp_Typ),
4333 Id_Char => 'Z');
4335 Decorate_Package_Specification (Lim_Typ);
4336 Set_Scope (Lim_Typ, Scope);
4338 Set_Chars (Lim_Typ, Chars (Comp_Typ));
4339 Set_Parent (Lim_Typ, Parent (Comp_Typ));
4340 Set_From_With_Type (Lim_Typ);
4342 -- Note: The non_limited_view attribute is not used
4343 -- for local packages.
4345 Build_Chain
4346 (Scope => Lim_Typ,
4347 First_Decl => First (Visible_Declarations (Spec)));
4348 end;
4349 end if;
4351 Next (Decl);
4352 end loop;
4353 end Build_Chain;
4355 -- Start of processing for Build_Limited_Views
4357 begin
4358 pragma Assert (Limited_Present (N));
4360 -- A library_item mentioned in a limited_with_clause shall be
4361 -- a package_declaration, not a subprogram_declaration,
4362 -- generic_declaration, generic_instantiation, or
4363 -- package_renaming_declaration
4365 case Nkind (Unit (Library_Unit (N))) is
4367 when N_Package_Declaration =>
4368 null;
4370 when N_Subprogram_Declaration =>
4371 Error_Msg_N ("subprograms not allowed in "
4372 & "limited with_clauses", N);
4373 return;
4375 when N_Generic_Package_Declaration |
4376 N_Generic_Subprogram_Declaration =>
4377 Error_Msg_N ("generics not allowed in "
4378 & "limited with_clauses", N);
4379 return;
4381 when N_Package_Instantiation |
4382 N_Function_Instantiation |
4383 N_Procedure_Instantiation =>
4384 Error_Msg_N ("generic instantiations not allowed in "
4385 & "limited with_clauses", N);
4386 return;
4388 when N_Generic_Package_Renaming_Declaration |
4389 N_Generic_Procedure_Renaming_Declaration |
4390 N_Generic_Function_Renaming_Declaration =>
4391 Error_Msg_N ("generic renamings not allowed in "
4392 & "limited with_clauses", N);
4393 return;
4395 when N_Subprogram_Renaming_Declaration =>
4396 Error_Msg_N ("renamed subprograms not allowed in "
4397 & "limited with_clauses", N);
4398 return;
4400 when N_Package_Renaming_Declaration =>
4401 Error_Msg_N ("renamed packages not allowed in "
4402 & "limited with_clauses", N);
4403 return;
4405 when others =>
4406 raise Program_Error;
4407 end case;
4409 -- Check if the chain is already built
4411 Spec := Specification (Unit (Library_Unit (N)));
4413 if Limited_View_Installed (Spec) then
4414 return;
4415 end if;
4417 Set_Ekind (P, E_Package);
4419 -- Build the header of the limited_view
4421 Lim_Header := Make_Defining_Identifier (Sloc (N),
4422 Chars => New_Internal_Name (Id_Char => 'Z'));
4423 Set_Ekind (Lim_Header, E_Package);
4424 Set_Is_Internal (Lim_Header);
4425 Set_Limited_View (P, Lim_Header);
4427 -- Create the auxiliary chain. All the shadow entities are appended
4428 -- to the list of entities of the limited-view header
4430 Build_Chain
4431 (Scope => P,
4432 First_Decl => First (Visible_Declarations (Spec)));
4434 -- Save the last built shadow entity. It is needed later to set the
4435 -- reference to the first shadow entity in the private part
4437 Last_Pub_Lim_E := Last_Lim_E;
4439 -- Ada 2005 (AI-262): Add the limited view of the private declarations
4440 -- Required to give support to limited-private-with clauses
4442 Build_Chain (Scope => P,
4443 First_Decl => First (Private_Declarations (Spec)));
4445 if Last_Pub_Lim_E /= Empty then
4446 Set_First_Private_Entity (Lim_Header,
4447 Next_Entity (Last_Pub_Lim_E));
4448 else
4449 Set_First_Private_Entity (Lim_Header,
4450 First_Entity (P));
4451 end if;
4453 Set_Limited_View_Installed (Spec);
4454 end Build_Limited_Views;
4456 -------------------------------
4457 -- Check_Body_Needed_For_SAL --
4458 -------------------------------
4460 procedure Check_Body_Needed_For_SAL (Unit_Name : Entity_Id) is
4462 function Entity_Needs_Body (E : Entity_Id) return Boolean;
4463 -- Determine whether use of entity E might require the presence
4464 -- of its body. For a package this requires a recursive traversal
4465 -- of all nested declarations.
4467 ---------------------------
4468 -- Entity_Needed_For_SAL --
4469 ---------------------------
4471 function Entity_Needs_Body (E : Entity_Id) return Boolean is
4472 Ent : Entity_Id;
4474 begin
4475 if Is_Subprogram (E)
4476 and then Has_Pragma_Inline (E)
4477 then
4478 return True;
4480 elsif Ekind (E) = E_Generic_Function
4481 or else Ekind (E) = E_Generic_Procedure
4482 then
4483 return True;
4485 elsif Ekind (E) = E_Generic_Package
4486 and then
4487 Nkind (Unit_Declaration_Node (E)) = N_Generic_Package_Declaration
4488 and then Present (Corresponding_Body (Unit_Declaration_Node (E)))
4489 then
4490 return True;
4492 elsif Ekind (E) = E_Package
4493 and then
4494 Nkind (Unit_Declaration_Node (E)) = N_Package_Declaration
4495 and then Present (Corresponding_Body (Unit_Declaration_Node (E)))
4496 then
4497 Ent := First_Entity (E);
4498 while Present (Ent) loop
4499 if Entity_Needs_Body (Ent) then
4500 return True;
4501 end if;
4503 Next_Entity (Ent);
4504 end loop;
4506 return False;
4508 else
4509 return False;
4510 end if;
4511 end Entity_Needs_Body;
4513 -- Start of processing for Check_Body_Needed_For_SAL
4515 begin
4516 if Ekind (Unit_Name) = E_Generic_Package
4517 and then
4518 Nkind (Unit_Declaration_Node (Unit_Name)) =
4519 N_Generic_Package_Declaration
4520 and then
4521 Present (Corresponding_Body (Unit_Declaration_Node (Unit_Name)))
4522 then
4523 Set_Body_Needed_For_SAL (Unit_Name);
4525 elsif Ekind (Unit_Name) = E_Generic_Procedure
4526 or else Ekind (Unit_Name) = E_Generic_Function
4527 then
4528 Set_Body_Needed_For_SAL (Unit_Name);
4530 elsif Is_Subprogram (Unit_Name)
4531 and then Nkind (Unit_Declaration_Node (Unit_Name)) =
4532 N_Subprogram_Declaration
4533 and then Has_Pragma_Inline (Unit_Name)
4534 then
4535 Set_Body_Needed_For_SAL (Unit_Name);
4537 elsif Ekind (Unit_Name) = E_Subprogram_Body then
4538 Check_Body_Needed_For_SAL
4539 (Corresponding_Spec (Unit_Declaration_Node (Unit_Name)));
4541 elsif Ekind (Unit_Name) = E_Package
4542 and then Entity_Needs_Body (Unit_Name)
4543 then
4544 Set_Body_Needed_For_SAL (Unit_Name);
4546 elsif Ekind (Unit_Name) = E_Package_Body
4547 and then Nkind (Unit_Declaration_Node (Unit_Name)) = N_Package_Body
4548 then
4549 Check_Body_Needed_For_SAL
4550 (Corresponding_Spec (Unit_Declaration_Node (Unit_Name)));
4551 end if;
4552 end Check_Body_Needed_For_SAL;
4554 --------------------
4555 -- Remove_Context --
4556 --------------------
4558 procedure Remove_Context (N : Node_Id) is
4559 Lib_Unit : constant Node_Id := Unit (N);
4561 begin
4562 -- If this is a child unit, first remove the parent units
4564 if Is_Child_Spec (Lib_Unit) then
4565 Remove_Parents (Lib_Unit);
4566 end if;
4568 Remove_Context_Clauses (N);
4569 end Remove_Context;
4571 ----------------------------
4572 -- Remove_Context_Clauses --
4573 ----------------------------
4575 procedure Remove_Context_Clauses (N : Node_Id) is
4576 Item : Node_Id;
4577 Unit_Name : Entity_Id;
4579 begin
4580 -- Ada 2005 (AI-50217): We remove the context clauses in two phases:
4581 -- limited-views first and regular-views later (to maintain the
4582 -- stack model).
4584 -- First Phase: Remove limited_with context clauses
4586 Item := First (Context_Items (N));
4587 while Present (Item) loop
4589 -- We are interested only in with clauses which got installed
4590 -- on entry.
4592 if Nkind (Item) = N_With_Clause
4593 and then Limited_Present (Item)
4594 and then Limited_View_Installed (Item)
4595 then
4596 Remove_Limited_With_Clause (Item);
4597 end if;
4599 Next (Item);
4600 end loop;
4602 -- Second Phase: Loop through context items and undo regular
4603 -- with_clauses and use_clauses.
4605 Item := First (Context_Items (N));
4606 while Present (Item) loop
4608 -- We are interested only in with clauses which got installed
4609 -- on entry, as indicated by their Context_Installed flag set
4611 if Nkind (Item) = N_With_Clause
4612 and then Limited_Present (Item)
4613 and then Limited_View_Installed (Item)
4614 then
4615 null;
4617 elsif Nkind (Item) = N_With_Clause
4618 and then Context_Installed (Item)
4619 then
4620 -- Remove items from one with'ed unit
4622 Unit_Name := Entity (Name (Item));
4623 Remove_Unit_From_Visibility (Unit_Name);
4624 Set_Context_Installed (Item, False);
4626 elsif Nkind (Item) = N_Use_Package_Clause then
4627 End_Use_Package (Item);
4629 elsif Nkind (Item) = N_Use_Type_Clause then
4630 End_Use_Type (Item);
4632 elsif Nkind (Item) = N_With_Type_Clause then
4633 Remove_With_Type_Clause (Name (Item));
4634 end if;
4636 Next (Item);
4637 end loop;
4638 end Remove_Context_Clauses;
4640 --------------------------------
4641 -- Remove_Limited_With_Clause --
4642 --------------------------------
4644 procedure Remove_Limited_With_Clause (N : Node_Id) is
4645 P_Unit : constant Entity_Id := Unit (Library_Unit (N));
4646 P : Entity_Id;
4647 Lim_Header : Entity_Id;
4648 Lim_Typ : Entity_Id;
4649 Prev : Entity_Id;
4651 begin
4652 pragma Assert (Limited_View_Installed (N));
4654 -- In case of limited with_clause on subprograms, generics, instances,
4655 -- or renamings, the corresponding error was previously posted and we
4656 -- have nothing to do here.
4658 if Nkind (P_Unit) /= N_Package_Declaration then
4659 return;
4660 end if;
4662 P := Defining_Unit_Name (Specification (P_Unit));
4664 -- Handle child packages
4666 if Nkind (P) = N_Defining_Program_Unit_Name then
4667 P := Defining_Identifier (P);
4668 end if;
4670 if Debug_Flag_I then
4671 Write_Str ("remove limited view of ");
4672 Write_Name (Chars (P));
4673 Write_Str (" from visibility");
4674 Write_Eol;
4675 end if;
4677 -- Prepare the removal of the shadow entities from visibility. The
4678 -- first element of the limited view is a header (an E_Package
4679 -- entity) that is used to reference the first shadow entity in the
4680 -- private part of the package
4682 Lim_Header := Limited_View (P);
4683 Lim_Typ := First_Entity (Lim_Header);
4685 -- Remove package and shadow entities from visibility if it has not
4686 -- been analyzed
4688 if not Analyzed (P_Unit) then
4689 Unchain (P);
4690 Set_Is_Immediately_Visible (P, False);
4692 while Present (Lim_Typ) loop
4693 Unchain (Lim_Typ);
4694 Next_Entity (Lim_Typ);
4695 end loop;
4697 -- Otherwise this package has already appeared in the closure and its
4698 -- shadow entities must be replaced by its real entities. This code
4699 -- must be kept synchronized with the complementary code in Install
4700 -- Limited_Withed_Unit.
4702 else
4703 -- Real entities that are type or subtype declarations were hidden
4704 -- from visibility at the point of installation of the limited-view.
4705 -- Now we recover the previous value of the hidden attribute.
4707 declare
4708 E : Entity_Id;
4710 begin
4711 E := First_Entity (P);
4712 while Present (E) and then E /= First_Private_Entity (P) loop
4713 if Is_Type (E) then
4714 Set_Is_Hidden (E, Was_Hidden (E));
4715 end if;
4717 Next_Entity (E);
4718 end loop;
4719 end;
4721 while Present (Lim_Typ)
4722 and then Lim_Typ /= First_Private_Entity (Lim_Header)
4723 loop
4724 pragma Assert (not In_Chain (Non_Limited_View (Lim_Typ)));
4726 -- Child units have not been unchained
4728 if not Is_Child_Unit (Non_Limited_View (Lim_Typ)) then
4729 Prev := Current_Entity (Lim_Typ);
4731 if Prev = Lim_Typ then
4732 Set_Current_Entity (Non_Limited_View (Lim_Typ));
4733 else
4734 while Present (Prev)
4735 and then Homonym (Prev) /= Lim_Typ
4736 loop
4737 Prev := Homonym (Prev);
4738 end loop;
4740 pragma Assert (Present (Prev));
4741 Set_Homonym (Prev, Non_Limited_View (Lim_Typ));
4742 end if;
4744 -- We must also set the next homonym entity of the real entity
4745 -- to handle the case in which the next homonym was a shadow
4746 -- entity.
4748 Set_Homonym (Non_Limited_View (Lim_Typ), Homonym (Lim_Typ));
4749 end if;
4751 Next_Entity (Lim_Typ);
4752 end loop;
4753 end if;
4755 -- Indicate that the limited view of the package is not installed
4757 Set_From_With_Type (P, False);
4758 Set_Limited_View_Installed (N, False);
4759 end Remove_Limited_With_Clause;
4761 --------------------
4762 -- Remove_Parents --
4763 --------------------
4765 procedure Remove_Parents (Lib_Unit : Node_Id) is
4766 P : Node_Id;
4767 P_Name : Entity_Id;
4768 P_Spec : Node_Id := Empty;
4769 E : Entity_Id;
4770 Vis : constant Boolean :=
4771 Scope_Stack.Table (Scope_Stack.Last).Previous_Visibility;
4773 begin
4774 if Is_Child_Spec (Lib_Unit) then
4775 P_Spec := Parent_Spec (Lib_Unit);
4777 elsif Nkind (Lib_Unit) = N_Package_Body
4778 and then Nkind (Original_Node (Lib_Unit)) = N_Package_Instantiation
4779 then
4780 P_Spec := Parent_Spec (Original_Node (Lib_Unit));
4781 end if;
4783 if Present (P_Spec) then
4785 P := Unit (P_Spec);
4786 P_Name := Get_Parent_Entity (P);
4787 Remove_Context_Clauses (P_Spec);
4788 End_Package_Scope (P_Name);
4789 Set_Is_Immediately_Visible (P_Name, Vis);
4791 -- Remove from visibility the siblings as well, which are directly
4792 -- visible while the parent is in scope.
4794 E := First_Entity (P_Name);
4795 while Present (E) loop
4796 if Is_Child_Unit (E) then
4797 Set_Is_Immediately_Visible (E, False);
4798 end if;
4800 Next_Entity (E);
4801 end loop;
4803 Set_In_Package_Body (P_Name, False);
4805 -- This is the recursive call to remove the context of any
4806 -- higher level parent. This recursion ensures that all parents
4807 -- are removed in the reverse order of their installation.
4809 Remove_Parents (P);
4810 end if;
4811 end Remove_Parents;
4813 -----------------------------
4814 -- Remove_With_Type_Clause --
4815 -----------------------------
4817 procedure Remove_With_Type_Clause (Name : Node_Id) is
4818 Typ : Entity_Id;
4819 P : Entity_Id;
4821 procedure Unchain (E : Entity_Id);
4822 -- Remove entity from visibility list
4824 -------------
4825 -- Unchain --
4826 -------------
4828 procedure Unchain (E : Entity_Id) is
4829 Prev : Entity_Id;
4831 begin
4832 Prev := Current_Entity (E);
4834 -- Package entity may appear is several with_type_clauses, and
4835 -- may have been removed already.
4837 if No (Prev) then
4838 return;
4840 elsif Prev = E then
4841 Set_Name_Entity_Id (Chars (E), Homonym (E));
4843 else
4844 while Present (Prev)
4845 and then Homonym (Prev) /= E
4846 loop
4847 Prev := Homonym (Prev);
4848 end loop;
4850 if Present (Prev) then
4851 Set_Homonym (Prev, Homonym (E));
4852 end if;
4853 end if;
4854 end Unchain;
4856 -- Start of processing for Remove_With_Type_Clause
4858 begin
4859 if Nkind (Name) = N_Selected_Component then
4860 Typ := Entity (Selector_Name (Name));
4862 -- If no Typ, then error in declaration, ignore
4864 if No (Typ) then
4865 return;
4866 end if;
4867 else
4868 return;
4869 end if;
4871 P := Scope (Typ);
4873 -- If the exporting package has been analyzed, it has appeared in the
4874 -- context already and should be left alone. Otherwise, remove from
4875 -- visibility.
4877 if not Analyzed (Unit_Declaration_Node (P)) then
4878 Unchain (P);
4879 Unchain (Typ);
4880 Set_Is_Frozen (Typ, False);
4881 end if;
4883 if Ekind (Typ) = E_Record_Type then
4884 Set_From_With_Type (Class_Wide_Type (Typ), False);
4885 Set_From_With_Type (Typ, False);
4886 end if;
4888 Set_From_With_Type (P, False);
4890 -- If P is a child unit, remove parents as well
4892 P := Scope (P);
4893 while Present (P)
4894 and then P /= Standard_Standard
4895 loop
4896 Set_From_With_Type (P, False);
4898 if not Analyzed (Unit_Declaration_Node (P)) then
4899 Unchain (P);
4900 end if;
4902 P := Scope (P);
4903 end loop;
4905 -- The back-end needs to know that an access type is imported, so it
4906 -- does not need elaboration and can appear in a mutually recursive
4907 -- record definition, so the imported flag on an access type is
4908 -- preserved.
4910 end Remove_With_Type_Clause;
4912 ---------------------------------
4913 -- Remove_Unit_From_Visibility --
4914 ---------------------------------
4916 procedure Remove_Unit_From_Visibility (Unit_Name : Entity_Id) is
4917 P : constant Entity_Id := Scope (Unit_Name);
4919 begin
4921 if Debug_Flag_I then
4922 Write_Str ("remove unit ");
4923 Write_Name (Chars (Unit_Name));
4924 Write_Str (" from visibility");
4925 Write_Eol;
4926 end if;
4928 if P /= Standard_Standard then
4929 Set_Is_Visible_Child_Unit (Unit_Name, False);
4930 end if;
4932 Set_Is_Potentially_Use_Visible (Unit_Name, False);
4933 Set_Is_Immediately_Visible (Unit_Name, False);
4935 end Remove_Unit_From_Visibility;
4937 -------------
4938 -- Unchain --
4939 -------------
4941 procedure Unchain (E : Entity_Id) is
4942 Prev : Entity_Id;
4944 begin
4945 Prev := Current_Entity (E);
4947 if No (Prev) then
4948 return;
4950 elsif Prev = E then
4951 Set_Name_Entity_Id (Chars (E), Homonym (E));
4953 else
4954 while Present (Prev)
4955 and then Homonym (Prev) /= E
4956 loop
4957 Prev := Homonym (Prev);
4958 end loop;
4960 if Present (Prev) then
4961 Set_Homonym (Prev, Homonym (E));
4962 end if;
4963 end if;
4965 if Debug_Flag_I then
4966 Write_Str (" (homonym) unchain ");
4967 Write_Name (Chars (E));
4968 Write_Eol;
4969 end if;
4971 end Unchain;
4972 end Sem_Ch10;