Merge with trank @ 137446
[official-gcc.git] / gcc / ada / sem_ch12.adb
blobcae84097d1a1454a561a68302d27277988073092
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 1 2 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2008, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Einfo; use Einfo;
28 with Elists; use Elists;
29 with Errout; use Errout;
30 with Expander; use Expander;
31 with Fname; use Fname;
32 with Fname.UF; use Fname.UF;
33 with Freeze; use Freeze;
34 with Hostparm;
35 with Lib; use Lib;
36 with Lib.Load; use Lib.Load;
37 with Lib.Xref; use Lib.Xref;
38 with Nlists; use Nlists;
39 with Namet; use Namet;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Rident; use Rident;
43 with Restrict; use Restrict;
44 with Rtsfind; use Rtsfind;
45 with Sem; use Sem;
46 with Sem_Cat; use Sem_Cat;
47 with Sem_Ch3; use Sem_Ch3;
48 with Sem_Ch6; use Sem_Ch6;
49 with Sem_Ch7; use Sem_Ch7;
50 with Sem_Ch8; use Sem_Ch8;
51 with Sem_Ch10; use Sem_Ch10;
52 with Sem_Ch13; use Sem_Ch13;
53 with Sem_Disp; use Sem_Disp;
54 with Sem_Elab; use Sem_Elab;
55 with Sem_Elim; use Sem_Elim;
56 with Sem_Eval; use Sem_Eval;
57 with Sem_Res; use Sem_Res;
58 with Sem_Type; use Sem_Type;
59 with Sem_Util; use Sem_Util;
60 with Sem_Warn; use Sem_Warn;
61 with Stand; use Stand;
62 with Sinfo; use Sinfo;
63 with Sinfo.CN; use Sinfo.CN;
64 with Sinput; use Sinput;
65 with Sinput.L; use Sinput.L;
66 with Snames; use Snames;
67 with Stringt; use Stringt;
68 with Uname; use Uname;
69 with Table;
70 with Tbuild; use Tbuild;
71 with Uintp; use Uintp;
72 with Urealp; use Urealp;
74 with GNAT.HTable;
76 package body Sem_Ch12 is
78 ----------------------------------------------------------
79 -- Implementation of Generic Analysis and Instantiation --
80 ----------------------------------------------------------
82 -- GNAT implements generics by macro expansion. No attempt is made to share
83 -- generic instantiations (for now). Analysis of a generic definition does
84 -- not perform any expansion action, but the expander must be called on the
85 -- tree for each instantiation, because the expansion may of course depend
86 -- on the generic actuals. All of this is best achieved as follows:
88 -- a) Semantic analysis of a generic unit is performed on a copy of the
89 -- tree for the generic unit. All tree modifications that follow analysis
90 -- do not affect the original tree. Links are kept between the original
91 -- tree and the copy, in order to recognize non-local references within
92 -- the generic, and propagate them to each instance (recall that name
93 -- resolution is done on the generic declaration: generics are not really
94 -- macros!). This is summarized in the following diagram:
96 -- .-----------. .----------.
97 -- | semantic |<--------------| generic |
98 -- | copy | | unit |
99 -- | |==============>| |
100 -- |___________| global |__________|
101 -- references | | |
102 -- | | |
103 -- .-----|--|.
104 -- | .-----|---.
105 -- | | .----------.
106 -- | | | generic |
107 -- |__| | |
108 -- |__| instance |
109 -- |__________|
111 -- b) Each instantiation copies the original tree, and inserts into it a
112 -- series of declarations that describe the mapping between generic formals
113 -- and actuals. For example, a generic In OUT parameter is an object
114 -- renaming of the corresponding actual, etc. Generic IN parameters are
115 -- constant declarations.
117 -- c) In order to give the right visibility for these renamings, we use
118 -- a different scheme for package and subprogram instantiations. For
119 -- packages, the list of renamings is inserted into the package
120 -- specification, before the visible declarations of the package. The
121 -- renamings are analyzed before any of the text of the instance, and are
122 -- thus visible at the right place. Furthermore, outside of the instance,
123 -- the generic parameters are visible and denote their corresponding
124 -- actuals.
126 -- For subprograms, we create a container package to hold the renamings
127 -- and the subprogram instance itself. Analysis of the package makes the
128 -- renaming declarations visible to the subprogram. After analyzing the
129 -- package, the defining entity for the subprogram is touched-up so that
130 -- it appears declared in the current scope, and not inside the container
131 -- package.
133 -- If the instantiation is a compilation unit, the container package is
134 -- given the same name as the subprogram instance. This ensures that
135 -- the elaboration procedure called by the binder, using the compilation
136 -- unit name, calls in fact the elaboration procedure for the package.
138 -- Not surprisingly, private types complicate this approach. By saving in
139 -- the original generic object the non-local references, we guarantee that
140 -- the proper entities are referenced at the point of instantiation.
141 -- However, for private types, this by itself does not insure that the
142 -- proper VIEW of the entity is used (the full type may be visible at the
143 -- point of generic definition, but not at instantiation, or vice-versa).
144 -- In order to reference the proper view, we special-case any reference
145 -- to private types in the generic object, by saving both views, one in
146 -- the generic and one in the semantic copy. At time of instantiation, we
147 -- check whether the two views are consistent, and exchange declarations if
148 -- necessary, in order to restore the correct visibility. Similarly, if
149 -- the instance view is private when the generic view was not, we perform
150 -- the exchange. After completing the instantiation, we restore the
151 -- current visibility. The flag Has_Private_View marks identifiers in the
152 -- the generic unit that require checking.
154 -- Visibility within nested generic units requires special handling.
155 -- Consider the following scheme:
157 -- type Global is ... -- outside of generic unit.
158 -- generic ...
159 -- package Outer is
160 -- ...
161 -- type Semi_Global is ... -- global to inner.
163 -- generic ... -- 1
164 -- procedure inner (X1 : Global; X2 : Semi_Global);
166 -- procedure in2 is new inner (...); -- 4
167 -- end Outer;
169 -- package New_Outer is new Outer (...); -- 2
170 -- procedure New_Inner is new New_Outer.Inner (...); -- 3
172 -- The semantic analysis of Outer captures all occurrences of Global.
173 -- The semantic analysis of Inner (at 1) captures both occurrences of
174 -- Global and Semi_Global.
176 -- At point 2 (instantiation of Outer), we also produce a generic copy
177 -- of Inner, even though Inner is, at that point, not being instantiated.
178 -- (This is just part of the semantic analysis of New_Outer).
180 -- Critically, references to Global within Inner must be preserved, while
181 -- references to Semi_Global should not preserved, because they must now
182 -- resolve to an entity within New_Outer. To distinguish between these, we
183 -- use a global variable, Current_Instantiated_Parent, which is set when
184 -- performing a generic copy during instantiation (at 2). This variable is
185 -- used when performing a generic copy that is not an instantiation, but
186 -- that is nested within one, as the occurrence of 1 within 2. The analysis
187 -- of a nested generic only preserves references that are global to the
188 -- enclosing Current_Instantiated_Parent. We use the Scope_Depth value to
189 -- determine whether a reference is external to the given parent.
191 -- The instantiation at point 3 requires no special treatment. The method
192 -- works as well for further nestings of generic units, but of course the
193 -- variable Current_Instantiated_Parent must be stacked because nested
194 -- instantiations can occur, e.g. the occurrence of 4 within 2.
196 -- The instantiation of package and subprogram bodies is handled in a
197 -- similar manner, except that it is delayed until after semantic
198 -- analysis is complete. In this fashion complex cross-dependencies
199 -- between several package declarations and bodies containing generics
200 -- can be compiled which otherwise would diagnose spurious circularities.
202 -- For example, it is possible to compile two packages A and B that
203 -- have the following structure:
205 -- package A is package B is
206 -- generic ... generic ...
207 -- package G_A is package G_B is
209 -- with B; with A;
210 -- package body A is package body B is
211 -- package N_B is new G_B (..) package N_A is new G_A (..)
213 -- The table Pending_Instantiations in package Inline is used to keep
214 -- track of body instantiations that are delayed in this manner. Inline
215 -- handles the actual calls to do the body instantiations. This activity
216 -- is part of Inline, since the processing occurs at the same point, and
217 -- for essentially the same reason, as the handling of inlined routines.
219 ----------------------------------------------
220 -- Detection of Instantiation Circularities --
221 ----------------------------------------------
223 -- If we have a chain of instantiations that is circular, this is static
224 -- error which must be detected at compile time. The detection of these
225 -- circularities is carried out at the point that we insert a generic
226 -- instance spec or body. If there is a circularity, then the analysis of
227 -- the offending spec or body will eventually result in trying to load the
228 -- same unit again, and we detect this problem as we analyze the package
229 -- instantiation for the second time.
231 -- At least in some cases after we have detected the circularity, we get
232 -- into trouble if we try to keep going. The following flag is set if a
233 -- circularity is detected, and used to abandon compilation after the
234 -- messages have been posted.
236 Circularity_Detected : Boolean := False;
237 -- This should really be reset on encountering a new main unit, but in
238 -- practice we are not using multiple main units so it is not critical.
240 -------------------------------------------------
241 -- Formal packages and partial parametrization --
242 -------------------------------------------------
244 -- When compiling a generic, a formal package is a local instantiation. If
245 -- declared with a box, its generic formals are visible in the enclosing
246 -- generic. If declared with a partial list of actuals, those actuals that
247 -- are defaulted (covered by an Others clause, or given an explicit box
248 -- initialization) are also visible in the enclosing generic, while those
249 -- that have a corresponding actual are not.
251 -- In our source model of instantiation, the same visibility must be
252 -- present in the spec and body of an instance: the names of the formals
253 -- that are defaulted must be made visible within the instance, and made
254 -- invisible (hidden) after the instantiation is complete, so that they
255 -- are not accessible outside of the instance.
257 -- In a generic, a formal package is treated like a special instantiation.
258 -- Our Ada95 compiler handled formals with and without box in different
259 -- ways. With partial parametrization, we use a single model for both.
260 -- We create a package declaration that consists of the specification of
261 -- the generic package, and a set of declarations that map the actuals
262 -- into local renamings, just as we do for bona fide instantiations. For
263 -- defaulted parameters and formals with a box, we copy directly the
264 -- declarations of the formal into this local package. The result is a
265 -- a package whose visible declarations may include generic formals. This
266 -- package is only used for type checking and visibility analysis, and
267 -- never reaches the back-end, so it can freely violate the placement
268 -- rules for generic formal declarations.
270 -- The list of declarations (renamings and copies of formals) is built
271 -- by Analyze_Associations, just as for regular instantiations.
273 -- At the point of instantiation, conformance checking must be applied only
274 -- to those parameters that were specified in the formal. We perform this
275 -- checking by creating another internal instantiation, this one including
276 -- only the renamings and the formals (the rest of the package spec is not
277 -- relevant to conformance checking). We can then traverse two lists: the
278 -- list of actuals in the instance that corresponds to the formal package,
279 -- and the list of actuals produced for this bogus instantiation. We apply
280 -- the conformance rules to those actuals that are not defaulted (i.e.
281 -- which still appear as generic formals.
283 -- When we compile an instance body we must make the right parameters
284 -- visible again. The predicate Is_Generic_Formal indicates which of the
285 -- formals should have its Is_Hidden flag reset.
287 -----------------------
288 -- Local subprograms --
289 -----------------------
291 procedure Abandon_Instantiation (N : Node_Id);
292 pragma No_Return (Abandon_Instantiation);
293 -- Posts an error message "instantiation abandoned" at the indicated node
294 -- and then raises the exception Instantiation_Error to do it.
296 procedure Analyze_Formal_Array_Type
297 (T : in out Entity_Id;
298 Def : Node_Id);
299 -- A formal array type is treated like an array type declaration, and
300 -- invokes Array_Type_Declaration (sem_ch3) whose first parameter is
301 -- in-out, because in the case of an anonymous type the entity is
302 -- actually created in the procedure.
304 -- The following procedures treat other kinds of formal parameters
306 procedure Analyze_Formal_Derived_Interface_Type
307 (N : Node_Id;
308 T : Entity_Id;
309 Def : Node_Id);
311 procedure Analyze_Formal_Derived_Type
312 (N : Node_Id;
313 T : Entity_Id;
314 Def : Node_Id);
316 procedure Analyze_Formal_Interface_Type
317 (N : Node_Id;
318 T : Entity_Id;
319 Def : Node_Id);
321 -- The following subprograms create abbreviated declarations for formal
322 -- scalar types. We introduce an anonymous base of the proper class for
323 -- each of them, and define the formals as constrained first subtypes of
324 -- their bases. The bounds are expressions that are non-static in the
325 -- generic.
327 procedure Analyze_Formal_Decimal_Fixed_Point_Type
328 (T : Entity_Id; Def : Node_Id);
329 procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id);
330 procedure Analyze_Formal_Floating_Type (T : Entity_Id; Def : Node_Id);
331 procedure Analyze_Formal_Signed_Integer_Type (T : Entity_Id; Def : Node_Id);
332 procedure Analyze_Formal_Modular_Type (T : Entity_Id; Def : Node_Id);
333 procedure Analyze_Formal_Ordinary_Fixed_Point_Type
334 (T : Entity_Id; Def : Node_Id);
336 procedure Analyze_Formal_Private_Type
337 (N : Node_Id;
338 T : Entity_Id;
339 Def : Node_Id);
340 -- Creates a new private type, which does not require completion
342 procedure Analyze_Generic_Formal_Part (N : Node_Id);
344 procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id);
345 -- Create a new access type with the given designated type
347 function Analyze_Associations
348 (I_Node : Node_Id;
349 Formals : List_Id;
350 F_Copy : List_Id) return List_Id;
351 -- At instantiation time, build the list of associations between formals
352 -- and actuals. Each association becomes a renaming declaration for the
353 -- formal entity. F_Copy is the analyzed list of formals in the generic
354 -- copy. It is used to apply legality checks to the actuals. I_Node is the
355 -- instantiation node itself.
357 procedure Analyze_Subprogram_Instantiation
358 (N : Node_Id;
359 K : Entity_Kind);
361 procedure Build_Instance_Compilation_Unit_Nodes
362 (N : Node_Id;
363 Act_Body : Node_Id;
364 Act_Decl : Node_Id);
365 -- This procedure is used in the case where the generic instance of a
366 -- subprogram body or package body is a library unit. In this case, the
367 -- original library unit node for the generic instantiation must be
368 -- replaced by the resulting generic body, and a link made to a new
369 -- compilation unit node for the generic declaration. The argument N is
370 -- the original generic instantiation. Act_Body and Act_Decl are the body
371 -- and declaration of the instance (either package body and declaration
372 -- nodes or subprogram body and declaration nodes depending on the case).
373 -- On return, the node N has been rewritten with the actual body.
375 procedure Check_Access_Definition (N : Node_Id);
376 -- Subsidiary routine to null exclusion processing. Perform an assertion
377 -- check on Ada version and the presence of an access definition in N.
379 procedure Check_Formal_Packages (P_Id : Entity_Id);
380 -- Apply the following to all formal packages in generic associations
382 procedure Check_Formal_Package_Instance
383 (Formal_Pack : Entity_Id;
384 Actual_Pack : Entity_Id);
385 -- Verify that the actuals of the actual instance match the actuals of
386 -- the template for a formal package that is not declared with a box.
388 procedure Check_Forward_Instantiation (Decl : Node_Id);
389 -- If the generic is a local entity and the corresponding body has not
390 -- been seen yet, flag enclosing packages to indicate that it will be
391 -- elaborated after the generic body. Subprograms declared in the same
392 -- package cannot be inlined by the front-end because front-end inlining
393 -- requires a strict linear order of elaboration.
395 procedure Check_Hidden_Child_Unit
396 (N : Node_Id;
397 Gen_Unit : Entity_Id;
398 Act_Decl_Id : Entity_Id);
399 -- If the generic unit is an implicit child instance within a parent
400 -- instance, we need to make an explicit test that it is not hidden by
401 -- a child instance of the same name and parent.
403 procedure Check_Generic_Actuals
404 (Instance : Entity_Id;
405 Is_Formal_Box : Boolean);
406 -- Similar to previous one. Check the actuals in the instantiation,
407 -- whose views can change between the point of instantiation and the point
408 -- of instantiation of the body. In addition, mark the generic renamings
409 -- as generic actuals, so that they are not compatible with other actuals.
410 -- Recurse on an actual that is a formal package whose declaration has
411 -- a box.
413 function Contains_Instance_Of
414 (Inner : Entity_Id;
415 Outer : Entity_Id;
416 N : Node_Id) return Boolean;
417 -- Inner is instantiated within the generic Outer. Check whether Inner
418 -- directly or indirectly contains an instance of Outer or of one of its
419 -- parents, in the case of a subunit. Each generic unit holds a list of
420 -- the entities instantiated within (at any depth). This procedure
421 -- determines whether the set of such lists contains a cycle, i.e. an
422 -- illegal circular instantiation.
424 function Denotes_Formal_Package
425 (Pack : Entity_Id;
426 On_Exit : Boolean := False) return Boolean;
427 -- Returns True if E is a formal package of an enclosing generic, or
428 -- the actual for such a formal in an enclosing instantiation. If such
429 -- a package is used as a formal in an nested generic, or as an actual
430 -- in a nested instantiation, the visibility of ITS formals should not
431 -- be modified. When called from within Restore_Private_Views, the flag
432 -- On_Exit is true, to indicate that the search for a possible enclosing
433 -- instance should ignore the current one.
435 function Find_Actual_Type
436 (Typ : Entity_Id;
437 Gen_Type : Entity_Id) return Entity_Id;
438 -- When validating the actual types of a child instance, check whether
439 -- the formal is a formal type of the parent unit, and retrieve the current
440 -- actual for it. Typ is the entity in the analyzed formal type declaration
441 -- (component or index type of an array type, or designated type of an
442 -- access formal) and Gen_Type is the enclosing analyzed formal array
443 -- or access type. The desired actual may be a formal of a parent, or may
444 -- be declared in a formal package of a parent. In both cases it is a
445 -- generic actual type because it appears within a visible instance.
446 -- Finally, it may be declared in a parent unit without being a formal
447 -- of that unit, in which case it must be retrieved by visibility.
448 -- Ambiguities may still arise if two homonyms are declared in two formal
449 -- packages, and the prefix of the formal type may be needed to resolve
450 -- the ambiguity in the instance ???
452 function In_Same_Declarative_Part
453 (F_Node : Node_Id;
454 Inst : Node_Id) return Boolean;
455 -- True if the instantiation Inst and the given freeze_node F_Node appear
456 -- within the same declarative part, ignoring subunits, but with no inter-
457 -- vening subprograms or concurrent units. If true, the freeze node
458 -- of the instance can be placed after the freeze node of the parent,
459 -- which it itself an instance.
461 function In_Main_Context (E : Entity_Id) return Boolean;
462 -- Check whether an instantiation is in the context of the main unit.
463 -- Used to determine whether its body should be elaborated to allow
464 -- front-end inlining.
466 function Is_Generic_Formal (E : Entity_Id) return Boolean;
467 -- Utility to determine whether a given entity is declared by means of
468 -- of a formal parameter declaration. Used to set properly the visibility
469 -- of generic formals of a generic package declared with a box or with
470 -- partial parametrization.
472 procedure Set_Instance_Env
473 (Gen_Unit : Entity_Id;
474 Act_Unit : Entity_Id);
475 -- Save current instance on saved environment, to be used to determine
476 -- the global status of entities in nested instances. Part of Save_Env.
477 -- called after verifying that the generic unit is legal for the instance,
478 -- The procedure also examines whether the generic unit is a predefined
479 -- unit, in order to set configuration switches accordingly. As a result
480 -- the procedure must be called after analyzing and freezing the actuals.
482 procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id);
483 -- Associate analyzed generic parameter with corresponding
484 -- instance. Used for semantic checks at instantiation time.
486 function Has_Been_Exchanged (E : Entity_Id) return Boolean;
487 -- Traverse the Exchanged_Views list to see if a type was private
488 -- and has already been flipped during this phase of instantiation.
490 procedure Hide_Current_Scope;
491 -- When instantiating a generic child unit, the parent context must be
492 -- present, but the instance and all entities that may be generated
493 -- must be inserted in the current scope. We leave the current scope
494 -- on the stack, but make its entities invisible to avoid visibility
495 -- problems. This is reversed at the end of the instantiation. This is
496 -- not done for the instantiation of the bodies, which only require the
497 -- instances of the generic parents to be in scope.
499 procedure Install_Body
500 (Act_Body : Node_Id;
501 N : Node_Id;
502 Gen_Body : Node_Id;
503 Gen_Decl : Node_Id);
504 -- If the instantiation happens textually before the body of the generic,
505 -- the instantiation of the body must be analyzed after the generic body,
506 -- and not at the point of instantiation. Such early instantiations can
507 -- happen if the generic and the instance appear in a package declaration
508 -- because the generic body can only appear in the corresponding package
509 -- body. Early instantiations can also appear if generic, instance and
510 -- body are all in the declarative part of a subprogram or entry. Entities
511 -- of packages that are early instantiations are delayed, and their freeze
512 -- node appears after the generic body.
514 procedure Insert_After_Last_Decl (N : Node_Id; F_Node : Node_Id);
515 -- Insert freeze node at the end of the declarative part that includes the
516 -- instance node N. If N is in the visible part of an enclosing package
517 -- declaration, the freeze node has to be inserted at the end of the
518 -- private declarations, if any.
520 procedure Freeze_Subprogram_Body
521 (Inst_Node : Node_Id;
522 Gen_Body : Node_Id;
523 Pack_Id : Entity_Id);
524 -- The generic body may appear textually after the instance, including
525 -- in the proper body of a stub, or within a different package instance.
526 -- Given that the instance can only be elaborated after the generic, we
527 -- place freeze_nodes for the instance and/or for packages that may enclose
528 -- the instance and the generic, so that the back-end can establish the
529 -- proper order of elaboration.
531 procedure Init_Env;
532 -- Establish environment for subsequent instantiation. Separated from
533 -- Save_Env because data-structures for visibility handling must be
534 -- initialized before call to Check_Generic_Child_Unit.
536 procedure Install_Formal_Packages (Par : Entity_Id);
537 -- If any of the formals of the parent are formal packages with box,
538 -- their formal parts are visible in the parent and thus in the child
539 -- unit as well. Analogous to what is done in Check_Generic_Actuals
540 -- for the unit itself. This procedure is also used in an instance, to
541 -- make visible the proper entities of the actual for a formal package
542 -- declared with a box.
544 procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False);
545 -- When compiling an instance of a child unit the parent (which is
546 -- itself an instance) is an enclosing scope that must be made
547 -- immediately visible. This procedure is also used to install the non-
548 -- generic parent of a generic child unit when compiling its body, so
549 -- that full views of types in the parent are made visible.
551 procedure Remove_Parent (In_Body : Boolean := False);
552 -- Reverse effect after instantiation of child is complete
554 procedure Inline_Instance_Body
555 (N : Node_Id;
556 Gen_Unit : Entity_Id;
557 Act_Decl : Node_Id);
558 -- If front-end inlining is requested, instantiate the package body,
559 -- and preserve the visibility of its compilation unit, to insure
560 -- that successive instantiations succeed.
562 -- The functions Instantiate_XXX perform various legality checks and build
563 -- the declarations for instantiated generic parameters. In all of these
564 -- Formal is the entity in the generic unit, Actual is the entity of
565 -- expression in the generic associations, and Analyzed_Formal is the
566 -- formal in the generic copy, which contains the semantic information to
567 -- be used to validate the actual.
569 function Instantiate_Object
570 (Formal : Node_Id;
571 Actual : Node_Id;
572 Analyzed_Formal : Node_Id) return List_Id;
574 function Instantiate_Type
575 (Formal : Node_Id;
576 Actual : Node_Id;
577 Analyzed_Formal : Node_Id;
578 Actual_Decls : List_Id) return List_Id;
580 function Instantiate_Formal_Subprogram
581 (Formal : Node_Id;
582 Actual : Node_Id;
583 Analyzed_Formal : Node_Id) return Node_Id;
585 function Instantiate_Formal_Package
586 (Formal : Node_Id;
587 Actual : Node_Id;
588 Analyzed_Formal : Node_Id) return List_Id;
589 -- If the formal package is declared with a box, special visibility rules
590 -- apply to its formals: they are in the visible part of the package. This
591 -- is true in the declarative region of the formal package, that is to say
592 -- in the enclosing generic or instantiation. For an instantiation, the
593 -- parameters of the formal package are made visible in an explicit step.
594 -- Furthermore, if the actual has a visible USE clause, these formals must
595 -- be made potentially use-visible as well. On exit from the enclosing
596 -- instantiation, the reverse must be done.
598 -- For a formal package declared without a box, there are conformance rules
599 -- that apply to the actuals in the generic declaration and the actuals of
600 -- the actual package in the enclosing instantiation. The simplest way to
601 -- apply these rules is to repeat the instantiation of the formal package
602 -- in the context of the enclosing instance, and compare the generic
603 -- associations of this instantiation with those of the actual package.
604 -- This internal instantiation only needs to contain the renamings of the
605 -- formals: the visible and private declarations themselves need not be
606 -- created.
608 -- In Ada 2005, the formal package may be only partially parametrized. In
609 -- that case the visibility step must make visible those actuals whose
610 -- corresponding formals were given with a box. A final complication
611 -- involves inherited operations from formal derived types, which must be
612 -- visible if the type is.
614 function Is_In_Main_Unit (N : Node_Id) return Boolean;
615 -- Test if given node is in the main unit
617 procedure Load_Parent_Of_Generic
618 (N : Node_Id;
619 Spec : Node_Id;
620 Body_Optional : Boolean := False);
621 -- If the generic appears in a separate non-generic library unit, load the
622 -- corresponding body to retrieve the body of the generic. N is the node
623 -- for the generic instantiation, Spec is the generic package declaration.
625 -- Body_Optional is a flag that indicates that the body is being loaded to
626 -- ensure that temporaries are generated consistently when there are other
627 -- instances in the current declarative part that precede the one being
628 -- loaded. In that case a missing body is acceptable.
630 procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id);
631 -- Add the context clause of the unit containing a generic unit to an
632 -- instantiation that is a compilation unit.
634 function Get_Associated_Node (N : Node_Id) return Node_Id;
635 -- In order to propagate semantic information back from the analyzed copy
636 -- to the original generic, we maintain links between selected nodes in the
637 -- generic and their corresponding copies. At the end of generic analysis,
638 -- the routine Save_Global_References traverses the generic tree, examines
639 -- the semantic information, and preserves the links to those nodes that
640 -- contain global information. At instantiation, the information from the
641 -- associated node is placed on the new copy, so that name resolution is
642 -- not repeated.
644 -- Three kinds of source nodes have associated nodes:
646 -- a) those that can reference (denote) entities, that is identifiers,
647 -- character literals, expanded_names, operator symbols, operators,
648 -- and attribute reference nodes. These nodes have an Entity field
649 -- and are the set of nodes that are in N_Has_Entity.
651 -- b) aggregates (N_Aggregate and N_Extension_Aggregate)
653 -- c) selected components (N_Selected_Component)
655 -- For the first class, the associated node preserves the entity if it is
656 -- global. If the generic contains nested instantiations, the associated
657 -- node itself has been recopied, and a chain of them must be followed.
659 -- For aggregates, the associated node allows retrieval of the type, which
660 -- may otherwise not appear in the generic. The view of this type may be
661 -- different between generic and instantiation, and the full view can be
662 -- installed before the instantiation is analyzed. For aggregates of type
663 -- extensions, the same view exchange may have to be performed for some of
664 -- the ancestor types, if their view is private at the point of
665 -- instantiation.
667 -- Nodes that are selected components in the parse tree may be rewritten
668 -- as expanded names after resolution, and must be treated as potential
669 -- entity holders, which is why they also have an Associated_Node.
671 -- Nodes that do not come from source, such as freeze nodes, do not appear
672 -- in the generic tree, and need not have an associated node.
674 -- The associated node is stored in the Associated_Node field. Note that
675 -- this field overlaps Entity, which is fine, because the whole point is
676 -- that we don't need or want the normal Entity field in this situation.
678 procedure Move_Freeze_Nodes
679 (Out_Of : Entity_Id;
680 After : Node_Id;
681 L : List_Id);
682 -- Freeze nodes can be generated in the analysis of a generic unit, but
683 -- will not be seen by the back-end. It is necessary to move those nodes
684 -- to the enclosing scope if they freeze an outer entity. We place them
685 -- at the end of the enclosing generic package, which is semantically
686 -- neutral.
688 procedure Preanalyze_Actuals (N : Node_Id);
689 -- Analyze actuals to perform name resolution. Full resolution is done
690 -- later, when the expected types are known, but names have to be captured
691 -- before installing parents of generics, that are not visible for the
692 -- actuals themselves.
694 procedure Valid_Default_Attribute (Nam : Entity_Id; Def : Node_Id);
695 -- Verify that an attribute that appears as the default for a formal
696 -- subprogram is a function or procedure with the correct profile.
698 -------------------------------------------
699 -- Data Structures for Generic Renamings --
700 -------------------------------------------
702 -- The map Generic_Renamings associates generic entities with their
703 -- corresponding actuals. Currently used to validate type instances. It
704 -- will eventually be used for all generic parameters to eliminate the
705 -- need for overload resolution in the instance.
707 type Assoc_Ptr is new Int;
709 Assoc_Null : constant Assoc_Ptr := -1;
711 type Assoc is record
712 Gen_Id : Entity_Id;
713 Act_Id : Entity_Id;
714 Next_In_HTable : Assoc_Ptr;
715 end record;
717 package Generic_Renamings is new Table.Table
718 (Table_Component_Type => Assoc,
719 Table_Index_Type => Assoc_Ptr,
720 Table_Low_Bound => 0,
721 Table_Initial => 10,
722 Table_Increment => 100,
723 Table_Name => "Generic_Renamings");
725 -- Variable to hold enclosing instantiation. When the environment is
726 -- saved for a subprogram inlining, the corresponding Act_Id is empty.
728 Current_Instantiated_Parent : Assoc := (Empty, Empty, Assoc_Null);
730 -- Hash table for associations
732 HTable_Size : constant := 37;
733 type HTable_Range is range 0 .. HTable_Size - 1;
735 procedure Set_Next_Assoc (E : Assoc_Ptr; Next : Assoc_Ptr);
736 function Next_Assoc (E : Assoc_Ptr) return Assoc_Ptr;
737 function Get_Gen_Id (E : Assoc_Ptr) return Entity_Id;
738 function Hash (F : Entity_Id) return HTable_Range;
740 package Generic_Renamings_HTable is new GNAT.HTable.Static_HTable (
741 Header_Num => HTable_Range,
742 Element => Assoc,
743 Elmt_Ptr => Assoc_Ptr,
744 Null_Ptr => Assoc_Null,
745 Set_Next => Set_Next_Assoc,
746 Next => Next_Assoc,
747 Key => Entity_Id,
748 Get_Key => Get_Gen_Id,
749 Hash => Hash,
750 Equal => "=");
752 Exchanged_Views : Elist_Id;
753 -- This list holds the private views that have been exchanged during
754 -- instantiation to restore the visibility of the generic declaration.
755 -- (see comments above). After instantiation, the current visibility is
756 -- reestablished by means of a traversal of this list.
758 Hidden_Entities : Elist_Id;
759 -- This list holds the entities of the current scope that are removed
760 -- from immediate visibility when instantiating a child unit. Their
761 -- visibility is restored in Remove_Parent.
763 -- Because instantiations can be recursive, the following must be saved
764 -- on entry and restored on exit from an instantiation (spec or body).
765 -- This is done by the two procedures Save_Env and Restore_Env. For
766 -- package and subprogram instantiations (but not for the body instances)
767 -- the action of Save_Env is done in two steps: Init_Env is called before
768 -- Check_Generic_Child_Unit, because setting the parent instances requires
769 -- that the visibility data structures be properly initialized. Once the
770 -- generic is unit is validated, Set_Instance_Env completes Save_Env.
772 Parent_Unit_Visible : Boolean := False;
773 -- Parent_Unit_Visible is used when the generic is a child unit, and
774 -- indicates whether the ultimate parent of the generic is visible in the
775 -- instantiation environment. It is used to reset the visibility of the
776 -- parent at the end of the instantiation (see Remove_Parent).
778 Instance_Parent_Unit : Entity_Id := Empty;
779 -- This records the ultimate parent unit of an instance of a generic
780 -- child unit and is used in conjunction with Parent_Unit_Visible to
781 -- indicate the unit to which the Parent_Unit_Visible flag corresponds.
783 type Instance_Env is record
784 Instantiated_Parent : Assoc;
785 Exchanged_Views : Elist_Id;
786 Hidden_Entities : Elist_Id;
787 Current_Sem_Unit : Unit_Number_Type;
788 Parent_Unit_Visible : Boolean := False;
789 Instance_Parent_Unit : Entity_Id := Empty;
790 Switches : Config_Switches_Type;
791 end record;
793 package Instance_Envs is new Table.Table (
794 Table_Component_Type => Instance_Env,
795 Table_Index_Type => Int,
796 Table_Low_Bound => 0,
797 Table_Initial => 32,
798 Table_Increment => 100,
799 Table_Name => "Instance_Envs");
801 procedure Restore_Private_Views
802 (Pack_Id : Entity_Id;
803 Is_Package : Boolean := True);
804 -- Restore the private views of external types, and unmark the generic
805 -- renamings of actuals, so that they become compatible subtypes again.
806 -- For subprograms, Pack_Id is the package constructed to hold the
807 -- renamings.
809 procedure Switch_View (T : Entity_Id);
810 -- Switch the partial and full views of a type and its private
811 -- dependents (i.e. its subtypes and derived types).
813 ------------------------------------
814 -- Structures for Error Reporting --
815 ------------------------------------
817 Instantiation_Node : Node_Id;
818 -- Used by subprograms that validate instantiation of formal parameters
819 -- where there might be no actual on which to place the error message.
820 -- Also used to locate the instantiation node for generic subunits.
822 Instantiation_Error : exception;
823 -- When there is a semantic error in the generic parameter matching,
824 -- there is no point in continuing the instantiation, because the
825 -- number of cascaded errors is unpredictable. This exception aborts
826 -- the instantiation process altogether.
828 S_Adjustment : Sloc_Adjustment;
829 -- Offset created for each node in an instantiation, in order to keep
830 -- track of the source position of the instantiation in each of its nodes.
831 -- A subsequent semantic error or warning on a construct of the instance
832 -- points to both places: the original generic node, and the point of
833 -- instantiation. See Sinput and Sinput.L for additional details.
835 ------------------------------------------------------------
836 -- Data structure for keeping track when inside a Generic --
837 ------------------------------------------------------------
839 -- The following table is used to save values of the Inside_A_Generic
840 -- flag (see spec of Sem) when they are saved by Start_Generic.
842 package Generic_Flags is new Table.Table (
843 Table_Component_Type => Boolean,
844 Table_Index_Type => Int,
845 Table_Low_Bound => 0,
846 Table_Initial => 32,
847 Table_Increment => 200,
848 Table_Name => "Generic_Flags");
850 ---------------------------
851 -- Abandon_Instantiation --
852 ---------------------------
854 procedure Abandon_Instantiation (N : Node_Id) is
855 begin
856 Error_Msg_N ("\instantiation abandoned!", N);
857 raise Instantiation_Error;
858 end Abandon_Instantiation;
860 --------------------------
861 -- Analyze_Associations --
862 --------------------------
864 function Analyze_Associations
865 (I_Node : Node_Id;
866 Formals : List_Id;
867 F_Copy : List_Id) return List_Id
869 Actual_Types : constant Elist_Id := New_Elmt_List;
870 Assoc : constant List_Id := New_List;
871 Default_Actuals : constant Elist_Id := New_Elmt_List;
872 Gen_Unit : constant Entity_Id := Defining_Entity (Parent (F_Copy));
873 Actuals : List_Id;
874 Actual : Node_Id;
875 Formal : Node_Id;
876 Next_Formal : Node_Id;
877 Temp_Formal : Node_Id;
878 Analyzed_Formal : Node_Id;
879 Match : Node_Id;
880 Named : Node_Id;
881 First_Named : Node_Id := Empty;
883 Default_Formals : constant List_Id := New_List;
884 -- If an Other_Choice is present, some of the formals may be defaulted.
885 -- To simplify the treatment of visibility in an instance, we introduce
886 -- individual defaults for each such formal. These defaults are
887 -- appended to the list of associations and replace the Others_Choice.
889 Found_Assoc : Node_Id;
890 -- Association for the current formal being match. Empty if there are
891 -- no remaining actuals, or if there is no named association with the
892 -- name of the formal.
894 Is_Named_Assoc : Boolean;
895 Num_Matched : Int := 0;
896 Num_Actuals : Int := 0;
898 Others_Present : Boolean := False;
899 -- In Ada 2005, indicates partial parametrization of of a formal
900 -- package. As usual an others association must be last in the list.
902 function Matching_Actual
903 (F : Entity_Id;
904 A_F : Entity_Id) return Node_Id;
905 -- Find actual that corresponds to a given a formal parameter. If the
906 -- actuals are positional, return the next one, if any. If the actuals
907 -- are named, scan the parameter associations to find the right one.
908 -- A_F is the corresponding entity in the analyzed generic,which is
909 -- placed on the selector name for ASIS use.
911 -- In Ada 2005, a named association may be given with a box, in which
912 -- case Matching_Actual sets Found_Assoc to the generic association,
913 -- but return Empty for the actual itself. In this case the code below
914 -- creates a corresponding declaration for the formal.
916 function Partial_Parametrization return Boolean;
917 -- Ada 2005: if no match is found for a given formal, check if the
918 -- association for it includes a box, or whether the associations
919 -- include an Others clause.
921 procedure Process_Default (F : Entity_Id);
922 -- Add a copy of the declaration of generic formal F to the list of
923 -- associations, and add an explicit box association for F if there
924 -- is none yet, and the default comes from an Others_Choice.
926 procedure Set_Analyzed_Formal;
927 -- Find the node in the generic copy that corresponds to a given formal.
928 -- The semantic information on this node is used to perform legality
929 -- checks on the actuals. Because semantic analysis can introduce some
930 -- anonymous entities or modify the declaration node itself, the
931 -- correspondence between the two lists is not one-one. In addition to
932 -- anonymous types, the presence a formal equality will introduce an
933 -- implicit declaration for the corresponding inequality.
935 ---------------------
936 -- Matching_Actual --
937 ---------------------
939 function Matching_Actual
940 (F : Entity_Id;
941 A_F : Entity_Id) return Node_Id
943 Prev : Node_Id;
944 Act : Node_Id;
946 begin
947 Is_Named_Assoc := False;
949 -- End of list of purely positional parameters
951 if No (Actual)
952 or else Nkind (Actual) = N_Others_Choice
953 then
954 Found_Assoc := Empty;
955 Act := Empty;
957 -- Case of positional parameter corresponding to current formal
959 elsif No (Selector_Name (Actual)) then
960 Found_Assoc := Actual;
961 Act := Explicit_Generic_Actual_Parameter (Actual);
962 Num_Matched := Num_Matched + 1;
963 Next (Actual);
965 -- Otherwise scan list of named actuals to find the one with the
966 -- desired name. All remaining actuals have explicit names.
968 else
969 Is_Named_Assoc := True;
970 Found_Assoc := Empty;
971 Act := Empty;
972 Prev := Empty;
974 while Present (Actual) loop
975 if Chars (Selector_Name (Actual)) = Chars (F) then
976 Set_Entity (Selector_Name (Actual), A_F);
977 Set_Etype (Selector_Name (Actual), Etype (A_F));
978 Generate_Reference (A_F, Selector_Name (Actual));
979 Found_Assoc := Actual;
980 Act := Explicit_Generic_Actual_Parameter (Actual);
981 Num_Matched := Num_Matched + 1;
982 exit;
983 end if;
985 Prev := Actual;
986 Next (Actual);
987 end loop;
989 -- Reset for subsequent searches. In most cases the named
990 -- associations are in order. If they are not, we reorder them
991 -- to avoid scanning twice the same actual. This is not just a
992 -- question of efficiency: there may be multiple defaults with
993 -- boxes that have the same name. In a nested instantiation we
994 -- insert actuals for those defaults, and cannot rely on their
995 -- names to disambiguate them.
997 if Actual = First_Named then
998 Next (First_Named);
1000 elsif Present (Actual) then
1001 Insert_Before (First_Named, Remove_Next (Prev));
1002 end if;
1004 Actual := First_Named;
1005 end if;
1007 if Is_Entity_Name (Act) and then Present (Entity (Act)) then
1008 Set_Used_As_Generic_Actual (Entity (Act));
1009 end if;
1011 return Act;
1012 end Matching_Actual;
1014 -----------------------------
1015 -- Partial_Parametrization --
1016 -----------------------------
1018 function Partial_Parametrization return Boolean is
1019 begin
1020 return Others_Present
1021 or else (Present (Found_Assoc) and then Box_Present (Found_Assoc));
1022 end Partial_Parametrization;
1024 ---------------------
1025 -- Process_Default --
1026 ---------------------
1028 procedure Process_Default (F : Entity_Id) is
1029 Loc : constant Source_Ptr := Sloc (I_Node);
1030 F_Id : constant Entity_Id := Defining_Entity (F);
1032 Decl : Node_Id;
1033 Default : Node_Id;
1034 Id : Entity_Id;
1036 begin
1037 -- Append copy of formal declaration to associations, and create
1038 -- new defining identifier for it.
1040 Decl := New_Copy_Tree (F);
1041 Id := Make_Defining_Identifier (Sloc (F_Id), Chars => Chars (F_Id));
1043 if Nkind (F) in N_Formal_Subprogram_Declaration then
1044 Set_Defining_Unit_Name (Specification (Decl), Id);
1046 else
1047 Set_Defining_Identifier (Decl, Id);
1048 end if;
1050 Append (Decl, Assoc);
1052 if No (Found_Assoc) then
1053 Default :=
1054 Make_Generic_Association (Loc,
1055 Selector_Name => New_Occurrence_Of (Id, Loc),
1056 Explicit_Generic_Actual_Parameter => Empty);
1057 Set_Box_Present (Default);
1058 Append (Default, Default_Formals);
1059 end if;
1060 end Process_Default;
1062 -------------------------
1063 -- Set_Analyzed_Formal --
1064 -------------------------
1066 procedure Set_Analyzed_Formal is
1067 Kind : Node_Kind;
1069 begin
1070 while Present (Analyzed_Formal) loop
1071 Kind := Nkind (Analyzed_Formal);
1073 case Nkind (Formal) is
1075 when N_Formal_Subprogram_Declaration =>
1076 exit when Kind in N_Formal_Subprogram_Declaration
1077 and then
1078 Chars
1079 (Defining_Unit_Name (Specification (Formal))) =
1080 Chars
1081 (Defining_Unit_Name (Specification (Analyzed_Formal)));
1083 when N_Formal_Package_Declaration =>
1084 exit when Nkind_In (Kind, N_Formal_Package_Declaration,
1085 N_Generic_Package_Declaration,
1086 N_Package_Declaration);
1088 when N_Use_Package_Clause | N_Use_Type_Clause => exit;
1090 when others =>
1092 -- Skip freeze nodes, and nodes inserted to replace
1093 -- unrecognized pragmas.
1095 exit when
1096 Kind not in N_Formal_Subprogram_Declaration
1097 and then not Nkind_In (Kind, N_Subprogram_Declaration,
1098 N_Freeze_Entity,
1099 N_Null_Statement,
1100 N_Itype_Reference)
1101 and then Chars (Defining_Identifier (Formal)) =
1102 Chars (Defining_Identifier (Analyzed_Formal));
1103 end case;
1105 Next (Analyzed_Formal);
1106 end loop;
1107 end Set_Analyzed_Formal;
1109 -- Start of processing for Analyze_Associations
1111 begin
1112 Actuals := Generic_Associations (I_Node);
1114 if Present (Actuals) then
1116 -- check for an Others choice, indicating a partial parametrization
1117 -- for a formal package.
1119 Actual := First (Actuals);
1120 while Present (Actual) loop
1121 if Nkind (Actual) = N_Others_Choice then
1122 Others_Present := True;
1124 if Present (Next (Actual)) then
1125 Error_Msg_N ("others must be last association", Actual);
1126 end if;
1128 -- This subprogram is used both for formal packages and for
1129 -- instantiations. For the latter, associations must all be
1130 -- explicit.
1132 if Nkind (I_Node) /= N_Formal_Package_Declaration
1133 and then Comes_From_Source (I_Node)
1134 then
1135 Error_Msg_N
1136 ("others association not allowed in an instance",
1137 Actual);
1138 end if;
1140 -- In any case, nothing to do after the others association
1142 exit;
1144 elsif Box_Present (Actual)
1145 and then Comes_From_Source (I_Node)
1146 and then Nkind (I_Node) /= N_Formal_Package_Declaration
1147 then
1148 Error_Msg_N
1149 ("box association not allowed in an instance", Actual);
1150 end if;
1152 Next (Actual);
1153 end loop;
1155 -- If named associations are present, save first named association
1156 -- (it may of course be Empty) to facilitate subsequent name search.
1158 First_Named := First (Actuals);
1159 while Present (First_Named)
1160 and then Nkind (First_Named) /= N_Others_Choice
1161 and then No (Selector_Name (First_Named))
1162 loop
1163 Num_Actuals := Num_Actuals + 1;
1164 Next (First_Named);
1165 end loop;
1166 end if;
1168 Named := First_Named;
1169 while Present (Named) loop
1170 if Nkind (Named) /= N_Others_Choice
1171 and then No (Selector_Name (Named))
1172 then
1173 Error_Msg_N ("invalid positional actual after named one", Named);
1174 Abandon_Instantiation (Named);
1175 end if;
1177 -- A named association may lack an actual parameter, if it was
1178 -- introduced for a default subprogram that turns out to be local
1179 -- to the outer instantiation.
1181 if Nkind (Named) /= N_Others_Choice
1182 and then Present (Explicit_Generic_Actual_Parameter (Named))
1183 then
1184 Num_Actuals := Num_Actuals + 1;
1185 end if;
1187 Next (Named);
1188 end loop;
1190 if Present (Formals) then
1191 Formal := First_Non_Pragma (Formals);
1192 Analyzed_Formal := First_Non_Pragma (F_Copy);
1194 if Present (Actuals) then
1195 Actual := First (Actuals);
1197 -- All formals should have default values
1199 else
1200 Actual := Empty;
1201 end if;
1203 while Present (Formal) loop
1204 Set_Analyzed_Formal;
1205 Next_Formal := Next_Non_Pragma (Formal);
1207 case Nkind (Formal) is
1208 when N_Formal_Object_Declaration =>
1209 Match :=
1210 Matching_Actual (
1211 Defining_Identifier (Formal),
1212 Defining_Identifier (Analyzed_Formal));
1214 if No (Match) and then Partial_Parametrization then
1215 Process_Default (Formal);
1216 else
1217 Append_List
1218 (Instantiate_Object (Formal, Match, Analyzed_Formal),
1219 Assoc);
1220 end if;
1222 when N_Formal_Type_Declaration =>
1223 Match :=
1224 Matching_Actual (
1225 Defining_Identifier (Formal),
1226 Defining_Identifier (Analyzed_Formal));
1228 if No (Match) then
1229 if Partial_Parametrization then
1230 Process_Default (Formal);
1232 else
1233 Error_Msg_Sloc := Sloc (Gen_Unit);
1234 Error_Msg_NE
1235 ("missing actual&",
1236 Instantiation_Node,
1237 Defining_Identifier (Formal));
1238 Error_Msg_NE ("\in instantiation of & declared#",
1239 Instantiation_Node, Gen_Unit);
1240 Abandon_Instantiation (Instantiation_Node);
1241 end if;
1243 else
1244 Analyze (Match);
1245 Append_List
1246 (Instantiate_Type
1247 (Formal, Match, Analyzed_Formal, Assoc),
1248 Assoc);
1250 -- An instantiation is a freeze point for the actuals,
1251 -- unless this is a rewritten formal package.
1253 if Nkind (I_Node) /= N_Formal_Package_Declaration then
1254 Append_Elmt (Entity (Match), Actual_Types);
1255 end if;
1256 end if;
1258 -- A remote access-to-class-wide type must not be an
1259 -- actual parameter for a generic formal of an access
1260 -- type (E.2.2 (17)).
1262 if Nkind (Analyzed_Formal) = N_Formal_Type_Declaration
1263 and then
1264 Nkind (Formal_Type_Definition (Analyzed_Formal)) =
1265 N_Access_To_Object_Definition
1266 then
1267 Validate_Remote_Access_To_Class_Wide_Type (Match);
1268 end if;
1270 when N_Formal_Subprogram_Declaration =>
1271 Match :=
1272 Matching_Actual (
1273 Defining_Unit_Name (Specification (Formal)),
1274 Defining_Unit_Name (Specification (Analyzed_Formal)));
1276 -- If the formal subprogram has the same name as
1277 -- another formal subprogram of the generic, then
1278 -- a named association is illegal (12.3(9)). Exclude
1279 -- named associations that are generated for a nested
1280 -- instance.
1282 if Present (Match)
1283 and then Is_Named_Assoc
1284 and then Comes_From_Source (Found_Assoc)
1285 then
1286 Temp_Formal := First (Formals);
1287 while Present (Temp_Formal) loop
1288 if Nkind (Temp_Formal) in
1289 N_Formal_Subprogram_Declaration
1290 and then Temp_Formal /= Formal
1291 and then
1292 Chars (Selector_Name (Found_Assoc)) =
1293 Chars (Defining_Unit_Name
1294 (Specification (Temp_Formal)))
1295 then
1296 Error_Msg_N
1297 ("name not allowed for overloaded formal",
1298 Found_Assoc);
1299 Abandon_Instantiation (Instantiation_Node);
1300 end if;
1302 Next (Temp_Formal);
1303 end loop;
1304 end if;
1306 -- If there is no corresponding actual, this may be case of
1307 -- partial parametrization, or else the formal has a default
1308 -- or a box.
1310 if No (Match)
1311 and then Partial_Parametrization
1312 then
1313 Process_Default (Formal);
1314 else
1315 Append_To (Assoc,
1316 Instantiate_Formal_Subprogram
1317 (Formal, Match, Analyzed_Formal));
1318 end if;
1320 -- If this is a nested generic, preserve default for later
1321 -- instantiations.
1323 if No (Match)
1324 and then Box_Present (Formal)
1325 then
1326 Append_Elmt
1327 (Defining_Unit_Name (Specification (Last (Assoc))),
1328 Default_Actuals);
1329 end if;
1331 when N_Formal_Package_Declaration =>
1332 Match :=
1333 Matching_Actual (
1334 Defining_Identifier (Formal),
1335 Defining_Identifier (Original_Node (Analyzed_Formal)));
1337 if No (Match) then
1338 if Partial_Parametrization then
1339 Process_Default (Formal);
1341 else
1342 Error_Msg_Sloc := Sloc (Gen_Unit);
1343 Error_Msg_NE
1344 ("missing actual&",
1345 Instantiation_Node, Defining_Identifier (Formal));
1346 Error_Msg_NE ("\in instantiation of & declared#",
1347 Instantiation_Node, Gen_Unit);
1349 Abandon_Instantiation (Instantiation_Node);
1350 end if;
1352 else
1353 Analyze (Match);
1354 Append_List
1355 (Instantiate_Formal_Package
1356 (Formal, Match, Analyzed_Formal),
1357 Assoc);
1358 end if;
1360 -- For use type and use package appearing in the generic part,
1361 -- we have already copied them, so we can just move them where
1362 -- they belong (we mustn't recopy them since this would mess up
1363 -- the Sloc values).
1365 when N_Use_Package_Clause |
1366 N_Use_Type_Clause =>
1367 if Nkind (Original_Node (I_Node)) =
1368 N_Formal_Package_Declaration
1369 then
1370 Append (New_Copy_Tree (Formal), Assoc);
1371 else
1372 Remove (Formal);
1373 Append (Formal, Assoc);
1374 end if;
1376 when others =>
1377 raise Program_Error;
1379 end case;
1381 Formal := Next_Formal;
1382 Next_Non_Pragma (Analyzed_Formal);
1383 end loop;
1385 if Num_Actuals > Num_Matched then
1386 Error_Msg_Sloc := Sloc (Gen_Unit);
1388 if Present (Selector_Name (Actual)) then
1389 Error_Msg_NE
1390 ("unmatched actual&",
1391 Actual, Selector_Name (Actual));
1392 Error_Msg_NE ("\in instantiation of& declared#",
1393 Actual, Gen_Unit);
1394 else
1395 Error_Msg_NE
1396 ("unmatched actual in instantiation of& declared#",
1397 Actual, Gen_Unit);
1398 end if;
1399 end if;
1401 elsif Present (Actuals) then
1402 Error_Msg_N
1403 ("too many actuals in generic instantiation", Instantiation_Node);
1404 end if;
1406 declare
1407 Elmt : Elmt_Id := First_Elmt (Actual_Types);
1409 begin
1410 while Present (Elmt) loop
1411 Freeze_Before (I_Node, Node (Elmt));
1412 Next_Elmt (Elmt);
1413 end loop;
1414 end;
1416 -- If there are default subprograms, normalize the tree by adding
1417 -- explicit associations for them. This is required if the instance
1418 -- appears within a generic.
1420 declare
1421 Elmt : Elmt_Id;
1422 Subp : Entity_Id;
1423 New_D : Node_Id;
1425 begin
1426 Elmt := First_Elmt (Default_Actuals);
1427 while Present (Elmt) loop
1428 if No (Actuals) then
1429 Actuals := New_List;
1430 Set_Generic_Associations (I_Node, Actuals);
1431 end if;
1433 Subp := Node (Elmt);
1434 New_D :=
1435 Make_Generic_Association (Sloc (Subp),
1436 Selector_Name => New_Occurrence_Of (Subp, Sloc (Subp)),
1437 Explicit_Generic_Actual_Parameter =>
1438 New_Occurrence_Of (Subp, Sloc (Subp)));
1439 Mark_Rewrite_Insertion (New_D);
1440 Append_To (Actuals, New_D);
1441 Next_Elmt (Elmt);
1442 end loop;
1443 end;
1445 -- If this is a formal package, normalize the parameter list by adding
1446 -- explicit box associations for the formals that are covered by an
1447 -- Others_Choice.
1449 if not Is_Empty_List (Default_Formals) then
1450 Append_List (Default_Formals, Formals);
1451 end if;
1453 return Assoc;
1454 end Analyze_Associations;
1456 -------------------------------
1457 -- Analyze_Formal_Array_Type --
1458 -------------------------------
1460 procedure Analyze_Formal_Array_Type
1461 (T : in out Entity_Id;
1462 Def : Node_Id)
1464 DSS : Node_Id;
1466 begin
1467 -- Treated like a non-generic array declaration, with additional
1468 -- semantic checks.
1470 Enter_Name (T);
1472 if Nkind (Def) = N_Constrained_Array_Definition then
1473 DSS := First (Discrete_Subtype_Definitions (Def));
1474 while Present (DSS) loop
1475 if Nkind_In (DSS, N_Subtype_Indication,
1476 N_Range,
1477 N_Attribute_Reference)
1478 then
1479 Error_Msg_N ("only a subtype mark is allowed in a formal", DSS);
1480 end if;
1482 Next (DSS);
1483 end loop;
1484 end if;
1486 Array_Type_Declaration (T, Def);
1487 Set_Is_Generic_Type (Base_Type (T));
1489 if Ekind (Component_Type (T)) = E_Incomplete_Type
1490 and then No (Full_View (Component_Type (T)))
1491 then
1492 Error_Msg_N ("premature usage of incomplete type", Def);
1494 -- Check that range constraint is not allowed on the component type
1495 -- of a generic formal array type (AARM 12.5.3(3))
1497 elsif Is_Internal (Component_Type (T))
1498 and then Present (Subtype_Indication (Component_Definition (Def)))
1499 and then Nkind (Original_Node
1500 (Subtype_Indication (Component_Definition (Def)))) =
1501 N_Subtype_Indication
1502 then
1503 Error_Msg_N
1504 ("in a formal, a subtype indication can only be "
1505 & "a subtype mark (RM 12.5.3(3))",
1506 Subtype_Indication (Component_Definition (Def)));
1507 end if;
1509 end Analyze_Formal_Array_Type;
1511 ---------------------------------------------
1512 -- Analyze_Formal_Decimal_Fixed_Point_Type --
1513 ---------------------------------------------
1515 -- As for other generic types, we create a valid type representation with
1516 -- legal but arbitrary attributes, whose values are never considered
1517 -- static. For all scalar types we introduce an anonymous base type, with
1518 -- the same attributes. We choose the corresponding integer type to be
1519 -- Standard_Integer.
1521 procedure Analyze_Formal_Decimal_Fixed_Point_Type
1522 (T : Entity_Id;
1523 Def : Node_Id)
1525 Loc : constant Source_Ptr := Sloc (Def);
1526 Base : constant Entity_Id :=
1527 New_Internal_Entity
1528 (E_Decimal_Fixed_Point_Type,
1529 Current_Scope, Sloc (Def), 'G');
1530 Int_Base : constant Entity_Id := Standard_Integer;
1531 Delta_Val : constant Ureal := Ureal_1;
1532 Digs_Val : constant Uint := Uint_6;
1534 begin
1535 Enter_Name (T);
1537 Set_Etype (Base, Base);
1538 Set_Size_Info (Base, Int_Base);
1539 Set_RM_Size (Base, RM_Size (Int_Base));
1540 Set_First_Rep_Item (Base, First_Rep_Item (Int_Base));
1541 Set_Digits_Value (Base, Digs_Val);
1542 Set_Delta_Value (Base, Delta_Val);
1543 Set_Small_Value (Base, Delta_Val);
1544 Set_Scalar_Range (Base,
1545 Make_Range (Loc,
1546 Low_Bound => Make_Real_Literal (Loc, Ureal_1),
1547 High_Bound => Make_Real_Literal (Loc, Ureal_1)));
1549 Set_Is_Generic_Type (Base);
1550 Set_Parent (Base, Parent (Def));
1552 Set_Ekind (T, E_Decimal_Fixed_Point_Subtype);
1553 Set_Etype (T, Base);
1554 Set_Size_Info (T, Int_Base);
1555 Set_RM_Size (T, RM_Size (Int_Base));
1556 Set_First_Rep_Item (T, First_Rep_Item (Int_Base));
1557 Set_Digits_Value (T, Digs_Val);
1558 Set_Delta_Value (T, Delta_Val);
1559 Set_Small_Value (T, Delta_Val);
1560 Set_Scalar_Range (T, Scalar_Range (Base));
1561 Set_Is_Constrained (T);
1563 Check_Restriction (No_Fixed_Point, Def);
1564 end Analyze_Formal_Decimal_Fixed_Point_Type;
1566 -------------------------------------------
1567 -- Analyze_Formal_Derived_Interface_Type --
1568 -------------------------------------------
1570 procedure Analyze_Formal_Derived_Interface_Type
1571 (N : Node_Id;
1572 T : Entity_Id;
1573 Def : Node_Id)
1575 Loc : constant Source_Ptr := Sloc (Def);
1577 begin
1578 -- Rewrite as a type declaration of a derived type. This ensures that
1579 -- the interface list and primitive operations are properly captured.
1581 Rewrite (N,
1582 Make_Full_Type_Declaration (Loc,
1583 Defining_Identifier => T,
1584 Type_Definition => Def));
1585 Analyze (N);
1586 Set_Is_Generic_Type (T);
1587 end Analyze_Formal_Derived_Interface_Type;
1589 ---------------------------------
1590 -- Analyze_Formal_Derived_Type --
1591 ---------------------------------
1593 procedure Analyze_Formal_Derived_Type
1594 (N : Node_Id;
1595 T : Entity_Id;
1596 Def : Node_Id)
1598 Loc : constant Source_Ptr := Sloc (Def);
1599 Unk_Disc : constant Boolean := Unknown_Discriminants_Present (N);
1600 New_N : Node_Id;
1602 begin
1603 Set_Is_Generic_Type (T);
1605 if Private_Present (Def) then
1606 New_N :=
1607 Make_Private_Extension_Declaration (Loc,
1608 Defining_Identifier => T,
1609 Discriminant_Specifications => Discriminant_Specifications (N),
1610 Unknown_Discriminants_Present => Unk_Disc,
1611 Subtype_Indication => Subtype_Mark (Def),
1612 Interface_List => Interface_List (Def));
1614 Set_Abstract_Present (New_N, Abstract_Present (Def));
1615 Set_Limited_Present (New_N, Limited_Present (Def));
1616 Set_Synchronized_Present (New_N, Synchronized_Present (Def));
1618 else
1619 New_N :=
1620 Make_Full_Type_Declaration (Loc,
1621 Defining_Identifier => T,
1622 Discriminant_Specifications =>
1623 Discriminant_Specifications (Parent (T)),
1624 Type_Definition =>
1625 Make_Derived_Type_Definition (Loc,
1626 Subtype_Indication => Subtype_Mark (Def)));
1628 Set_Abstract_Present
1629 (Type_Definition (New_N), Abstract_Present (Def));
1630 Set_Limited_Present
1631 (Type_Definition (New_N), Limited_Present (Def));
1632 end if;
1634 Rewrite (N, New_N);
1635 Analyze (N);
1637 if Unk_Disc then
1638 if not Is_Composite_Type (T) then
1639 Error_Msg_N
1640 ("unknown discriminants not allowed for elementary types", N);
1641 else
1642 Set_Has_Unknown_Discriminants (T);
1643 Set_Is_Constrained (T, False);
1644 end if;
1645 end if;
1647 -- If the parent type has a known size, so does the formal, which makes
1648 -- legal representation clauses that involve the formal.
1650 Set_Size_Known_At_Compile_Time
1651 (T, Size_Known_At_Compile_Time (Entity (Subtype_Mark (Def))));
1652 end Analyze_Formal_Derived_Type;
1654 ----------------------------------
1655 -- Analyze_Formal_Discrete_Type --
1656 ----------------------------------
1658 -- The operations defined for a discrete types are those of an enumeration
1659 -- type. The size is set to an arbitrary value, for use in analyzing the
1660 -- generic unit.
1662 procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id) is
1663 Loc : constant Source_Ptr := Sloc (Def);
1664 Lo : Node_Id;
1665 Hi : Node_Id;
1667 Base : constant Entity_Id :=
1668 New_Internal_Entity
1669 (E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G');
1670 begin
1671 Enter_Name (T);
1672 Set_Ekind (T, E_Enumeration_Subtype);
1673 Set_Etype (T, Base);
1674 Init_Size (T, 8);
1675 Init_Alignment (T);
1676 Set_Is_Generic_Type (T);
1677 Set_Is_Constrained (T);
1679 -- For semantic analysis, the bounds of the type must be set to some
1680 -- non-static value. The simplest is to create attribute nodes for those
1681 -- bounds, that refer to the type itself. These bounds are never
1682 -- analyzed but serve as place-holders.
1684 Lo :=
1685 Make_Attribute_Reference (Loc,
1686 Attribute_Name => Name_First,
1687 Prefix => New_Reference_To (T, Loc));
1688 Set_Etype (Lo, T);
1690 Hi :=
1691 Make_Attribute_Reference (Loc,
1692 Attribute_Name => Name_Last,
1693 Prefix => New_Reference_To (T, Loc));
1694 Set_Etype (Hi, T);
1696 Set_Scalar_Range (T,
1697 Make_Range (Loc,
1698 Low_Bound => Lo,
1699 High_Bound => Hi));
1701 Set_Ekind (Base, E_Enumeration_Type);
1702 Set_Etype (Base, Base);
1703 Init_Size (Base, 8);
1704 Init_Alignment (Base);
1705 Set_Is_Generic_Type (Base);
1706 Set_Scalar_Range (Base, Scalar_Range (T));
1707 Set_Parent (Base, Parent (Def));
1708 end Analyze_Formal_Discrete_Type;
1710 ----------------------------------
1711 -- Analyze_Formal_Floating_Type --
1712 ---------------------------------
1714 procedure Analyze_Formal_Floating_Type (T : Entity_Id; Def : Node_Id) is
1715 Base : constant Entity_Id :=
1716 New_Internal_Entity
1717 (E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G');
1719 begin
1720 -- The various semantic attributes are taken from the predefined type
1721 -- Float, just so that all of them are initialized. Their values are
1722 -- never used because no constant folding or expansion takes place in
1723 -- the generic itself.
1725 Enter_Name (T);
1726 Set_Ekind (T, E_Floating_Point_Subtype);
1727 Set_Etype (T, Base);
1728 Set_Size_Info (T, (Standard_Float));
1729 Set_RM_Size (T, RM_Size (Standard_Float));
1730 Set_Digits_Value (T, Digits_Value (Standard_Float));
1731 Set_Scalar_Range (T, Scalar_Range (Standard_Float));
1732 Set_Is_Constrained (T);
1734 Set_Is_Generic_Type (Base);
1735 Set_Etype (Base, Base);
1736 Set_Size_Info (Base, (Standard_Float));
1737 Set_RM_Size (Base, RM_Size (Standard_Float));
1738 Set_Digits_Value (Base, Digits_Value (Standard_Float));
1739 Set_Scalar_Range (Base, Scalar_Range (Standard_Float));
1740 Set_Parent (Base, Parent (Def));
1742 Check_Restriction (No_Floating_Point, Def);
1743 end Analyze_Formal_Floating_Type;
1745 -----------------------------------
1746 -- Analyze_Formal_Interface_Type;--
1747 -----------------------------------
1749 procedure Analyze_Formal_Interface_Type
1750 (N : Node_Id;
1751 T : Entity_Id;
1752 Def : Node_Id)
1754 Loc : constant Source_Ptr := Sloc (N);
1755 New_N : Node_Id;
1757 begin
1758 New_N :=
1759 Make_Full_Type_Declaration (Loc,
1760 Defining_Identifier => T,
1761 Type_Definition => Def);
1763 Rewrite (N, New_N);
1764 Analyze (N);
1765 Set_Is_Generic_Type (T);
1766 end Analyze_Formal_Interface_Type;
1768 ---------------------------------
1769 -- Analyze_Formal_Modular_Type --
1770 ---------------------------------
1772 procedure Analyze_Formal_Modular_Type (T : Entity_Id; Def : Node_Id) is
1773 begin
1774 -- Apart from their entity kind, generic modular types are treated like
1775 -- signed integer types, and have the same attributes.
1777 Analyze_Formal_Signed_Integer_Type (T, Def);
1778 Set_Ekind (T, E_Modular_Integer_Subtype);
1779 Set_Ekind (Etype (T), E_Modular_Integer_Type);
1781 end Analyze_Formal_Modular_Type;
1783 ---------------------------------------
1784 -- Analyze_Formal_Object_Declaration --
1785 ---------------------------------------
1787 procedure Analyze_Formal_Object_Declaration (N : Node_Id) is
1788 E : constant Node_Id := Default_Expression (N);
1789 Id : constant Node_Id := Defining_Identifier (N);
1790 K : Entity_Kind;
1791 T : Node_Id;
1793 begin
1794 Enter_Name (Id);
1796 -- Determine the mode of the formal object
1798 if Out_Present (N) then
1799 K := E_Generic_In_Out_Parameter;
1801 if not In_Present (N) then
1802 Error_Msg_N ("formal generic objects cannot have mode OUT", N);
1803 end if;
1805 else
1806 K := E_Generic_In_Parameter;
1807 end if;
1809 if Present (Subtype_Mark (N)) then
1810 Find_Type (Subtype_Mark (N));
1811 T := Entity (Subtype_Mark (N));
1813 -- Ada 2005 (AI-423): Formal object with an access definition
1815 else
1816 Check_Access_Definition (N);
1817 T := Access_Definition
1818 (Related_Nod => N,
1819 N => Access_Definition (N));
1820 end if;
1822 if Ekind (T) = E_Incomplete_Type then
1823 declare
1824 Error_Node : Node_Id;
1826 begin
1827 if Present (Subtype_Mark (N)) then
1828 Error_Node := Subtype_Mark (N);
1829 else
1830 Check_Access_Definition (N);
1831 Error_Node := Access_Definition (N);
1832 end if;
1834 Error_Msg_N ("premature usage of incomplete type", Error_Node);
1835 end;
1836 end if;
1838 if K = E_Generic_In_Parameter then
1840 -- Ada 2005 (AI-287): Limited aggregates allowed in generic formals
1842 if Ada_Version < Ada_05 and then Is_Limited_Type (T) then
1843 Error_Msg_N
1844 ("generic formal of mode IN must not be of limited type", N);
1845 Explain_Limited_Type (T, N);
1846 end if;
1848 if Is_Abstract_Type (T) then
1849 Error_Msg_N
1850 ("generic formal of mode IN must not be of abstract type", N);
1851 end if;
1853 if Present (E) then
1854 Preanalyze_Spec_Expression (E, T);
1856 if Is_Limited_Type (T) and then not OK_For_Limited_Init (E) then
1857 Error_Msg_N
1858 ("initialization not allowed for limited types", E);
1859 Explain_Limited_Type (T, E);
1860 end if;
1861 end if;
1863 Set_Ekind (Id, K);
1864 Set_Etype (Id, T);
1866 -- Case of generic IN OUT parameter
1868 else
1869 -- If the formal has an unconstrained type, construct its actual
1870 -- subtype, as is done for subprogram formals. In this fashion, all
1871 -- its uses can refer to specific bounds.
1873 Set_Ekind (Id, K);
1874 Set_Etype (Id, T);
1876 if (Is_Array_Type (T)
1877 and then not Is_Constrained (T))
1878 or else
1879 (Ekind (T) = E_Record_Type
1880 and then Has_Discriminants (T))
1881 then
1882 declare
1883 Non_Freezing_Ref : constant Node_Id :=
1884 New_Reference_To (Id, Sloc (Id));
1885 Decl : Node_Id;
1887 begin
1888 -- Make sure the actual subtype doesn't generate bogus freezing
1890 Set_Must_Not_Freeze (Non_Freezing_Ref);
1891 Decl := Build_Actual_Subtype (T, Non_Freezing_Ref);
1892 Insert_Before_And_Analyze (N, Decl);
1893 Set_Actual_Subtype (Id, Defining_Identifier (Decl));
1894 end;
1895 else
1896 Set_Actual_Subtype (Id, T);
1897 end if;
1899 if Present (E) then
1900 Error_Msg_N
1901 ("initialization not allowed for `IN OUT` formals", N);
1902 end if;
1903 end if;
1905 end Analyze_Formal_Object_Declaration;
1907 ----------------------------------------------
1908 -- Analyze_Formal_Ordinary_Fixed_Point_Type --
1909 ----------------------------------------------
1911 procedure Analyze_Formal_Ordinary_Fixed_Point_Type
1912 (T : Entity_Id;
1913 Def : Node_Id)
1915 Loc : constant Source_Ptr := Sloc (Def);
1916 Base : constant Entity_Id :=
1917 New_Internal_Entity
1918 (E_Ordinary_Fixed_Point_Type, Current_Scope, Sloc (Def), 'G');
1919 begin
1920 -- The semantic attributes are set for completeness only, their values
1921 -- will never be used, since all properties of the type are non-static.
1923 Enter_Name (T);
1924 Set_Ekind (T, E_Ordinary_Fixed_Point_Subtype);
1925 Set_Etype (T, Base);
1926 Set_Size_Info (T, Standard_Integer);
1927 Set_RM_Size (T, RM_Size (Standard_Integer));
1928 Set_Small_Value (T, Ureal_1);
1929 Set_Delta_Value (T, Ureal_1);
1930 Set_Scalar_Range (T,
1931 Make_Range (Loc,
1932 Low_Bound => Make_Real_Literal (Loc, Ureal_1),
1933 High_Bound => Make_Real_Literal (Loc, Ureal_1)));
1934 Set_Is_Constrained (T);
1936 Set_Is_Generic_Type (Base);
1937 Set_Etype (Base, Base);
1938 Set_Size_Info (Base, Standard_Integer);
1939 Set_RM_Size (Base, RM_Size (Standard_Integer));
1940 Set_Small_Value (Base, Ureal_1);
1941 Set_Delta_Value (Base, Ureal_1);
1942 Set_Scalar_Range (Base, Scalar_Range (T));
1943 Set_Parent (Base, Parent (Def));
1945 Check_Restriction (No_Fixed_Point, Def);
1946 end Analyze_Formal_Ordinary_Fixed_Point_Type;
1948 ----------------------------
1949 -- Analyze_Formal_Package --
1950 ----------------------------
1952 procedure Analyze_Formal_Package (N : Node_Id) is
1953 Loc : constant Source_Ptr := Sloc (N);
1954 Pack_Id : constant Entity_Id := Defining_Identifier (N);
1955 Formal : Entity_Id;
1956 Gen_Id : constant Node_Id := Name (N);
1957 Gen_Decl : Node_Id;
1958 Gen_Unit : Entity_Id;
1959 New_N : Node_Id;
1960 Parent_Installed : Boolean := False;
1961 Renaming : Node_Id;
1962 Parent_Instance : Entity_Id;
1963 Renaming_In_Par : Entity_Id;
1964 No_Associations : Boolean := False;
1966 function Build_Local_Package return Node_Id;
1967 -- The formal package is rewritten so that its parameters are replaced
1968 -- with corresponding declarations. For parameters with bona fide
1969 -- associations these declarations are created by Analyze_Associations
1970 -- as for a regular instantiation. For boxed parameters, we preserve
1971 -- the formal declarations and analyze them, in order to introduce
1972 -- entities of the right kind in the environment of the formal.
1974 -------------------------
1975 -- Build_Local_Package --
1976 -------------------------
1978 function Build_Local_Package return Node_Id is
1979 Decls : List_Id;
1980 Pack_Decl : Node_Id;
1982 begin
1983 -- Within the formal, the name of the generic package is a renaming
1984 -- of the formal (as for a regular instantiation).
1986 Pack_Decl :=
1987 Make_Package_Declaration (Loc,
1988 Specification =>
1989 Copy_Generic_Node
1990 (Specification (Original_Node (Gen_Decl)),
1991 Empty, Instantiating => True));
1993 Renaming := Make_Package_Renaming_Declaration (Loc,
1994 Defining_Unit_Name =>
1995 Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
1996 Name => New_Occurrence_Of (Formal, Loc));
1998 if Nkind (Gen_Id) = N_Identifier
1999 and then Chars (Gen_Id) = Chars (Pack_Id)
2000 then
2001 Error_Msg_NE
2002 ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
2003 end if;
2005 -- If the formal is declared with a box, or with an others choice,
2006 -- create corresponding declarations for all entities in the formal
2007 -- part, so that names with the proper types are available in the
2008 -- specification of the formal package.
2009 -- On the other hand, if there are no associations, then all the
2010 -- formals must have defaults, and this will be checked by the
2011 -- call to Analyze_Associations.
2013 if Box_Present (N)
2014 or else Nkind (First (Generic_Associations (N))) = N_Others_Choice
2015 then
2016 declare
2017 Formal_Decl : Node_Id;
2019 begin
2020 -- TBA : for a formal package, need to recurse ???
2022 Decls := New_List;
2023 Formal_Decl :=
2024 First
2025 (Generic_Formal_Declarations (Original_Node (Gen_Decl)));
2026 while Present (Formal_Decl) loop
2027 Append_To
2028 (Decls, Copy_Generic_Node (Formal_Decl, Empty, True));
2029 Next (Formal_Decl);
2030 end loop;
2031 end;
2033 -- If generic associations are present, use Analyze_Associations to
2034 -- create the proper renaming declarations.
2036 else
2037 declare
2038 Act_Tree : constant Node_Id :=
2039 Copy_Generic_Node
2040 (Original_Node (Gen_Decl), Empty,
2041 Instantiating => True);
2043 begin
2044 Generic_Renamings.Set_Last (0);
2045 Generic_Renamings_HTable.Reset;
2046 Instantiation_Node := N;
2048 Decls :=
2049 Analyze_Associations
2050 (Original_Node (N),
2051 Generic_Formal_Declarations (Act_Tree),
2052 Generic_Formal_Declarations (Gen_Decl));
2053 end;
2054 end if;
2056 Append (Renaming, To => Decls);
2058 -- Add generated declarations ahead of local declarations in
2059 -- the package.
2061 if No (Visible_Declarations (Specification (Pack_Decl))) then
2062 Set_Visible_Declarations (Specification (Pack_Decl), Decls);
2063 else
2064 Insert_List_Before
2065 (First (Visible_Declarations (Specification (Pack_Decl))),
2066 Decls);
2067 end if;
2069 return Pack_Decl;
2070 end Build_Local_Package;
2072 -- Start of processing for Analyze_Formal_Package
2074 begin
2075 Text_IO_Kludge (Gen_Id);
2077 Init_Env;
2078 Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
2079 Gen_Unit := Entity (Gen_Id);
2081 -- Check for a formal package that is a package renaming
2083 if Present (Renamed_Object (Gen_Unit)) then
2084 Gen_Unit := Renamed_Object (Gen_Unit);
2085 end if;
2087 if Ekind (Gen_Unit) /= E_Generic_Package then
2088 Error_Msg_N ("expect generic package name", Gen_Id);
2089 Restore_Env;
2090 return;
2092 elsif Gen_Unit = Current_Scope then
2093 Error_Msg_N
2094 ("generic package cannot be used as a formal package of itself",
2095 Gen_Id);
2096 Restore_Env;
2097 return;
2099 elsif In_Open_Scopes (Gen_Unit) then
2100 if Is_Compilation_Unit (Gen_Unit)
2101 and then Is_Child_Unit (Current_Scope)
2102 then
2103 -- Special-case the error when the formal is a parent, and
2104 -- continue analysis to minimize cascaded errors.
2106 Error_Msg_N
2107 ("generic parent cannot be used as formal package "
2108 & "of a child unit",
2109 Gen_Id);
2111 else
2112 Error_Msg_N
2113 ("generic package cannot be used as a formal package "
2114 & "within itself",
2115 Gen_Id);
2116 Restore_Env;
2117 return;
2118 end if;
2119 end if;
2121 if Box_Present (N)
2122 or else No (Generic_Associations (N))
2123 or else Nkind (First (Generic_Associations (N))) = N_Others_Choice
2124 then
2125 No_Associations := True;
2126 end if;
2128 -- If there are no generic associations, the generic parameters appear
2129 -- as local entities and are instantiated like them. We copy the generic
2130 -- package declaration as if it were an instantiation, and analyze it
2131 -- like a regular package, except that we treat the formals as
2132 -- additional visible components.
2134 Gen_Decl := Unit_Declaration_Node (Gen_Unit);
2136 if In_Extended_Main_Source_Unit (N) then
2137 Set_Is_Instantiated (Gen_Unit);
2138 Generate_Reference (Gen_Unit, N);
2139 end if;
2141 Formal := New_Copy (Pack_Id);
2142 Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
2144 begin
2145 -- Make local generic without formals. The formals will be replaced
2146 -- with internal declarations.
2148 New_N := Build_Local_Package;
2150 -- If there are errors in the parameter list, Analyze_Associations
2151 -- raises Instantiation_Error. Patch the declaration to prevent
2152 -- further exception propagation.
2154 exception
2155 when Instantiation_Error =>
2157 Enter_Name (Formal);
2158 Set_Ekind (Formal, E_Variable);
2159 Set_Etype (Formal, Any_Type);
2161 if Parent_Installed then
2162 Remove_Parent;
2163 end if;
2165 return;
2166 end;
2168 Rewrite (N, New_N);
2169 Set_Defining_Unit_Name (Specification (New_N), Formal);
2170 Set_Generic_Parent (Specification (N), Gen_Unit);
2171 Set_Instance_Env (Gen_Unit, Formal);
2172 Set_Is_Generic_Instance (Formal);
2174 Enter_Name (Formal);
2175 Set_Ekind (Formal, E_Package);
2176 Set_Etype (Formal, Standard_Void_Type);
2177 Set_Inner_Instances (Formal, New_Elmt_List);
2178 Push_Scope (Formal);
2180 if Is_Child_Unit (Gen_Unit)
2181 and then Parent_Installed
2182 then
2183 -- Similarly, we have to make the name of the formal visible in the
2184 -- parent instance, to resolve properly fully qualified names that
2185 -- may appear in the generic unit. The parent instance has been
2186 -- placed on the scope stack ahead of the current scope.
2188 Parent_Instance := Scope_Stack.Table (Scope_Stack.Last - 1).Entity;
2190 Renaming_In_Par :=
2191 Make_Defining_Identifier (Loc, Chars (Gen_Unit));
2192 Set_Ekind (Renaming_In_Par, E_Package);
2193 Set_Etype (Renaming_In_Par, Standard_Void_Type);
2194 Set_Scope (Renaming_In_Par, Parent_Instance);
2195 Set_Parent (Renaming_In_Par, Parent (Formal));
2196 Set_Renamed_Object (Renaming_In_Par, Formal);
2197 Append_Entity (Renaming_In_Par, Parent_Instance);
2198 end if;
2200 Analyze (Specification (N));
2202 -- The formals for which associations are provided are not visible
2203 -- outside of the formal package. The others are still declared by a
2204 -- formal parameter declaration.
2206 if not No_Associations then
2207 declare
2208 E : Entity_Id;
2210 begin
2211 E := First_Entity (Formal);
2212 while Present (E) loop
2213 exit when Ekind (E) = E_Package
2214 and then Renamed_Entity (E) = Formal;
2216 if not Is_Generic_Formal (E) then
2217 Set_Is_Hidden (E);
2218 end if;
2220 Next_Entity (E);
2221 end loop;
2222 end;
2223 end if;
2225 End_Package_Scope (Formal);
2227 if Parent_Installed then
2228 Remove_Parent;
2229 end if;
2231 Restore_Env;
2233 -- Inside the generic unit, the formal package is a regular package, but
2234 -- no body is needed for it. Note that after instantiation, the defining
2235 -- unit name we need is in the new tree and not in the original (see
2236 -- Package_Instantiation). A generic formal package is an instance, and
2237 -- can be used as an actual for an inner instance.
2239 Set_Has_Completion (Formal, True);
2241 -- Add semantic information to the original defining identifier.
2242 -- for ASIS use.
2244 Set_Ekind (Pack_Id, E_Package);
2245 Set_Etype (Pack_Id, Standard_Void_Type);
2246 Set_Scope (Pack_Id, Scope (Formal));
2247 Set_Has_Completion (Pack_Id, True);
2248 end Analyze_Formal_Package;
2250 ---------------------------------
2251 -- Analyze_Formal_Private_Type --
2252 ---------------------------------
2254 procedure Analyze_Formal_Private_Type
2255 (N : Node_Id;
2256 T : Entity_Id;
2257 Def : Node_Id)
2259 begin
2260 New_Private_Type (N, T, Def);
2262 -- Set the size to an arbitrary but legal value
2264 Set_Size_Info (T, Standard_Integer);
2265 Set_RM_Size (T, RM_Size (Standard_Integer));
2266 end Analyze_Formal_Private_Type;
2268 ----------------------------------------
2269 -- Analyze_Formal_Signed_Integer_Type --
2270 ----------------------------------------
2272 procedure Analyze_Formal_Signed_Integer_Type
2273 (T : Entity_Id;
2274 Def : Node_Id)
2276 Base : constant Entity_Id :=
2277 New_Internal_Entity
2278 (E_Signed_Integer_Type, Current_Scope, Sloc (Def), 'G');
2280 begin
2281 Enter_Name (T);
2283 Set_Ekind (T, E_Signed_Integer_Subtype);
2284 Set_Etype (T, Base);
2285 Set_Size_Info (T, Standard_Integer);
2286 Set_RM_Size (T, RM_Size (Standard_Integer));
2287 Set_Scalar_Range (T, Scalar_Range (Standard_Integer));
2288 Set_Is_Constrained (T);
2290 Set_Is_Generic_Type (Base);
2291 Set_Size_Info (Base, Standard_Integer);
2292 Set_RM_Size (Base, RM_Size (Standard_Integer));
2293 Set_Etype (Base, Base);
2294 Set_Scalar_Range (Base, Scalar_Range (Standard_Integer));
2295 Set_Parent (Base, Parent (Def));
2296 end Analyze_Formal_Signed_Integer_Type;
2298 -------------------------------
2299 -- Analyze_Formal_Subprogram --
2300 -------------------------------
2302 procedure Analyze_Formal_Subprogram (N : Node_Id) is
2303 Spec : constant Node_Id := Specification (N);
2304 Def : constant Node_Id := Default_Name (N);
2305 Nam : constant Entity_Id := Defining_Unit_Name (Spec);
2306 Subp : Entity_Id;
2308 begin
2309 if Nam = Error then
2310 return;
2311 end if;
2313 if Nkind (Nam) = N_Defining_Program_Unit_Name then
2314 Error_Msg_N ("name of formal subprogram must be a direct name", Nam);
2315 return;
2316 end if;
2318 Analyze_Subprogram_Declaration (N);
2319 Set_Is_Formal_Subprogram (Nam);
2320 Set_Has_Completion (Nam);
2322 if Nkind (N) = N_Formal_Abstract_Subprogram_Declaration then
2323 Set_Is_Abstract_Subprogram (Nam);
2324 Set_Is_Dispatching_Operation (Nam);
2326 declare
2327 Ctrl_Type : constant Entity_Id := Find_Dispatching_Type (Nam);
2328 begin
2329 if No (Ctrl_Type) then
2330 Error_Msg_N
2331 ("abstract formal subprogram must have a controlling type",
2333 else
2334 Check_Controlling_Formals (Ctrl_Type, Nam);
2335 end if;
2336 end;
2337 end if;
2339 -- Default name is resolved at the point of instantiation
2341 if Box_Present (N) then
2342 null;
2344 -- Else default is bound at the point of generic declaration
2346 elsif Present (Def) then
2347 if Nkind (Def) = N_Operator_Symbol then
2348 Find_Direct_Name (Def);
2350 elsif Nkind (Def) /= N_Attribute_Reference then
2351 Analyze (Def);
2353 else
2354 -- For an attribute reference, analyze the prefix and verify
2355 -- that it has the proper profile for the subprogram.
2357 Analyze (Prefix (Def));
2358 Valid_Default_Attribute (Nam, Def);
2359 return;
2360 end if;
2362 -- Default name may be overloaded, in which case the interpretation
2363 -- with the correct profile must be selected, as for a renaming.
2364 -- If the definition is an indexed component, it must denote a
2365 -- member of an entry family. If it is a selected component, it
2366 -- can be a protected operation.
2368 if Etype (Def) = Any_Type then
2369 return;
2371 elsif Nkind (Def) = N_Selected_Component then
2372 if not Is_Overloadable (Entity (Selector_Name (Def))) then
2373 Error_Msg_N ("expect valid subprogram name as default", Def);
2374 end if;
2376 elsif Nkind (Def) = N_Indexed_Component then
2377 if Is_Entity_Name (Prefix (Def)) then
2378 if Ekind (Entity (Prefix (Def))) /= E_Entry_Family then
2379 Error_Msg_N ("expect valid subprogram name as default", Def);
2380 end if;
2382 elsif Nkind (Prefix (Def)) = N_Selected_Component then
2383 if Ekind (Entity (Selector_Name (Prefix (Def))))
2384 /= E_Entry_Family
2385 then
2386 Error_Msg_N ("expect valid subprogram name as default", Def);
2387 end if;
2389 else
2390 Error_Msg_N ("expect valid subprogram name as default", Def);
2391 return;
2392 end if;
2394 elsif Nkind (Def) = N_Character_Literal then
2396 -- Needs some type checks: subprogram should be parameterless???
2398 Resolve (Def, (Etype (Nam)));
2400 elsif not Is_Entity_Name (Def)
2401 or else not Is_Overloadable (Entity (Def))
2402 then
2403 Error_Msg_N ("expect valid subprogram name as default", Def);
2404 return;
2406 elsif not Is_Overloaded (Def) then
2407 Subp := Entity (Def);
2409 if Subp = Nam then
2410 Error_Msg_N ("premature usage of formal subprogram", Def);
2412 elsif not Entity_Matches_Spec (Subp, Nam) then
2413 Error_Msg_N ("no visible entity matches specification", Def);
2414 end if;
2416 else
2418 -- Several interpretations. Disambiguate as for a renaming.
2420 declare
2421 I : Interp_Index;
2422 I1 : Interp_Index := 0;
2423 It : Interp;
2424 It1 : Interp;
2426 begin
2427 Subp := Any_Id;
2428 Get_First_Interp (Def, I, It);
2429 while Present (It.Nam) loop
2431 if Entity_Matches_Spec (It.Nam, Nam) then
2432 if Subp /= Any_Id then
2433 It1 := Disambiguate (Def, I1, I, Etype (Subp));
2435 if It1 = No_Interp then
2436 Error_Msg_N ("ambiguous default subprogram", Def);
2437 else
2438 Subp := It1.Nam;
2439 end if;
2441 exit;
2443 else
2444 I1 := I;
2445 Subp := It.Nam;
2446 end if;
2447 end if;
2449 Get_Next_Interp (I, It);
2450 end loop;
2451 end;
2453 if Subp /= Any_Id then
2454 Set_Entity (Def, Subp);
2456 if Subp = Nam then
2457 Error_Msg_N ("premature usage of formal subprogram", Def);
2459 elsif Ekind (Subp) /= E_Operator then
2460 Check_Mode_Conformant (Subp, Nam);
2461 end if;
2463 else
2464 Error_Msg_N ("no visible subprogram matches specification", N);
2465 end if;
2466 end if;
2467 end if;
2468 end Analyze_Formal_Subprogram;
2470 -------------------------------------
2471 -- Analyze_Formal_Type_Declaration --
2472 -------------------------------------
2474 procedure Analyze_Formal_Type_Declaration (N : Node_Id) is
2475 Def : constant Node_Id := Formal_Type_Definition (N);
2476 T : Entity_Id;
2478 begin
2479 T := Defining_Identifier (N);
2481 if Present (Discriminant_Specifications (N))
2482 and then Nkind (Def) /= N_Formal_Private_Type_Definition
2483 then
2484 Error_Msg_N
2485 ("discriminants not allowed for this formal type", T);
2486 end if;
2488 -- Enter the new name, and branch to specific routine
2490 case Nkind (Def) is
2491 when N_Formal_Private_Type_Definition =>
2492 Analyze_Formal_Private_Type (N, T, Def);
2494 when N_Formal_Derived_Type_Definition =>
2495 Analyze_Formal_Derived_Type (N, T, Def);
2497 when N_Formal_Discrete_Type_Definition =>
2498 Analyze_Formal_Discrete_Type (T, Def);
2500 when N_Formal_Signed_Integer_Type_Definition =>
2501 Analyze_Formal_Signed_Integer_Type (T, Def);
2503 when N_Formal_Modular_Type_Definition =>
2504 Analyze_Formal_Modular_Type (T, Def);
2506 when N_Formal_Floating_Point_Definition =>
2507 Analyze_Formal_Floating_Type (T, Def);
2509 when N_Formal_Ordinary_Fixed_Point_Definition =>
2510 Analyze_Formal_Ordinary_Fixed_Point_Type (T, Def);
2512 when N_Formal_Decimal_Fixed_Point_Definition =>
2513 Analyze_Formal_Decimal_Fixed_Point_Type (T, Def);
2515 when N_Array_Type_Definition =>
2516 Analyze_Formal_Array_Type (T, Def);
2518 when N_Access_To_Object_Definition |
2519 N_Access_Function_Definition |
2520 N_Access_Procedure_Definition =>
2521 Analyze_Generic_Access_Type (T, Def);
2523 -- Ada 2005: a interface declaration is encoded as an abstract
2524 -- record declaration or a abstract type derivation.
2526 when N_Record_Definition =>
2527 Analyze_Formal_Interface_Type (N, T, Def);
2529 when N_Derived_Type_Definition =>
2530 Analyze_Formal_Derived_Interface_Type (N, T, Def);
2532 when N_Error =>
2533 null;
2535 when others =>
2536 raise Program_Error;
2538 end case;
2540 Set_Is_Generic_Type (T);
2541 end Analyze_Formal_Type_Declaration;
2543 ------------------------------------
2544 -- Analyze_Function_Instantiation --
2545 ------------------------------------
2547 procedure Analyze_Function_Instantiation (N : Node_Id) is
2548 begin
2549 Analyze_Subprogram_Instantiation (N, E_Function);
2550 end Analyze_Function_Instantiation;
2552 ---------------------------------
2553 -- Analyze_Generic_Access_Type --
2554 ---------------------------------
2556 procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id) is
2557 begin
2558 Enter_Name (T);
2560 if Nkind (Def) = N_Access_To_Object_Definition then
2561 Access_Type_Declaration (T, Def);
2563 if Is_Incomplete_Or_Private_Type (Designated_Type (T))
2564 and then No (Full_View (Designated_Type (T)))
2565 and then not Is_Generic_Type (Designated_Type (T))
2566 then
2567 Error_Msg_N ("premature usage of incomplete type", Def);
2569 elsif Is_Internal (Designated_Type (T)) then
2570 Error_Msg_N
2571 ("only a subtype mark is allowed in a formal", Def);
2572 end if;
2574 else
2575 Access_Subprogram_Declaration (T, Def);
2576 end if;
2577 end Analyze_Generic_Access_Type;
2579 ---------------------------------
2580 -- Analyze_Generic_Formal_Part --
2581 ---------------------------------
2583 procedure Analyze_Generic_Formal_Part (N : Node_Id) is
2584 Gen_Parm_Decl : Node_Id;
2586 begin
2587 -- The generic formals are processed in the scope of the generic unit,
2588 -- where they are immediately visible. The scope is installed by the
2589 -- caller.
2591 Gen_Parm_Decl := First (Generic_Formal_Declarations (N));
2593 while Present (Gen_Parm_Decl) loop
2594 Analyze (Gen_Parm_Decl);
2595 Next (Gen_Parm_Decl);
2596 end loop;
2598 Generate_Reference_To_Generic_Formals (Current_Scope);
2599 end Analyze_Generic_Formal_Part;
2601 ------------------------------------------
2602 -- Analyze_Generic_Package_Declaration --
2603 ------------------------------------------
2605 procedure Analyze_Generic_Package_Declaration (N : Node_Id) is
2606 Loc : constant Source_Ptr := Sloc (N);
2607 Id : Entity_Id;
2608 New_N : Node_Id;
2609 Save_Parent : Node_Id;
2610 Renaming : Node_Id;
2611 Decls : constant List_Id :=
2612 Visible_Declarations (Specification (N));
2613 Decl : Node_Id;
2615 begin
2616 -- We introduce a renaming of the enclosing package, to have a usable
2617 -- entity as the prefix of an expanded name for a local entity of the
2618 -- form Par.P.Q, where P is the generic package. This is because a local
2619 -- entity named P may hide it, so that the usual visibility rules in
2620 -- the instance will not resolve properly.
2622 Renaming :=
2623 Make_Package_Renaming_Declaration (Loc,
2624 Defining_Unit_Name =>
2625 Make_Defining_Identifier (Loc,
2626 Chars => New_External_Name (Chars (Defining_Entity (N)), "GH")),
2627 Name => Make_Identifier (Loc, Chars (Defining_Entity (N))));
2629 if Present (Decls) then
2630 Decl := First (Decls);
2631 while Present (Decl)
2632 and then Nkind (Decl) = N_Pragma
2633 loop
2634 Next (Decl);
2635 end loop;
2637 if Present (Decl) then
2638 Insert_Before (Decl, Renaming);
2639 else
2640 Append (Renaming, Visible_Declarations (Specification (N)));
2641 end if;
2643 else
2644 Set_Visible_Declarations (Specification (N), New_List (Renaming));
2645 end if;
2647 -- Create copy of generic unit, and save for instantiation. If the unit
2648 -- is a child unit, do not copy the specifications for the parent, which
2649 -- are not part of the generic tree.
2651 Save_Parent := Parent_Spec (N);
2652 Set_Parent_Spec (N, Empty);
2654 New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
2655 Set_Parent_Spec (New_N, Save_Parent);
2656 Rewrite (N, New_N);
2657 Id := Defining_Entity (N);
2658 Generate_Definition (Id);
2660 -- Expansion is not applied to generic units
2662 Start_Generic;
2664 Enter_Name (Id);
2665 Set_Ekind (Id, E_Generic_Package);
2666 Set_Etype (Id, Standard_Void_Type);
2667 Push_Scope (Id);
2668 Enter_Generic_Scope (Id);
2669 Set_Inner_Instances (Id, New_Elmt_List);
2671 Set_Categorization_From_Pragmas (N);
2672 Set_Is_Pure (Id, Is_Pure (Current_Scope));
2674 -- Link the declaration of the generic homonym in the generic copy to
2675 -- the package it renames, so that it is always resolved properly.
2677 Set_Generic_Homonym (Id, Defining_Unit_Name (Renaming));
2678 Set_Entity (Associated_Node (Name (Renaming)), Id);
2680 -- For a library unit, we have reconstructed the entity for the unit,
2681 -- and must reset it in the library tables.
2683 if Nkind (Parent (N)) = N_Compilation_Unit then
2684 Set_Cunit_Entity (Current_Sem_Unit, Id);
2685 end if;
2687 Analyze_Generic_Formal_Part (N);
2689 -- After processing the generic formals, analysis proceeds as for a
2690 -- non-generic package.
2692 Analyze (Specification (N));
2694 Validate_Categorization_Dependency (N, Id);
2696 End_Generic;
2698 End_Package_Scope (Id);
2699 Exit_Generic_Scope (Id);
2701 if Nkind (Parent (N)) /= N_Compilation_Unit then
2702 Move_Freeze_Nodes (Id, N, Visible_Declarations (Specification (N)));
2703 Move_Freeze_Nodes (Id, N, Private_Declarations (Specification (N)));
2704 Move_Freeze_Nodes (Id, N, Generic_Formal_Declarations (N));
2706 else
2707 Set_Body_Required (Parent (N), Unit_Requires_Body (Id));
2708 Validate_RT_RAT_Component (N);
2710 -- If this is a spec without a body, check that generic parameters
2711 -- are referenced.
2713 if not Body_Required (Parent (N)) then
2714 Check_References (Id);
2715 end if;
2716 end if;
2717 end Analyze_Generic_Package_Declaration;
2719 --------------------------------------------
2720 -- Analyze_Generic_Subprogram_Declaration --
2721 --------------------------------------------
2723 procedure Analyze_Generic_Subprogram_Declaration (N : Node_Id) is
2724 Spec : Node_Id;
2725 Id : Entity_Id;
2726 Formals : List_Id;
2727 New_N : Node_Id;
2728 Result_Type : Entity_Id;
2729 Save_Parent : Node_Id;
2731 begin
2732 -- Create copy of generic unit, and save for instantiation. If the unit
2733 -- is a child unit, do not copy the specifications for the parent, which
2734 -- are not part of the generic tree.
2736 Save_Parent := Parent_Spec (N);
2737 Set_Parent_Spec (N, Empty);
2739 New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
2740 Set_Parent_Spec (New_N, Save_Parent);
2741 Rewrite (N, New_N);
2743 Spec := Specification (N);
2744 Id := Defining_Entity (Spec);
2745 Generate_Definition (Id);
2747 if Nkind (Id) = N_Defining_Operator_Symbol then
2748 Error_Msg_N
2749 ("operator symbol not allowed for generic subprogram", Id);
2750 end if;
2752 Start_Generic;
2754 Enter_Name (Id);
2756 Set_Scope_Depth_Value (Id, Scope_Depth (Current_Scope) + 1);
2757 Push_Scope (Id);
2758 Enter_Generic_Scope (Id);
2759 Set_Inner_Instances (Id, New_Elmt_List);
2760 Set_Is_Pure (Id, Is_Pure (Current_Scope));
2762 Analyze_Generic_Formal_Part (N);
2764 Formals := Parameter_Specifications (Spec);
2766 if Present (Formals) then
2767 Process_Formals (Formals, Spec);
2768 end if;
2770 if Nkind (Spec) = N_Function_Specification then
2771 Set_Ekind (Id, E_Generic_Function);
2773 if Nkind (Result_Definition (Spec)) = N_Access_Definition then
2774 Result_Type := Access_Definition (Spec, Result_Definition (Spec));
2775 Set_Etype (Id, Result_Type);
2776 else
2777 Find_Type (Result_Definition (Spec));
2778 Set_Etype (Id, Entity (Result_Definition (Spec)));
2779 end if;
2781 else
2782 Set_Ekind (Id, E_Generic_Procedure);
2783 Set_Etype (Id, Standard_Void_Type);
2784 end if;
2786 -- For a library unit, we have reconstructed the entity for the unit,
2787 -- and must reset it in the library tables. We also make sure that
2788 -- Body_Required is set properly in the original compilation unit node.
2790 if Nkind (Parent (N)) = N_Compilation_Unit then
2791 Set_Cunit_Entity (Current_Sem_Unit, Id);
2792 Set_Body_Required (Parent (N), Unit_Requires_Body (Id));
2793 end if;
2795 Set_Categorization_From_Pragmas (N);
2796 Validate_Categorization_Dependency (N, Id);
2798 Save_Global_References (Original_Node (N));
2800 End_Generic;
2801 End_Scope;
2802 Exit_Generic_Scope (Id);
2803 Generate_Reference_To_Formals (Id);
2804 end Analyze_Generic_Subprogram_Declaration;
2806 -----------------------------------
2807 -- Analyze_Package_Instantiation --
2808 -----------------------------------
2810 procedure Analyze_Package_Instantiation (N : Node_Id) is
2811 Loc : constant Source_Ptr := Sloc (N);
2812 Gen_Id : constant Node_Id := Name (N);
2814 Act_Decl : Node_Id;
2815 Act_Decl_Name : Node_Id;
2816 Act_Decl_Id : Entity_Id;
2817 Act_Spec : Node_Id;
2818 Act_Tree : Node_Id;
2820 Gen_Decl : Node_Id;
2821 Gen_Unit : Entity_Id;
2823 Is_Actual_Pack : constant Boolean :=
2824 Is_Internal (Defining_Entity (N));
2826 Env_Installed : Boolean := False;
2827 Parent_Installed : Boolean := False;
2828 Renaming_List : List_Id;
2829 Unit_Renaming : Node_Id;
2830 Needs_Body : Boolean;
2831 Inline_Now : Boolean := False;
2833 procedure Delay_Descriptors (E : Entity_Id);
2834 -- Delay generation of subprogram descriptors for given entity
2836 function Might_Inline_Subp return Boolean;
2837 -- If inlining is active and the generic contains inlined subprograms,
2838 -- we instantiate the body. This may cause superfluous instantiations,
2839 -- but it is simpler than detecting the need for the body at the point
2840 -- of inlining, when the context of the instance is not available.
2842 -----------------------
2843 -- Delay_Descriptors --
2844 -----------------------
2846 procedure Delay_Descriptors (E : Entity_Id) is
2847 begin
2848 if not Delay_Subprogram_Descriptors (E) then
2849 Set_Delay_Subprogram_Descriptors (E);
2850 Pending_Descriptor.Append (E);
2851 end if;
2852 end Delay_Descriptors;
2854 -----------------------
2855 -- Might_Inline_Subp --
2856 -----------------------
2858 function Might_Inline_Subp return Boolean is
2859 E : Entity_Id;
2861 begin
2862 if not Inline_Processing_Required then
2863 return False;
2865 else
2866 E := First_Entity (Gen_Unit);
2867 while Present (E) loop
2868 if Is_Subprogram (E)
2869 and then Is_Inlined (E)
2870 then
2871 return True;
2872 end if;
2874 Next_Entity (E);
2875 end loop;
2876 end if;
2878 return False;
2879 end Might_Inline_Subp;
2881 -- Start of processing for Analyze_Package_Instantiation
2883 begin
2884 -- Very first thing: apply the special kludge for Text_IO processing
2885 -- in case we are instantiating one of the children of [Wide_]Text_IO.
2887 Text_IO_Kludge (Name (N));
2889 -- Make node global for error reporting
2891 Instantiation_Node := N;
2893 -- Case of instantiation of a generic package
2895 if Nkind (N) = N_Package_Instantiation then
2896 Act_Decl_Id := New_Copy (Defining_Entity (N));
2897 Set_Comes_From_Source (Act_Decl_Id, True);
2899 if Nkind (Defining_Unit_Name (N)) = N_Defining_Program_Unit_Name then
2900 Act_Decl_Name :=
2901 Make_Defining_Program_Unit_Name (Loc,
2902 Name => New_Copy_Tree (Name (Defining_Unit_Name (N))),
2903 Defining_Identifier => Act_Decl_Id);
2904 else
2905 Act_Decl_Name := Act_Decl_Id;
2906 end if;
2908 -- Case of instantiation of a formal package
2910 else
2911 Act_Decl_Id := Defining_Identifier (N);
2912 Act_Decl_Name := Act_Decl_Id;
2913 end if;
2915 Generate_Definition (Act_Decl_Id);
2916 Preanalyze_Actuals (N);
2918 Init_Env;
2919 Env_Installed := True;
2920 Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
2921 Gen_Unit := Entity (Gen_Id);
2923 -- Verify that it is the name of a generic package
2925 if Etype (Gen_Unit) = Any_Type then
2926 Restore_Env;
2927 return;
2929 elsif Ekind (Gen_Unit) /= E_Generic_Package then
2931 -- Ada 2005 (AI-50217): Cannot use instance in limited with_clause
2933 if From_With_Type (Gen_Unit) then
2934 Error_Msg_N
2935 ("cannot instantiate a limited withed package", Gen_Id);
2936 else
2937 Error_Msg_N
2938 ("expect name of generic package in instantiation", Gen_Id);
2939 end if;
2941 Restore_Env;
2942 return;
2943 end if;
2945 if In_Extended_Main_Source_Unit (N) then
2946 Set_Is_Instantiated (Gen_Unit);
2947 Generate_Reference (Gen_Unit, N);
2949 if Present (Renamed_Object (Gen_Unit)) then
2950 Set_Is_Instantiated (Renamed_Object (Gen_Unit));
2951 Generate_Reference (Renamed_Object (Gen_Unit), N);
2952 end if;
2953 end if;
2955 if Nkind (Gen_Id) = N_Identifier
2956 and then Chars (Gen_Unit) = Chars (Defining_Entity (N))
2957 then
2958 Error_Msg_NE
2959 ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
2961 elsif Nkind (Gen_Id) = N_Expanded_Name
2962 and then Is_Child_Unit (Gen_Unit)
2963 and then Nkind (Prefix (Gen_Id)) = N_Identifier
2964 and then Chars (Act_Decl_Id) = Chars (Prefix (Gen_Id))
2965 then
2966 Error_Msg_N
2967 ("& is hidden within declaration of instance ", Prefix (Gen_Id));
2968 end if;
2970 Set_Entity (Gen_Id, Gen_Unit);
2972 -- If generic is a renaming, get original generic unit
2974 if Present (Renamed_Object (Gen_Unit))
2975 and then Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Package
2976 then
2977 Gen_Unit := Renamed_Object (Gen_Unit);
2978 end if;
2980 -- Verify that there are no circular instantiations
2982 if In_Open_Scopes (Gen_Unit) then
2983 Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit);
2984 Restore_Env;
2985 return;
2987 elsif Contains_Instance_Of (Gen_Unit, Current_Scope, Gen_Id) then
2988 Error_Msg_Node_2 := Current_Scope;
2989 Error_Msg_NE
2990 ("circular Instantiation: & instantiated in &!", N, Gen_Unit);
2991 Circularity_Detected := True;
2992 Restore_Env;
2993 return;
2995 else
2996 Gen_Decl := Unit_Declaration_Node (Gen_Unit);
2998 -- Initialize renamings map, for error checking, and the list that
2999 -- holds private entities whose views have changed between generic
3000 -- definition and instantiation. If this is the instance created to
3001 -- validate an actual package, the instantiation environment is that
3002 -- of the enclosing instance.
3004 Generic_Renamings.Set_Last (0);
3005 Generic_Renamings_HTable.Reset;
3007 Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
3009 -- Copy original generic tree, to produce text for instantiation
3011 Act_Tree :=
3012 Copy_Generic_Node
3013 (Original_Node (Gen_Decl), Empty, Instantiating => True);
3015 Act_Spec := Specification (Act_Tree);
3017 -- If this is the instance created to validate an actual package,
3018 -- only the formals matter, do not examine the package spec itself.
3020 if Is_Actual_Pack then
3021 Set_Visible_Declarations (Act_Spec, New_List);
3022 Set_Private_Declarations (Act_Spec, New_List);
3023 end if;
3025 Renaming_List :=
3026 Analyze_Associations
3028 Generic_Formal_Declarations (Act_Tree),
3029 Generic_Formal_Declarations (Gen_Decl));
3031 Set_Instance_Env (Gen_Unit, Act_Decl_Id);
3032 Set_Defining_Unit_Name (Act_Spec, Act_Decl_Name);
3033 Set_Is_Generic_Instance (Act_Decl_Id);
3035 Set_Generic_Parent (Act_Spec, Gen_Unit);
3037 -- References to the generic in its own declaration or its body are
3038 -- references to the instance. Add a renaming declaration for the
3039 -- generic unit itself. This declaration, as well as the renaming
3040 -- declarations for the generic formals, must remain private to the
3041 -- unit: the formals, because this is the language semantics, and
3042 -- the unit because its use is an artifact of the implementation.
3044 Unit_Renaming :=
3045 Make_Package_Renaming_Declaration (Loc,
3046 Defining_Unit_Name =>
3047 Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
3048 Name => New_Reference_To (Act_Decl_Id, Loc));
3050 Append (Unit_Renaming, Renaming_List);
3052 -- The renaming declarations are the first local declarations of
3053 -- the new unit.
3055 if Is_Non_Empty_List (Visible_Declarations (Act_Spec)) then
3056 Insert_List_Before
3057 (First (Visible_Declarations (Act_Spec)), Renaming_List);
3058 else
3059 Set_Visible_Declarations (Act_Spec, Renaming_List);
3060 end if;
3062 Act_Decl :=
3063 Make_Package_Declaration (Loc,
3064 Specification => Act_Spec);
3066 -- Save the instantiation node, for subsequent instantiation of the
3067 -- body, if there is one and we are generating code for the current
3068 -- unit. Mark the unit as having a body, to avoid a premature error
3069 -- message.
3071 -- We instantiate the body if we are generating code, if we are
3072 -- generating cross-reference information, or if we are building
3073 -- trees for ASIS use.
3075 declare
3076 Enclosing_Body_Present : Boolean := False;
3077 -- If the generic unit is not a compilation unit, then a body may
3078 -- be present in its parent even if none is required. We create a
3079 -- tentative pending instantiation for the body, which will be
3080 -- discarded if none is actually present.
3082 Scop : Entity_Id;
3084 begin
3085 if Scope (Gen_Unit) /= Standard_Standard
3086 and then not Is_Child_Unit (Gen_Unit)
3087 then
3088 Scop := Scope (Gen_Unit);
3090 while Present (Scop)
3091 and then Scop /= Standard_Standard
3092 loop
3093 if Unit_Requires_Body (Scop) then
3094 Enclosing_Body_Present := True;
3095 exit;
3097 elsif In_Open_Scopes (Scop)
3098 and then In_Package_Body (Scop)
3099 then
3100 Enclosing_Body_Present := True;
3101 exit;
3102 end if;
3104 exit when Is_Compilation_Unit (Scop);
3105 Scop := Scope (Scop);
3106 end loop;
3107 end if;
3109 -- If front-end inlining is enabled, and this is a unit for which
3110 -- code will be generated, we instantiate the body at once.
3112 -- This is done if the instance is not the main unit, and if the
3113 -- generic is not a child unit of another generic, to avoid scope
3114 -- problems and the reinstallation of parent instances.
3116 if Expander_Active
3117 and then (not Is_Child_Unit (Gen_Unit)
3118 or else not Is_Generic_Unit (Scope (Gen_Unit)))
3119 and then Might_Inline_Subp
3120 and then not Is_Actual_Pack
3121 then
3122 if Front_End_Inlining
3123 and then (Is_In_Main_Unit (N)
3124 or else In_Main_Context (Current_Scope))
3125 and then Nkind (Parent (N)) /= N_Compilation_Unit
3126 then
3127 Inline_Now := True;
3129 -- In configurable_run_time mode we force the inlining of
3130 -- predefined subprograms marked Inline_Always, to minimize
3131 -- the use of the run-time library.
3133 elsif Is_Predefined_File_Name
3134 (Unit_File_Name (Get_Source_Unit (Gen_Decl)))
3135 and then Configurable_Run_Time_Mode
3136 and then Nkind (Parent (N)) /= N_Compilation_Unit
3137 then
3138 Inline_Now := True;
3139 end if;
3141 -- If the current scope is itself an instance within a child
3142 -- unit, there will be duplications in the scope stack, and the
3143 -- unstacking mechanism in Inline_Instance_Body will fail.
3144 -- This loses some rare cases of optimization, and might be
3145 -- improved some day, if we can find a proper abstraction for
3146 -- "the complete compilation context" that can be saved and
3147 -- restored. ???
3149 if Is_Generic_Instance (Current_Scope) then
3150 declare
3151 Curr_Unit : constant Entity_Id :=
3152 Cunit_Entity (Current_Sem_Unit);
3153 begin
3154 if Curr_Unit /= Current_Scope
3155 and then Is_Child_Unit (Curr_Unit)
3156 then
3157 Inline_Now := False;
3158 end if;
3159 end;
3160 end if;
3161 end if;
3163 Needs_Body :=
3164 (Unit_Requires_Body (Gen_Unit)
3165 or else Enclosing_Body_Present
3166 or else Present (Corresponding_Body (Gen_Decl)))
3167 and then (Is_In_Main_Unit (N)
3168 or else Might_Inline_Subp)
3169 and then not Is_Actual_Pack
3170 and then not Inline_Now
3171 and then (Operating_Mode = Generate_Code
3172 or else (Operating_Mode = Check_Semantics
3173 and then ASIS_Mode));
3175 -- If front_end_inlining is enabled, do not instantiate body if
3176 -- within a generic context.
3178 if (Front_End_Inlining
3179 and then not Expander_Active)
3180 or else Is_Generic_Unit (Cunit_Entity (Main_Unit))
3181 then
3182 Needs_Body := False;
3183 end if;
3185 -- If the current context is generic, and the package being
3186 -- instantiated is declared within a formal package, there is no
3187 -- body to instantiate until the enclosing generic is instantiated
3188 -- and there is an actual for the formal package. If the formal
3189 -- package has parameters, we build a regular package instance for
3190 -- it, that precedes the original formal package declaration.
3192 if In_Open_Scopes (Scope (Scope (Gen_Unit))) then
3193 declare
3194 Decl : constant Node_Id :=
3195 Original_Node
3196 (Unit_Declaration_Node (Scope (Gen_Unit)));
3197 begin
3198 if Nkind (Decl) = N_Formal_Package_Declaration
3199 or else (Nkind (Decl) = N_Package_Declaration
3200 and then Is_List_Member (Decl)
3201 and then Present (Next (Decl))
3202 and then
3203 Nkind (Next (Decl)) =
3204 N_Formal_Package_Declaration)
3205 then
3206 Needs_Body := False;
3207 end if;
3208 end;
3209 end if;
3210 end;
3212 -- If we are generating the calling stubs from the instantiation of
3213 -- a generic RCI package, we will not use the body of the generic
3214 -- package.
3216 if Distribution_Stub_Mode = Generate_Caller_Stub_Body
3217 and then Is_Compilation_Unit (Defining_Entity (N))
3218 then
3219 Needs_Body := False;
3220 end if;
3222 if Needs_Body then
3224 -- Here is a defence against a ludicrous number of instantiations
3225 -- caused by a circular set of instantiation attempts.
3227 if Pending_Instantiations.Last >
3228 Hostparm.Max_Instantiations
3229 then
3230 Error_Msg_N ("too many instantiations", N);
3231 raise Unrecoverable_Error;
3232 end if;
3234 -- Indicate that the enclosing scopes contain an instantiation,
3235 -- and that cleanup actions should be delayed until after the
3236 -- instance body is expanded.
3238 Check_Forward_Instantiation (Gen_Decl);
3239 if Nkind (N) = N_Package_Instantiation then
3240 declare
3241 Enclosing_Master : Entity_Id;
3243 begin
3244 -- Loop to search enclosing masters
3246 Enclosing_Master := Current_Scope;
3247 Scope_Loop : while Enclosing_Master /= Standard_Standard loop
3248 if Ekind (Enclosing_Master) = E_Package then
3249 if Is_Compilation_Unit (Enclosing_Master) then
3250 if In_Package_Body (Enclosing_Master) then
3251 Delay_Descriptors
3252 (Body_Entity (Enclosing_Master));
3253 else
3254 Delay_Descriptors
3255 (Enclosing_Master);
3256 end if;
3258 exit Scope_Loop;
3260 else
3261 Enclosing_Master := Scope (Enclosing_Master);
3262 end if;
3264 elsif Ekind (Enclosing_Master) = E_Generic_Package then
3265 Enclosing_Master := Scope (Enclosing_Master);
3267 elsif Is_Generic_Subprogram (Enclosing_Master)
3268 or else Ekind (Enclosing_Master) = E_Void
3269 then
3270 -- Cleanup actions will eventually be performed on the
3271 -- enclosing instance, if any. Enclosing scope is void
3272 -- in the formal part of a generic subprogram.
3274 exit Scope_Loop;
3276 else
3277 if Ekind (Enclosing_Master) = E_Entry
3278 and then
3279 Ekind (Scope (Enclosing_Master)) = E_Protected_Type
3280 then
3281 if not Expander_Active then
3282 exit Scope_Loop;
3283 else
3284 Enclosing_Master :=
3285 Protected_Body_Subprogram (Enclosing_Master);
3286 end if;
3287 end if;
3289 Set_Delay_Cleanups (Enclosing_Master);
3291 while Ekind (Enclosing_Master) = E_Block loop
3292 Enclosing_Master := Scope (Enclosing_Master);
3293 end loop;
3295 if Is_Subprogram (Enclosing_Master) then
3296 Delay_Descriptors (Enclosing_Master);
3298 elsif Is_Task_Type (Enclosing_Master) then
3299 declare
3300 TBP : constant Node_Id :=
3301 Get_Task_Body_Procedure
3302 (Enclosing_Master);
3303 begin
3304 if Present (TBP) then
3305 Delay_Descriptors (TBP);
3306 Set_Delay_Cleanups (TBP);
3307 end if;
3308 end;
3309 end if;
3311 exit Scope_Loop;
3312 end if;
3313 end loop Scope_Loop;
3314 end;
3316 -- Make entry in table
3318 Pending_Instantiations.Append
3319 ((Inst_Node => N,
3320 Act_Decl => Act_Decl,
3321 Expander_Status => Expander_Active,
3322 Current_Sem_Unit => Current_Sem_Unit,
3323 Scope_Suppress => Scope_Suppress,
3324 Local_Suppress_Stack_Top => Local_Suppress_Stack_Top));
3325 end if;
3326 end if;
3328 Set_Categorization_From_Pragmas (Act_Decl);
3330 if Parent_Installed then
3331 Hide_Current_Scope;
3332 end if;
3334 Set_Instance_Spec (N, Act_Decl);
3336 -- If not a compilation unit, insert the package declaration before
3337 -- the original instantiation node.
3339 if Nkind (Parent (N)) /= N_Compilation_Unit then
3340 Mark_Rewrite_Insertion (Act_Decl);
3341 Insert_Before (N, Act_Decl);
3342 Analyze (Act_Decl);
3344 -- For an instantiation that is a compilation unit, place declaration
3345 -- on current node so context is complete for analysis (including
3346 -- nested instantiations). If this is the main unit, the declaration
3347 -- eventually replaces the instantiation node. If the instance body
3348 -- is created later, it replaces the instance node, and the
3349 -- declaration is attached to it (see
3350 -- Build_Instance_Compilation_Unit_Nodes).
3352 else
3353 if Cunit_Entity (Current_Sem_Unit) = Defining_Entity (N) then
3355 -- The entity for the current unit is the newly created one,
3356 -- and all semantic information is attached to it.
3358 Set_Cunit_Entity (Current_Sem_Unit, Act_Decl_Id);
3360 -- If this is the main unit, replace the main entity as well
3362 if Current_Sem_Unit = Main_Unit then
3363 Main_Unit_Entity := Act_Decl_Id;
3364 end if;
3365 end if;
3367 Set_Unit (Parent (N), Act_Decl);
3368 Set_Parent_Spec (Act_Decl, Parent_Spec (N));
3369 Set_Package_Instantiation (Act_Decl_Id, N);
3370 Analyze (Act_Decl);
3371 Set_Unit (Parent (N), N);
3372 Set_Body_Required (Parent (N), False);
3374 -- We never need elaboration checks on instantiations, since by
3375 -- definition, the body instantiation is elaborated at the same
3376 -- time as the spec instantiation.
3378 Set_Suppress_Elaboration_Warnings (Act_Decl_Id);
3379 Set_Kill_Elaboration_Checks (Act_Decl_Id);
3380 end if;
3382 Check_Elab_Instantiation (N);
3384 if ABE_Is_Certain (N) and then Needs_Body then
3385 Pending_Instantiations.Decrement_Last;
3386 end if;
3388 Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id);
3390 Set_First_Private_Entity (Defining_Unit_Name (Unit_Renaming),
3391 First_Private_Entity (Act_Decl_Id));
3393 -- If the instantiation will receive a body, the unit will be
3394 -- transformed into a package body, and receive its own elaboration
3395 -- entity. Otherwise, the nature of the unit is now a package
3396 -- declaration.
3398 if Nkind (Parent (N)) = N_Compilation_Unit
3399 and then not Needs_Body
3400 then
3401 Rewrite (N, Act_Decl);
3402 end if;
3404 if Present (Corresponding_Body (Gen_Decl))
3405 or else Unit_Requires_Body (Gen_Unit)
3406 then
3407 Set_Has_Completion (Act_Decl_Id);
3408 end if;
3410 Check_Formal_Packages (Act_Decl_Id);
3412 Restore_Private_Views (Act_Decl_Id);
3414 Inherit_Context (Gen_Decl, N);
3416 if Parent_Installed then
3417 Remove_Parent;
3418 end if;
3420 Restore_Env;
3421 Env_Installed := False;
3422 end if;
3424 Validate_Categorization_Dependency (N, Act_Decl_Id);
3426 -- Check restriction, but skip this if something went wrong in the above
3427 -- analysis, indicated by Act_Decl_Id being void.
3429 if Ekind (Act_Decl_Id) /= E_Void
3430 and then not Is_Library_Level_Entity (Act_Decl_Id)
3431 then
3432 Check_Restriction (No_Local_Allocators, N);
3433 end if;
3435 if Inline_Now then
3436 Inline_Instance_Body (N, Gen_Unit, Act_Decl);
3437 end if;
3439 -- The following is a tree patch for ASIS: ASIS needs separate nodes to
3440 -- be used as defining identifiers for a formal package and for the
3441 -- corresponding expanded package.
3443 if Nkind (N) = N_Formal_Package_Declaration then
3444 Act_Decl_Id := New_Copy (Defining_Entity (N));
3445 Set_Comes_From_Source (Act_Decl_Id, True);
3446 Set_Is_Generic_Instance (Act_Decl_Id, False);
3447 Set_Defining_Identifier (N, Act_Decl_Id);
3448 end if;
3450 exception
3451 when Instantiation_Error =>
3452 if Parent_Installed then
3453 Remove_Parent;
3454 end if;
3456 if Env_Installed then
3457 Restore_Env;
3458 end if;
3459 end Analyze_Package_Instantiation;
3461 --------------------------
3462 -- Inline_Instance_Body --
3463 --------------------------
3465 procedure Inline_Instance_Body
3466 (N : Node_Id;
3467 Gen_Unit : Entity_Id;
3468 Act_Decl : Node_Id)
3470 Vis : Boolean;
3471 Gen_Comp : constant Entity_Id :=
3472 Cunit_Entity (Get_Source_Unit (Gen_Unit));
3473 Curr_Comp : constant Node_Id := Cunit (Current_Sem_Unit);
3474 Curr_Scope : Entity_Id := Empty;
3475 Curr_Unit : constant Entity_Id :=
3476 Cunit_Entity (Current_Sem_Unit);
3477 Removed : Boolean := False;
3478 Num_Scopes : Int := 0;
3480 Scope_Stack_Depth : constant Int :=
3481 Scope_Stack.Last - Scope_Stack.First + 1;
3483 Use_Clauses : array (1 .. Scope_Stack_Depth) of Node_Id;
3484 Instances : array (1 .. Scope_Stack_Depth) of Entity_Id;
3485 Inner_Scopes : array (1 .. Scope_Stack_Depth) of Entity_Id;
3486 Num_Inner : Int := 0;
3487 N_Instances : Int := 0;
3488 S : Entity_Id;
3490 begin
3491 -- Case of generic unit defined in another unit. We must remove the
3492 -- complete context of the current unit to install that of the generic.
3494 if Gen_Comp /= Cunit_Entity (Current_Sem_Unit) then
3496 -- Add some comments for the following two loops ???
3498 S := Current_Scope;
3499 while Present (S) and then S /= Standard_Standard loop
3500 loop
3501 Num_Scopes := Num_Scopes + 1;
3503 Use_Clauses (Num_Scopes) :=
3504 (Scope_Stack.Table
3505 (Scope_Stack.Last - Num_Scopes + 1).
3506 First_Use_Clause);
3507 End_Use_Clauses (Use_Clauses (Num_Scopes));
3509 exit when Scope_Stack.Last - Num_Scopes + 1 = Scope_Stack.First
3510 or else Scope_Stack.Table
3511 (Scope_Stack.Last - Num_Scopes).Entity
3512 = Scope (S);
3513 end loop;
3515 exit when Is_Generic_Instance (S)
3516 and then (In_Package_Body (S)
3517 or else Ekind (S) = E_Procedure
3518 or else Ekind (S) = E_Function);
3519 S := Scope (S);
3520 end loop;
3522 Vis := Is_Immediately_Visible (Gen_Comp);
3524 -- Find and save all enclosing instances
3526 S := Current_Scope;
3528 while Present (S)
3529 and then S /= Standard_Standard
3530 loop
3531 if Is_Generic_Instance (S) then
3532 N_Instances := N_Instances + 1;
3533 Instances (N_Instances) := S;
3535 exit when In_Package_Body (S);
3536 end if;
3538 S := Scope (S);
3539 end loop;
3541 -- Remove context of current compilation unit, unless we are within a
3542 -- nested package instantiation, in which case the context has been
3543 -- removed previously.
3545 -- If current scope is the body of a child unit, remove context of
3546 -- spec as well. If an enclosing scope is an instance body, the
3547 -- context has already been removed, but the entities in the body
3548 -- must be made invisible as well.
3550 S := Current_Scope;
3552 while Present (S)
3553 and then S /= Standard_Standard
3554 loop
3555 if Is_Generic_Instance (S)
3556 and then (In_Package_Body (S)
3557 or else Ekind (S) = E_Procedure
3558 or else Ekind (S) = E_Function)
3559 then
3560 -- We still have to remove the entities of the enclosing
3561 -- instance from direct visibility.
3563 declare
3564 E : Entity_Id;
3565 begin
3566 E := First_Entity (S);
3567 while Present (E) loop
3568 Set_Is_Immediately_Visible (E, False);
3569 Next_Entity (E);
3570 end loop;
3571 end;
3573 exit;
3574 end if;
3576 if S = Curr_Unit
3577 or else (Ekind (Curr_Unit) = E_Package_Body
3578 and then S = Spec_Entity (Curr_Unit))
3579 or else (Ekind (Curr_Unit) = E_Subprogram_Body
3580 and then S =
3581 Corresponding_Spec
3582 (Unit_Declaration_Node (Curr_Unit)))
3583 then
3584 Removed := True;
3586 -- Remove entities in current scopes from visibility, so that
3587 -- instance body is compiled in a clean environment.
3589 Save_Scope_Stack (Handle_Use => False);
3591 if Is_Child_Unit (S) then
3593 -- Remove child unit from stack, as well as inner scopes.
3594 -- Removing the context of a child unit removes parent units
3595 -- as well.
3597 while Current_Scope /= S loop
3598 Num_Inner := Num_Inner + 1;
3599 Inner_Scopes (Num_Inner) := Current_Scope;
3600 Pop_Scope;
3601 end loop;
3603 Pop_Scope;
3604 Remove_Context (Curr_Comp);
3605 Curr_Scope := S;
3607 else
3608 Remove_Context (Curr_Comp);
3609 end if;
3611 if Ekind (Curr_Unit) = E_Package_Body then
3612 Remove_Context (Library_Unit (Curr_Comp));
3613 end if;
3614 end if;
3616 S := Scope (S);
3617 end loop;
3618 pragma Assert (Num_Inner < Num_Scopes);
3620 Push_Scope (Standard_Standard);
3621 Scope_Stack.Table (Scope_Stack.Last).Is_Active_Stack_Base := True;
3622 Instantiate_Package_Body
3623 (Body_Info =>
3624 ((Inst_Node => N,
3625 Act_Decl => Act_Decl,
3626 Expander_Status => Expander_Active,
3627 Current_Sem_Unit => Current_Sem_Unit,
3628 Scope_Suppress => Scope_Suppress,
3629 Local_Suppress_Stack_Top => Local_Suppress_Stack_Top)),
3630 Inlined_Body => True);
3632 Pop_Scope;
3634 -- Restore context
3636 Set_Is_Immediately_Visible (Gen_Comp, Vis);
3638 -- Reset Generic_Instance flag so that use clauses can be installed
3639 -- in the proper order. (See Use_One_Package for effect of enclosing
3640 -- instances on processing of use clauses).
3642 for J in 1 .. N_Instances loop
3643 Set_Is_Generic_Instance (Instances (J), False);
3644 end loop;
3646 if Removed then
3647 Install_Context (Curr_Comp);
3649 if Present (Curr_Scope)
3650 and then Is_Child_Unit (Curr_Scope)
3651 then
3652 Push_Scope (Curr_Scope);
3653 Set_Is_Immediately_Visible (Curr_Scope);
3655 -- Finally, restore inner scopes as well
3657 for J in reverse 1 .. Num_Inner loop
3658 Push_Scope (Inner_Scopes (J));
3659 end loop;
3660 end if;
3662 Restore_Scope_Stack (Handle_Use => False);
3664 if Present (Curr_Scope)
3665 and then
3666 (In_Private_Part (Curr_Scope)
3667 or else In_Package_Body (Curr_Scope))
3668 then
3669 -- Install private declaration of ancestor units, which are
3670 -- currently available. Restore_Scope_Stack and Install_Context
3671 -- only install the visible part of parents.
3673 declare
3674 Par : Entity_Id;
3675 begin
3676 Par := Scope (Curr_Scope);
3677 while (Present (Par))
3678 and then Par /= Standard_Standard
3679 loop
3680 Install_Private_Declarations (Par);
3681 Par := Scope (Par);
3682 end loop;
3683 end;
3684 end if;
3685 end if;
3687 -- Restore use clauses. For a child unit, use clauses in the parents
3688 -- are restored when installing the context, so only those in inner
3689 -- scopes (and those local to the child unit itself) need to be
3690 -- installed explicitly.
3692 if Is_Child_Unit (Curr_Unit)
3693 and then Removed
3694 then
3695 for J in reverse 1 .. Num_Inner + 1 loop
3696 Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause :=
3697 Use_Clauses (J);
3698 Install_Use_Clauses (Use_Clauses (J));
3699 end loop;
3701 else
3702 for J in reverse 1 .. Num_Scopes loop
3703 Scope_Stack.Table (Scope_Stack.Last - J + 1).First_Use_Clause :=
3704 Use_Clauses (J);
3705 Install_Use_Clauses (Use_Clauses (J));
3706 end loop;
3707 end if;
3709 -- Restore status of instances. If one of them is a body, make
3710 -- its local entities visible again.
3712 declare
3713 E : Entity_Id;
3714 Inst : Entity_Id;
3716 begin
3717 for J in 1 .. N_Instances loop
3718 Inst := Instances (J);
3719 Set_Is_Generic_Instance (Inst, True);
3721 if In_Package_Body (Inst)
3722 or else Ekind (S) = E_Procedure
3723 or else Ekind (S) = E_Function
3724 then
3725 E := First_Entity (Instances (J));
3726 while Present (E) loop
3727 Set_Is_Immediately_Visible (E);
3728 Next_Entity (E);
3729 end loop;
3730 end if;
3731 end loop;
3732 end;
3734 -- If generic unit is in current unit, current context is correct
3736 else
3737 Instantiate_Package_Body
3738 (Body_Info =>
3739 ((Inst_Node => N,
3740 Act_Decl => Act_Decl,
3741 Expander_Status => Expander_Active,
3742 Current_Sem_Unit => Current_Sem_Unit,
3743 Scope_Suppress => Scope_Suppress,
3744 Local_Suppress_Stack_Top => Local_Suppress_Stack_Top)),
3745 Inlined_Body => True);
3746 end if;
3747 end Inline_Instance_Body;
3749 -------------------------------------
3750 -- Analyze_Procedure_Instantiation --
3751 -------------------------------------
3753 procedure Analyze_Procedure_Instantiation (N : Node_Id) is
3754 begin
3755 Analyze_Subprogram_Instantiation (N, E_Procedure);
3756 end Analyze_Procedure_Instantiation;
3758 --------------------------------------
3759 -- Analyze_Subprogram_Instantiation --
3760 --------------------------------------
3762 procedure Analyze_Subprogram_Instantiation
3763 (N : Node_Id;
3764 K : Entity_Kind)
3766 Loc : constant Source_Ptr := Sloc (N);
3767 Gen_Id : constant Node_Id := Name (N);
3769 Anon_Id : constant Entity_Id :=
3770 Make_Defining_Identifier (Sloc (Defining_Entity (N)),
3771 Chars => New_External_Name
3772 (Chars (Defining_Entity (N)), 'R'));
3774 Act_Decl_Id : Entity_Id;
3775 Act_Decl : Node_Id;
3776 Act_Spec : Node_Id;
3777 Act_Tree : Node_Id;
3779 Env_Installed : Boolean := False;
3780 Gen_Unit : Entity_Id;
3781 Gen_Decl : Node_Id;
3782 Pack_Id : Entity_Id;
3783 Parent_Installed : Boolean := False;
3784 Renaming_List : List_Id;
3786 procedure Analyze_Instance_And_Renamings;
3787 -- The instance must be analyzed in a context that includes the mappings
3788 -- of generic parameters into actuals. We create a package declaration
3789 -- for this purpose, and a subprogram with an internal name within the
3790 -- package. The subprogram instance is simply an alias for the internal
3791 -- subprogram, declared in the current scope.
3793 ------------------------------------
3794 -- Analyze_Instance_And_Renamings --
3795 ------------------------------------
3797 procedure Analyze_Instance_And_Renamings is
3798 Def_Ent : constant Entity_Id := Defining_Entity (N);
3799 Pack_Decl : Node_Id;
3801 begin
3802 if Nkind (Parent (N)) = N_Compilation_Unit then
3804 -- For the case of a compilation unit, the container package has
3805 -- the same name as the instantiation, to insure that the binder
3806 -- calls the elaboration procedure with the right name. Copy the
3807 -- entity of the instance, which may have compilation level flags
3808 -- (e.g. Is_Child_Unit) set.
3810 Pack_Id := New_Copy (Def_Ent);
3812 else
3813 -- Otherwise we use the name of the instantiation concatenated
3814 -- with its source position to ensure uniqueness if there are
3815 -- several instantiations with the same name.
3817 Pack_Id :=
3818 Make_Defining_Identifier (Loc,
3819 Chars => New_External_Name
3820 (Related_Id => Chars (Def_Ent),
3821 Suffix => "GP",
3822 Suffix_Index => Source_Offset (Sloc (Def_Ent))));
3823 end if;
3825 Pack_Decl := Make_Package_Declaration (Loc,
3826 Specification => Make_Package_Specification (Loc,
3827 Defining_Unit_Name => Pack_Id,
3828 Visible_Declarations => Renaming_List,
3829 End_Label => Empty));
3831 Set_Instance_Spec (N, Pack_Decl);
3832 Set_Is_Generic_Instance (Pack_Id);
3833 Set_Debug_Info_Needed (Pack_Id);
3835 -- Case of not a compilation unit
3837 if Nkind (Parent (N)) /= N_Compilation_Unit then
3838 Mark_Rewrite_Insertion (Pack_Decl);
3839 Insert_Before (N, Pack_Decl);
3840 Set_Has_Completion (Pack_Id);
3842 -- Case of an instantiation that is a compilation unit
3844 -- Place declaration on current node so context is complete for
3845 -- analysis (including nested instantiations), and for use in a
3846 -- context_clause (see Analyze_With_Clause).
3848 else
3849 Set_Unit (Parent (N), Pack_Decl);
3850 Set_Parent_Spec (Pack_Decl, Parent_Spec (N));
3851 end if;
3853 Analyze (Pack_Decl);
3854 Check_Formal_Packages (Pack_Id);
3855 Set_Is_Generic_Instance (Pack_Id, False);
3857 -- Body of the enclosing package is supplied when instantiating the
3858 -- subprogram body, after semantic analysis is completed.
3860 if Nkind (Parent (N)) = N_Compilation_Unit then
3862 -- Remove package itself from visibility, so it does not
3863 -- conflict with subprogram.
3865 Set_Name_Entity_Id (Chars (Pack_Id), Homonym (Pack_Id));
3867 -- Set name and scope of internal subprogram so that the proper
3868 -- external name will be generated. The proper scope is the scope
3869 -- of the wrapper package. We need to generate debugging info for
3870 -- the internal subprogram, so set flag accordingly.
3872 Set_Chars (Anon_Id, Chars (Defining_Entity (N)));
3873 Set_Scope (Anon_Id, Scope (Pack_Id));
3875 -- Mark wrapper package as referenced, to avoid spurious warnings
3876 -- if the instantiation appears in various with_ clauses of
3877 -- subunits of the main unit.
3879 Set_Referenced (Pack_Id);
3880 end if;
3882 Set_Is_Generic_Instance (Anon_Id);
3883 Set_Debug_Info_Needed (Anon_Id);
3884 Act_Decl_Id := New_Copy (Anon_Id);
3886 Set_Parent (Act_Decl_Id, Parent (Anon_Id));
3887 Set_Chars (Act_Decl_Id, Chars (Defining_Entity (N)));
3888 Set_Sloc (Act_Decl_Id, Sloc (Defining_Entity (N)));
3889 Set_Comes_From_Source (Act_Decl_Id, True);
3891 -- The signature may involve types that are not frozen yet, but the
3892 -- subprogram will be frozen at the point the wrapper package is
3893 -- frozen, so it does not need its own freeze node. In fact, if one
3894 -- is created, it might conflict with the freezing actions from the
3895 -- wrapper package.
3897 Set_Has_Delayed_Freeze (Anon_Id, False);
3899 -- If the instance is a child unit, mark the Id accordingly. Mark
3900 -- the anonymous entity as well, which is the real subprogram and
3901 -- which is used when the instance appears in a context clause.
3903 Set_Is_Child_Unit (Act_Decl_Id, Is_Child_Unit (Defining_Entity (N)));
3904 Set_Is_Child_Unit (Anon_Id, Is_Child_Unit (Defining_Entity (N)));
3905 New_Overloaded_Entity (Act_Decl_Id);
3906 Check_Eliminated (Act_Decl_Id);
3908 -- In compilation unit case, kill elaboration checks on the
3909 -- instantiation, since they are never needed -- the body is
3910 -- instantiated at the same point as the spec.
3912 if Nkind (Parent (N)) = N_Compilation_Unit then
3913 Set_Suppress_Elaboration_Warnings (Act_Decl_Id);
3914 Set_Kill_Elaboration_Checks (Act_Decl_Id);
3915 Set_Is_Compilation_Unit (Anon_Id);
3917 Set_Cunit_Entity (Current_Sem_Unit, Pack_Id);
3918 end if;
3920 -- The instance is not a freezing point for the new subprogram
3922 Set_Is_Frozen (Act_Decl_Id, False);
3924 if Nkind (Defining_Entity (N)) = N_Defining_Operator_Symbol then
3925 Valid_Operator_Definition (Act_Decl_Id);
3926 end if;
3928 Set_Alias (Act_Decl_Id, Anon_Id);
3929 Set_Parent (Act_Decl_Id, Parent (Anon_Id));
3930 Set_Has_Completion (Act_Decl_Id);
3931 Set_Related_Instance (Pack_Id, Act_Decl_Id);
3933 if Nkind (Parent (N)) = N_Compilation_Unit then
3934 Set_Body_Required (Parent (N), False);
3935 end if;
3936 end Analyze_Instance_And_Renamings;
3938 -- Start of processing for Analyze_Subprogram_Instantiation
3940 begin
3941 -- Very first thing: apply the special kludge for Text_IO processing
3942 -- in case we are instantiating one of the children of [Wide_]Text_IO.
3943 -- Of course such an instantiation is bogus (these are packages, not
3944 -- subprograms), but we get a better error message if we do this.
3946 Text_IO_Kludge (Gen_Id);
3948 -- Make node global for error reporting
3950 Instantiation_Node := N;
3951 Preanalyze_Actuals (N);
3953 Init_Env;
3954 Env_Installed := True;
3955 Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
3956 Gen_Unit := Entity (Gen_Id);
3958 Generate_Reference (Gen_Unit, Gen_Id);
3960 if Nkind (Gen_Id) = N_Identifier
3961 and then Chars (Gen_Unit) = Chars (Defining_Entity (N))
3962 then
3963 Error_Msg_NE
3964 ("& is hidden within declaration of instance", Gen_Id, Gen_Unit);
3965 end if;
3967 if Etype (Gen_Unit) = Any_Type then
3968 Restore_Env;
3969 return;
3970 end if;
3972 -- Verify that it is a generic subprogram of the right kind, and that
3973 -- it does not lead to a circular instantiation.
3975 if Ekind (Gen_Unit) /= E_Generic_Procedure
3976 and then Ekind (Gen_Unit) /= E_Generic_Function
3977 then
3978 Error_Msg_N ("expect generic subprogram in instantiation", Gen_Id);
3980 elsif In_Open_Scopes (Gen_Unit) then
3981 Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit);
3983 elsif K = E_Procedure
3984 and then Ekind (Gen_Unit) /= E_Generic_Procedure
3985 then
3986 if Ekind (Gen_Unit) = E_Generic_Function then
3987 Error_Msg_N
3988 ("cannot instantiate generic function as procedure", Gen_Id);
3989 else
3990 Error_Msg_N
3991 ("expect name of generic procedure in instantiation", Gen_Id);
3992 end if;
3994 elsif K = E_Function
3995 and then Ekind (Gen_Unit) /= E_Generic_Function
3996 then
3997 if Ekind (Gen_Unit) = E_Generic_Procedure then
3998 Error_Msg_N
3999 ("cannot instantiate generic procedure as function", Gen_Id);
4000 else
4001 Error_Msg_N
4002 ("expect name of generic function in instantiation", Gen_Id);
4003 end if;
4005 else
4006 Set_Entity (Gen_Id, Gen_Unit);
4007 Set_Is_Instantiated (Gen_Unit);
4009 if In_Extended_Main_Source_Unit (N) then
4010 Generate_Reference (Gen_Unit, N);
4011 end if;
4013 -- If renaming, get original unit
4015 if Present (Renamed_Object (Gen_Unit))
4016 and then (Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Procedure
4017 or else
4018 Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Function)
4019 then
4020 Gen_Unit := Renamed_Object (Gen_Unit);
4021 Set_Is_Instantiated (Gen_Unit);
4022 Generate_Reference (Gen_Unit, N);
4023 end if;
4025 if Contains_Instance_Of (Gen_Unit, Current_Scope, Gen_Id) then
4026 Error_Msg_Node_2 := Current_Scope;
4027 Error_Msg_NE
4028 ("circular Instantiation: & instantiated in &!", N, Gen_Unit);
4029 Circularity_Detected := True;
4030 return;
4031 end if;
4033 Gen_Decl := Unit_Declaration_Node (Gen_Unit);
4035 -- Initialize renamings map, for error checking
4037 Generic_Renamings.Set_Last (0);
4038 Generic_Renamings_HTable.Reset;
4040 Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment);
4042 -- Copy original generic tree, to produce text for instantiation
4044 Act_Tree :=
4045 Copy_Generic_Node
4046 (Original_Node (Gen_Decl), Empty, Instantiating => True);
4048 -- Inherit overriding indicator from instance node
4050 Act_Spec := Specification (Act_Tree);
4051 Set_Must_Override (Act_Spec, Must_Override (N));
4052 Set_Must_Not_Override (Act_Spec, Must_Not_Override (N));
4054 Renaming_List :=
4055 Analyze_Associations
4057 Generic_Formal_Declarations (Act_Tree),
4058 Generic_Formal_Declarations (Gen_Decl));
4060 -- The subprogram itself cannot contain a nested instance, so the
4061 -- current parent is left empty.
4063 Set_Instance_Env (Gen_Unit, Empty);
4065 -- Build the subprogram declaration, which does not appear in the
4066 -- generic template, and give it a sloc consistent with that of the
4067 -- template.
4069 Set_Defining_Unit_Name (Act_Spec, Anon_Id);
4070 Set_Generic_Parent (Act_Spec, Gen_Unit);
4071 Act_Decl :=
4072 Make_Subprogram_Declaration (Sloc (Act_Spec),
4073 Specification => Act_Spec);
4075 Set_Categorization_From_Pragmas (Act_Decl);
4077 if Parent_Installed then
4078 Hide_Current_Scope;
4079 end if;
4081 Append (Act_Decl, Renaming_List);
4082 Analyze_Instance_And_Renamings;
4084 -- If the generic is marked Import (Intrinsic), then so is the
4085 -- instance. This indicates that there is no body to instantiate. If
4086 -- generic is marked inline, so it the instance, and the anonymous
4087 -- subprogram it renames. If inlined, or else if inlining is enabled
4088 -- for the compilation, we generate the instance body even if it is
4089 -- not within the main unit.
4091 -- Any other pragmas might also be inherited ???
4093 if Is_Intrinsic_Subprogram (Gen_Unit) then
4094 Set_Is_Intrinsic_Subprogram (Anon_Id);
4095 Set_Is_Intrinsic_Subprogram (Act_Decl_Id);
4097 if Chars (Gen_Unit) = Name_Unchecked_Conversion then
4098 Validate_Unchecked_Conversion (N, Act_Decl_Id);
4099 end if;
4100 end if;
4102 Generate_Definition (Act_Decl_Id);
4104 Set_Is_Inlined (Act_Decl_Id, Is_Inlined (Gen_Unit));
4105 Set_Is_Inlined (Anon_Id, Is_Inlined (Gen_Unit));
4107 if not Is_Intrinsic_Subprogram (Gen_Unit) then
4108 Check_Elab_Instantiation (N);
4109 end if;
4111 if Is_Dispatching_Operation (Act_Decl_Id)
4112 and then Ada_Version >= Ada_05
4113 then
4114 declare
4115 Formal : Entity_Id;
4117 begin
4118 Formal := First_Formal (Act_Decl_Id);
4119 while Present (Formal) loop
4120 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type
4121 and then Is_Controlling_Formal (Formal)
4122 and then not Can_Never_Be_Null (Formal)
4123 then
4124 Error_Msg_NE ("access parameter& is controlling,",
4125 N, Formal);
4126 Error_Msg_NE ("\corresponding parameter of & must be"
4127 & " explicitly null-excluding", N, Gen_Id);
4128 end if;
4130 Next_Formal (Formal);
4131 end loop;
4132 end;
4133 end if;
4135 Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id);
4137 -- Subject to change, pending on if other pragmas are inherited ???
4139 Validate_Categorization_Dependency (N, Act_Decl_Id);
4141 if not Is_Intrinsic_Subprogram (Act_Decl_Id) then
4142 Inherit_Context (Gen_Decl, N);
4144 Restore_Private_Views (Pack_Id, False);
4146 -- If the context requires a full instantiation, mark node for
4147 -- subsequent construction of the body.
4149 if (Is_In_Main_Unit (N)
4150 or else Is_Inlined (Act_Decl_Id))
4151 and then (Operating_Mode = Generate_Code
4152 or else (Operating_Mode = Check_Semantics
4153 and then ASIS_Mode))
4154 and then (Expander_Active or else ASIS_Mode)
4155 and then not ABE_Is_Certain (N)
4156 and then not Is_Eliminated (Act_Decl_Id)
4157 then
4158 Pending_Instantiations.Append
4159 ((Inst_Node => N,
4160 Act_Decl => Act_Decl,
4161 Expander_Status => Expander_Active,
4162 Current_Sem_Unit => Current_Sem_Unit,
4163 Scope_Suppress => Scope_Suppress,
4164 Local_Suppress_Stack_Top => Local_Suppress_Stack_Top));
4166 Check_Forward_Instantiation (Gen_Decl);
4168 -- The wrapper package is always delayed, because it does not
4169 -- constitute a freeze point, but to insure that the freeze
4170 -- node is placed properly, it is created directly when
4171 -- instantiating the body (otherwise the freeze node might
4172 -- appear to early for nested instantiations).
4174 elsif Nkind (Parent (N)) = N_Compilation_Unit then
4176 -- For ASIS purposes, indicate that the wrapper package has
4177 -- replaced the instantiation node.
4179 Rewrite (N, Unit (Parent (N)));
4180 Set_Unit (Parent (N), N);
4181 end if;
4183 elsif Nkind (Parent (N)) = N_Compilation_Unit then
4185 -- Replace instance node for library-level instantiations of
4186 -- intrinsic subprograms, for ASIS use.
4188 Rewrite (N, Unit (Parent (N)));
4189 Set_Unit (Parent (N), N);
4190 end if;
4192 if Parent_Installed then
4193 Remove_Parent;
4194 end if;
4196 Restore_Env;
4197 Env_Installed := False;
4198 Generic_Renamings.Set_Last (0);
4199 Generic_Renamings_HTable.Reset;
4200 end if;
4202 exception
4203 when Instantiation_Error =>
4204 if Parent_Installed then
4205 Remove_Parent;
4206 end if;
4208 if Env_Installed then
4209 Restore_Env;
4210 end if;
4211 end Analyze_Subprogram_Instantiation;
4213 -------------------------
4214 -- Get_Associated_Node --
4215 -------------------------
4217 function Get_Associated_Node (N : Node_Id) return Node_Id is
4218 Assoc : Node_Id;
4220 begin
4221 Assoc := Associated_Node (N);
4223 if Nkind (Assoc) /= Nkind (N) then
4224 return Assoc;
4226 elsif Nkind_In (Assoc, N_Aggregate, N_Extension_Aggregate) then
4227 return Assoc;
4229 else
4230 -- If the node is part of an inner generic, it may itself have been
4231 -- remapped into a further generic copy. Associated_Node is otherwise
4232 -- used for the entity of the node, and will be of a different node
4233 -- kind, or else N has been rewritten as a literal or function call.
4235 while Present (Associated_Node (Assoc))
4236 and then Nkind (Associated_Node (Assoc)) = Nkind (Assoc)
4237 loop
4238 Assoc := Associated_Node (Assoc);
4239 end loop;
4241 -- Follow and additional link in case the final node was rewritten.
4242 -- This can only happen with nested generic units.
4244 if (Nkind (Assoc) = N_Identifier or else Nkind (Assoc) in N_Op)
4245 and then Present (Associated_Node (Assoc))
4246 and then (Nkind_In (Associated_Node (Assoc), N_Function_Call,
4247 N_Explicit_Dereference,
4248 N_Integer_Literal,
4249 N_Real_Literal,
4250 N_String_Literal))
4251 then
4252 Assoc := Associated_Node (Assoc);
4253 end if;
4255 return Assoc;
4256 end if;
4257 end Get_Associated_Node;
4259 -------------------------------------------
4260 -- Build_Instance_Compilation_Unit_Nodes --
4261 -------------------------------------------
4263 procedure Build_Instance_Compilation_Unit_Nodes
4264 (N : Node_Id;
4265 Act_Body : Node_Id;
4266 Act_Decl : Node_Id)
4268 Decl_Cunit : Node_Id;
4269 Body_Cunit : Node_Id;
4270 Citem : Node_Id;
4271 New_Main : constant Entity_Id := Defining_Entity (Act_Decl);
4272 Old_Main : constant Entity_Id := Cunit_Entity (Main_Unit);
4274 begin
4275 -- A new compilation unit node is built for the instance declaration
4277 Decl_Cunit :=
4278 Make_Compilation_Unit (Sloc (N),
4279 Context_Items => Empty_List,
4280 Unit => Act_Decl,
4281 Aux_Decls_Node =>
4282 Make_Compilation_Unit_Aux (Sloc (N)));
4284 Set_Parent_Spec (Act_Decl, Parent_Spec (N));
4285 Set_Body_Required (Decl_Cunit, True);
4287 -- We use the original instantiation compilation unit as the resulting
4288 -- compilation unit of the instance, since this is the main unit.
4290 Rewrite (N, Act_Body);
4291 Body_Cunit := Parent (N);
4293 -- The two compilation unit nodes are linked by the Library_Unit field
4295 Set_Library_Unit (Decl_Cunit, Body_Cunit);
4296 Set_Library_Unit (Body_Cunit, Decl_Cunit);
4298 -- Preserve the private nature of the package if needed
4300 Set_Private_Present (Decl_Cunit, Private_Present (Body_Cunit));
4302 -- If the instance is not the main unit, its context, categorization,
4303 -- and elaboration entity are not relevant to the compilation.
4305 if Parent (N) /= Cunit (Main_Unit) then
4306 return;
4307 end if;
4309 -- The context clause items on the instantiation, which are now attached
4310 -- to the body compilation unit (since the body overwrote the original
4311 -- instantiation node), semantically belong on the spec, so copy them
4312 -- there. It's harmless to leave them on the body as well. In fact one
4313 -- could argue that they belong in both places.
4315 Citem := First (Context_Items (Body_Cunit));
4316 while Present (Citem) loop
4317 Append (New_Copy (Citem), Context_Items (Decl_Cunit));
4318 Next (Citem);
4319 end loop;
4321 -- Propagate categorization flags on packages, so that they appear in
4322 -- the ali file for the spec of the unit.
4324 if Ekind (New_Main) = E_Package then
4325 Set_Is_Pure (Old_Main, Is_Pure (New_Main));
4326 Set_Is_Preelaborated (Old_Main, Is_Preelaborated (New_Main));
4327 Set_Is_Remote_Types (Old_Main, Is_Remote_Types (New_Main));
4328 Set_Is_Shared_Passive (Old_Main, Is_Shared_Passive (New_Main));
4329 Set_Is_Remote_Call_Interface
4330 (Old_Main, Is_Remote_Call_Interface (New_Main));
4331 end if;
4333 -- Make entry in Units table, so that binder can generate call to
4334 -- elaboration procedure for body, if any.
4336 Make_Instance_Unit (Body_Cunit);
4337 Main_Unit_Entity := New_Main;
4338 Set_Cunit_Entity (Main_Unit, Main_Unit_Entity);
4340 -- Build elaboration entity, since the instance may certainly generate
4341 -- elaboration code requiring a flag for protection.
4343 Build_Elaboration_Entity (Decl_Cunit, New_Main);
4344 end Build_Instance_Compilation_Unit_Nodes;
4346 -----------------------------
4347 -- Check_Access_Definition --
4348 -----------------------------
4350 procedure Check_Access_Definition (N : Node_Id) is
4351 begin
4352 pragma Assert
4353 (Ada_Version >= Ada_05
4354 and then Present (Access_Definition (N)));
4355 null;
4356 end Check_Access_Definition;
4358 -----------------------------------
4359 -- Check_Formal_Package_Instance --
4360 -----------------------------------
4362 -- If the formal has specific parameters, they must match those of the
4363 -- actual. Both of them are instances, and the renaming declarations for
4364 -- their formal parameters appear in the same order in both. The analyzed
4365 -- formal has been analyzed in the context of the current instance.
4367 procedure Check_Formal_Package_Instance
4368 (Formal_Pack : Entity_Id;
4369 Actual_Pack : Entity_Id)
4371 E1 : Entity_Id := First_Entity (Actual_Pack);
4372 E2 : Entity_Id := First_Entity (Formal_Pack);
4374 Expr1 : Node_Id;
4375 Expr2 : Node_Id;
4377 procedure Check_Mismatch (B : Boolean);
4378 -- Common error routine for mismatch between the parameters of the
4379 -- actual instance and those of the formal package.
4381 function Same_Instantiated_Constant (E1, E2 : Entity_Id) return Boolean;
4382 -- The formal may come from a nested formal package, and the actual may
4383 -- have been constant-folded. To determine whether the two denote the
4384 -- same entity we may have to traverse several definitions to recover
4385 -- the ultimate entity that they refer to.
4387 function Same_Instantiated_Variable (E1, E2 : Entity_Id) return Boolean;
4388 -- Similarly, if the formal comes from a nested formal package, the
4389 -- actual may designate the formal through multiple renamings, which
4390 -- have to be followed to determine the original variable in question.
4392 --------------------
4393 -- Check_Mismatch --
4394 --------------------
4396 procedure Check_Mismatch (B : Boolean) is
4397 Kind : constant Node_Kind := Nkind (Parent (E2));
4399 begin
4400 if Kind = N_Formal_Type_Declaration then
4401 return;
4403 elsif Nkind_In (Kind, N_Formal_Object_Declaration,
4404 N_Formal_Package_Declaration)
4405 or else Kind in N_Formal_Subprogram_Declaration
4406 then
4407 null;
4409 elsif B then
4410 Error_Msg_NE
4411 ("actual for & in actual instance does not match formal",
4412 Parent (Actual_Pack), E1);
4413 end if;
4414 end Check_Mismatch;
4416 --------------------------------
4417 -- Same_Instantiated_Constant --
4418 --------------------------------
4420 function Same_Instantiated_Constant
4421 (E1, E2 : Entity_Id) return Boolean
4423 Ent : Entity_Id;
4425 begin
4426 Ent := E2;
4427 while Present (Ent) loop
4428 if E1 = Ent then
4429 return True;
4431 elsif Ekind (Ent) /= E_Constant then
4432 return False;
4434 elsif Is_Entity_Name (Constant_Value (Ent)) then
4435 if Entity (Constant_Value (Ent)) = E1 then
4436 return True;
4437 else
4438 Ent := Entity (Constant_Value (Ent));
4439 end if;
4441 -- The actual may be a constant that has been folded. Recover
4442 -- original name.
4444 elsif Is_Entity_Name (Original_Node (Constant_Value (Ent))) then
4445 Ent := Entity (Original_Node (Constant_Value (Ent)));
4446 else
4447 return False;
4448 end if;
4449 end loop;
4451 return False;
4452 end Same_Instantiated_Constant;
4454 --------------------------------
4455 -- Same_Instantiated_Variable --
4456 --------------------------------
4458 function Same_Instantiated_Variable
4459 (E1, E2 : Entity_Id) return Boolean
4461 function Original_Entity (E : Entity_Id) return Entity_Id;
4462 -- Follow chain of renamings to the ultimate ancestor
4464 ---------------------
4465 -- Original_Entity --
4466 ---------------------
4468 function Original_Entity (E : Entity_Id) return Entity_Id is
4469 Orig : Entity_Id;
4471 begin
4472 Orig := E;
4473 while Nkind (Parent (Orig)) = N_Object_Renaming_Declaration
4474 and then Present (Renamed_Object (Orig))
4475 and then Is_Entity_Name (Renamed_Object (Orig))
4476 loop
4477 Orig := Entity (Renamed_Object (Orig));
4478 end loop;
4480 return Orig;
4481 end Original_Entity;
4483 -- Start of processing for Same_Instantiated_Variable
4485 begin
4486 return Ekind (E1) = Ekind (E2)
4487 and then Original_Entity (E1) = Original_Entity (E2);
4488 end Same_Instantiated_Variable;
4490 -- Start of processing for Check_Formal_Package_Instance
4492 begin
4493 while Present (E1)
4494 and then Present (E2)
4495 loop
4496 exit when Ekind (E1) = E_Package
4497 and then Renamed_Entity (E1) = Renamed_Entity (Actual_Pack);
4499 -- If the formal is the renaming of the formal package, this
4500 -- is the end of its formal part, which may occur before the
4501 -- end of the formal part in the actual in the presence of
4502 -- defaulted parameters in the formal package.
4504 exit when Nkind (Parent (E2)) = N_Package_Renaming_Declaration
4505 and then Renamed_Entity (E2) = Scope (E2);
4507 -- The analysis of the actual may generate additional internal
4508 -- entities. If the formal is defaulted, there is no corresponding
4509 -- analysis and the internal entities must be skipped, until we
4510 -- find corresponding entities again.
4512 if Comes_From_Source (E2)
4513 and then not Comes_From_Source (E1)
4514 and then Chars (E1) /= Chars (E2)
4515 then
4516 while Present (E1)
4517 and then Chars (E1) /= Chars (E2)
4518 loop
4519 Next_Entity (E1);
4520 end loop;
4521 end if;
4523 if No (E1) then
4524 return;
4526 -- If the formal entity comes from a formal declaration, it was
4527 -- defaulted in the formal package, and no check is needed on it.
4529 elsif Nkind (Parent (E2)) = N_Formal_Object_Declaration then
4530 goto Next_E;
4532 elsif Is_Type (E1) then
4534 -- Subtypes must statically match. E1, E2 are the local entities
4535 -- that are subtypes of the actuals. Itypes generated for other
4536 -- parameters need not be checked, the check will be performed
4537 -- on the parameters themselves.
4539 -- If E2 is a formal type declaration, it is a defaulted parameter
4540 -- and needs no checking.
4542 if not Is_Itype (E1)
4543 and then not Is_Itype (E2)
4544 then
4545 Check_Mismatch
4546 (not Is_Type (E2)
4547 or else Etype (E1) /= Etype (E2)
4548 or else not Subtypes_Statically_Match (E1, E2));
4549 end if;
4551 elsif Ekind (E1) = E_Constant then
4553 -- IN parameters must denote the same static value, or the same
4554 -- constant, or the literal null.
4556 Expr1 := Expression (Parent (E1));
4558 if Ekind (E2) /= E_Constant then
4559 Check_Mismatch (True);
4560 goto Next_E;
4561 else
4562 Expr2 := Expression (Parent (E2));
4563 end if;
4565 if Is_Static_Expression (Expr1) then
4567 if not Is_Static_Expression (Expr2) then
4568 Check_Mismatch (True);
4570 elsif Is_Discrete_Type (Etype (E1)) then
4571 declare
4572 V1 : constant Uint := Expr_Value (Expr1);
4573 V2 : constant Uint := Expr_Value (Expr2);
4574 begin
4575 Check_Mismatch (V1 /= V2);
4576 end;
4578 elsif Is_Real_Type (Etype (E1)) then
4579 declare
4580 V1 : constant Ureal := Expr_Value_R (Expr1);
4581 V2 : constant Ureal := Expr_Value_R (Expr2);
4582 begin
4583 Check_Mismatch (V1 /= V2);
4584 end;
4586 elsif Is_String_Type (Etype (E1))
4587 and then Nkind (Expr1) = N_String_Literal
4588 then
4589 if Nkind (Expr2) /= N_String_Literal then
4590 Check_Mismatch (True);
4591 else
4592 Check_Mismatch
4593 (not String_Equal (Strval (Expr1), Strval (Expr2)));
4594 end if;
4595 end if;
4597 elsif Is_Entity_Name (Expr1) then
4598 if Is_Entity_Name (Expr2) then
4599 if Entity (Expr1) = Entity (Expr2) then
4600 null;
4601 else
4602 Check_Mismatch
4603 (not Same_Instantiated_Constant
4604 (Entity (Expr1), Entity (Expr2)));
4605 end if;
4606 else
4607 Check_Mismatch (True);
4608 end if;
4610 elsif Is_Entity_Name (Original_Node (Expr1))
4611 and then Is_Entity_Name (Expr2)
4612 and then
4613 Same_Instantiated_Constant
4614 (Entity (Original_Node (Expr1)), Entity (Expr2))
4615 then
4616 null;
4618 elsif Nkind (Expr1) = N_Null then
4619 Check_Mismatch (Nkind (Expr1) /= N_Null);
4621 else
4622 Check_Mismatch (True);
4623 end if;
4625 elsif Ekind (E1) = E_Variable then
4626 Check_Mismatch (not Same_Instantiated_Variable (E1, E2));
4628 elsif Ekind (E1) = E_Package then
4629 Check_Mismatch
4630 (Ekind (E1) /= Ekind (E2)
4631 or else Renamed_Object (E1) /= Renamed_Object (E2));
4633 elsif Is_Overloadable (E1) then
4635 -- Verify that the actual subprograms match. Note that actuals
4636 -- that are attributes are rewritten as subprograms. If the
4637 -- subprogram in the formal package is defaulted, no check is
4638 -- needed. Note that this can only happen in Ada 2005 when the
4639 -- formal package can be partially parametrized.
4641 if Nkind (Unit_Declaration_Node (E1)) =
4642 N_Subprogram_Renaming_Declaration
4643 and then From_Default (Unit_Declaration_Node (E1))
4644 then
4645 null;
4647 else
4648 Check_Mismatch
4649 (Ekind (E2) /= Ekind (E1) or else (Alias (E1)) /= Alias (E2));
4650 end if;
4652 else
4653 raise Program_Error;
4654 end if;
4656 <<Next_E>>
4657 Next_Entity (E1);
4658 Next_Entity (E2);
4659 end loop;
4660 end Check_Formal_Package_Instance;
4662 ---------------------------
4663 -- Check_Formal_Packages --
4664 ---------------------------
4666 procedure Check_Formal_Packages (P_Id : Entity_Id) is
4667 E : Entity_Id;
4668 Formal_P : Entity_Id;
4670 begin
4671 -- Iterate through the declarations in the instance, looking for package
4672 -- renaming declarations that denote instances of formal packages. Stop
4673 -- when we find the renaming of the current package itself. The
4674 -- declaration for a formal package without a box is followed by an
4675 -- internal entity that repeats the instantiation.
4677 E := First_Entity (P_Id);
4678 while Present (E) loop
4679 if Ekind (E) = E_Package then
4680 if Renamed_Object (E) = P_Id then
4681 exit;
4683 elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
4684 null;
4686 elsif not Box_Present (Parent (Associated_Formal_Package (E))) then
4687 Formal_P := Next_Entity (E);
4688 Check_Formal_Package_Instance (Formal_P, E);
4690 -- After checking, remove the internal validating package. It
4691 -- is only needed for semantic checks, and as it may contain
4692 -- generic formal declarations it should not reach gigi.
4694 Remove (Unit_Declaration_Node (Formal_P));
4695 end if;
4696 end if;
4698 Next_Entity (E);
4699 end loop;
4700 end Check_Formal_Packages;
4702 ---------------------------------
4703 -- Check_Forward_Instantiation --
4704 ---------------------------------
4706 procedure Check_Forward_Instantiation (Decl : Node_Id) is
4707 S : Entity_Id;
4708 Gen_Comp : Entity_Id := Cunit_Entity (Get_Source_Unit (Decl));
4710 begin
4711 -- The instantiation appears before the generic body if we are in the
4712 -- scope of the unit containing the generic, either in its spec or in
4713 -- the package body, and before the generic body.
4715 if Ekind (Gen_Comp) = E_Package_Body then
4716 Gen_Comp := Spec_Entity (Gen_Comp);
4717 end if;
4719 if In_Open_Scopes (Gen_Comp)
4720 and then No (Corresponding_Body (Decl))
4721 then
4722 S := Current_Scope;
4724 while Present (S)
4725 and then not Is_Compilation_Unit (S)
4726 and then not Is_Child_Unit (S)
4727 loop
4728 if Ekind (S) = E_Package then
4729 Set_Has_Forward_Instantiation (S);
4730 end if;
4732 S := Scope (S);
4733 end loop;
4734 end if;
4735 end Check_Forward_Instantiation;
4737 ---------------------------
4738 -- Check_Generic_Actuals --
4739 ---------------------------
4741 -- The visibility of the actuals may be different between the point of
4742 -- generic instantiation and the instantiation of the body.
4744 procedure Check_Generic_Actuals
4745 (Instance : Entity_Id;
4746 Is_Formal_Box : Boolean)
4748 E : Entity_Id;
4749 Astype : Entity_Id;
4751 function Denotes_Previous_Actual (Typ : Entity_Id) return Boolean;
4752 -- For a formal that is an array type, the component type is often a
4753 -- previous formal in the same unit. The privacy status of the component
4754 -- type will have been examined earlier in the traversal of the
4755 -- corresponding actuals, and this status should not be modified for the
4756 -- array type itself.
4758 -- To detect this case we have to rescan the list of formals, which
4759 -- is usually short enough to ignore the resulting inefficiency.
4761 function Denotes_Previous_Actual (Typ : Entity_Id) return Boolean is
4762 Prev : Entity_Id;
4763 begin
4764 Prev := First_Entity (Instance);
4765 while Present (Prev) loop
4766 if Is_Type (Prev)
4767 and then Nkind (Parent (Prev)) = N_Subtype_Declaration
4768 and then Is_Entity_Name (Subtype_Indication (Parent (Prev)))
4769 and then Entity (Subtype_Indication (Parent (Prev))) = Typ
4770 then
4771 return True;
4772 elsif Prev = E then
4773 return False;
4774 else
4775 Next_Entity (Prev);
4776 end if;
4777 end loop;
4778 return False;
4779 end Denotes_Previous_Actual;
4781 -- Start of processing for Check_Generic_Actuals
4783 begin
4784 E := First_Entity (Instance);
4785 while Present (E) loop
4786 if Is_Type (E)
4787 and then Nkind (Parent (E)) = N_Subtype_Declaration
4788 and then Scope (Etype (E)) /= Instance
4789 and then Is_Entity_Name (Subtype_Indication (Parent (E)))
4790 then
4791 if Is_Array_Type (E)
4792 and then Denotes_Previous_Actual (Component_Type (E))
4793 then
4794 null;
4795 else
4796 Check_Private_View (Subtype_Indication (Parent (E)));
4797 end if;
4798 Set_Is_Generic_Actual_Type (E, True);
4799 Set_Is_Hidden (E, False);
4800 Set_Is_Potentially_Use_Visible (E,
4801 In_Use (Instance));
4803 -- We constructed the generic actual type as a subtype of the
4804 -- supplied type. This means that it normally would not inherit
4805 -- subtype specific attributes of the actual, which is wrong for
4806 -- the generic case.
4808 Astype := Ancestor_Subtype (E);
4810 if No (Astype) then
4812 -- This can happen when E is an itype that is the full view of
4813 -- a private type completed, e.g. with a constrained array. In
4814 -- that case, use the first subtype, which will carry size
4815 -- information. The base type itself is unconstrained and will
4816 -- not carry it.
4818 Astype := First_Subtype (E);
4819 end if;
4821 Set_Size_Info (E, (Astype));
4822 Set_RM_Size (E, RM_Size (Astype));
4823 Set_First_Rep_Item (E, First_Rep_Item (Astype));
4825 if Is_Discrete_Or_Fixed_Point_Type (E) then
4826 Set_RM_Size (E, RM_Size (Astype));
4828 -- In nested instances, the base type of an access actual
4829 -- may itself be private, and need to be exchanged.
4831 elsif Is_Access_Type (E)
4832 and then Is_Private_Type (Etype (E))
4833 then
4834 Check_Private_View
4835 (New_Occurrence_Of (Etype (E), Sloc (Instance)));
4836 end if;
4838 elsif Ekind (E) = E_Package then
4840 -- If this is the renaming for the current instance, we're done.
4841 -- Otherwise it is a formal package. If the corresponding formal
4842 -- was declared with a box, the (instantiations of the) generic
4843 -- formal part are also visible. Otherwise, ignore the entity
4844 -- created to validate the actuals.
4846 if Renamed_Object (E) = Instance then
4847 exit;
4849 elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
4850 null;
4852 -- The visibility of a formal of an enclosing generic is already
4853 -- correct.
4855 elsif Denotes_Formal_Package (E) then
4856 null;
4858 elsif Present (Associated_Formal_Package (E))
4859 and then not Is_Generic_Formal (E)
4860 then
4861 if Box_Present (Parent (Associated_Formal_Package (E))) then
4862 Check_Generic_Actuals (Renamed_Object (E), True);
4864 else
4865 Check_Generic_Actuals (Renamed_Object (E), False);
4866 end if;
4868 Set_Is_Hidden (E, False);
4869 end if;
4871 -- If this is a subprogram instance (in a wrapper package) the
4872 -- actual is fully visible.
4874 elsif Is_Wrapper_Package (Instance) then
4875 Set_Is_Hidden (E, False);
4877 -- If the formal package is declared with a box, or if the formal
4878 -- parameter is defaulted, it is visible in the body.
4880 elsif Is_Formal_Box
4881 or else Is_Visible_Formal (E)
4882 then
4883 Set_Is_Hidden (E, False);
4884 end if;
4886 Next_Entity (E);
4887 end loop;
4888 end Check_Generic_Actuals;
4890 ------------------------------
4891 -- Check_Generic_Child_Unit --
4892 ------------------------------
4894 procedure Check_Generic_Child_Unit
4895 (Gen_Id : Node_Id;
4896 Parent_Installed : in out Boolean)
4898 Loc : constant Source_Ptr := Sloc (Gen_Id);
4899 Gen_Par : Entity_Id := Empty;
4900 E : Entity_Id;
4901 Inst_Par : Entity_Id;
4902 S : Node_Id;
4904 function Find_Generic_Child
4905 (Scop : Entity_Id;
4906 Id : Node_Id) return Entity_Id;
4907 -- Search generic parent for possible child unit with the given name
4909 function In_Enclosing_Instance return Boolean;
4910 -- Within an instance of the parent, the child unit may be denoted
4911 -- by a simple name, or an abbreviated expanded name. Examine enclosing
4912 -- scopes to locate a possible parent instantiation.
4914 ------------------------
4915 -- Find_Generic_Child --
4916 ------------------------
4918 function Find_Generic_Child
4919 (Scop : Entity_Id;
4920 Id : Node_Id) return Entity_Id
4922 E : Entity_Id;
4924 begin
4925 -- If entity of name is already set, instance has already been
4926 -- resolved, e.g. in an enclosing instantiation.
4928 if Present (Entity (Id)) then
4929 if Scope (Entity (Id)) = Scop then
4930 return Entity (Id);
4931 else
4932 return Empty;
4933 end if;
4935 else
4936 E := First_Entity (Scop);
4937 while Present (E) loop
4938 if Chars (E) = Chars (Id)
4939 and then Is_Child_Unit (E)
4940 then
4941 if Is_Child_Unit (E)
4942 and then not Is_Visible_Child_Unit (E)
4943 then
4944 Error_Msg_NE
4945 ("generic child unit& is not visible", Gen_Id, E);
4946 end if;
4948 Set_Entity (Id, E);
4949 return E;
4950 end if;
4952 Next_Entity (E);
4953 end loop;
4955 return Empty;
4956 end if;
4957 end Find_Generic_Child;
4959 ---------------------------
4960 -- In_Enclosing_Instance --
4961 ---------------------------
4963 function In_Enclosing_Instance return Boolean is
4964 Enclosing_Instance : Node_Id;
4965 Instance_Decl : Node_Id;
4967 begin
4968 -- We do not inline any call that contains instantiations, except
4969 -- for instantiations of Unchecked_Conversion, so if we are within
4970 -- an inlined body the current instance does not require parents.
4972 if In_Inlined_Body then
4973 pragma Assert (Chars (Gen_Id) = Name_Unchecked_Conversion);
4974 return False;
4975 end if;
4977 -- Loop to check enclosing scopes
4979 Enclosing_Instance := Current_Scope;
4980 while Present (Enclosing_Instance) loop
4981 Instance_Decl := Unit_Declaration_Node (Enclosing_Instance);
4983 if Ekind (Enclosing_Instance) = E_Package
4984 and then Is_Generic_Instance (Enclosing_Instance)
4985 and then Present
4986 (Generic_Parent (Specification (Instance_Decl)))
4987 then
4988 -- Check whether the generic we are looking for is a child of
4989 -- this instance.
4991 E := Find_Generic_Child
4992 (Generic_Parent (Specification (Instance_Decl)), Gen_Id);
4993 exit when Present (E);
4995 else
4996 E := Empty;
4997 end if;
4999 Enclosing_Instance := Scope (Enclosing_Instance);
5000 end loop;
5002 if No (E) then
5004 -- Not a child unit
5006 Analyze (Gen_Id);
5007 return False;
5009 else
5010 Rewrite (Gen_Id,
5011 Make_Expanded_Name (Loc,
5012 Chars => Chars (E),
5013 Prefix => New_Occurrence_Of (Enclosing_Instance, Loc),
5014 Selector_Name => New_Occurrence_Of (E, Loc)));
5016 Set_Entity (Gen_Id, E);
5017 Set_Etype (Gen_Id, Etype (E));
5018 Parent_Installed := False; -- Already in scope.
5019 return True;
5020 end if;
5021 end In_Enclosing_Instance;
5023 -- Start of processing for Check_Generic_Child_Unit
5025 begin
5026 -- If the name of the generic is given by a selected component, it may
5027 -- be the name of a generic child unit, and the prefix is the name of an
5028 -- instance of the parent, in which case the child unit must be visible.
5029 -- If this instance is not in scope, it must be placed there and removed
5030 -- after instantiation, because what is being instantiated is not the
5031 -- original child, but the corresponding child present in the instance
5032 -- of the parent.
5034 -- If the child is instantiated within the parent, it can be given by
5035 -- a simple name. In this case the instance is already in scope, but
5036 -- the child generic must be recovered from the generic parent as well.
5038 if Nkind (Gen_Id) = N_Selected_Component then
5039 S := Selector_Name (Gen_Id);
5040 Analyze (Prefix (Gen_Id));
5041 Inst_Par := Entity (Prefix (Gen_Id));
5043 if Ekind (Inst_Par) = E_Package
5044 and then Present (Renamed_Object (Inst_Par))
5045 then
5046 Inst_Par := Renamed_Object (Inst_Par);
5047 end if;
5049 if Ekind (Inst_Par) = E_Package then
5050 if Nkind (Parent (Inst_Par)) = N_Package_Specification then
5051 Gen_Par := Generic_Parent (Parent (Inst_Par));
5053 elsif Nkind (Parent (Inst_Par)) = N_Defining_Program_Unit_Name
5054 and then
5055 Nkind (Parent (Parent (Inst_Par))) = N_Package_Specification
5056 then
5057 Gen_Par := Generic_Parent (Parent (Parent (Inst_Par)));
5058 end if;
5060 elsif Ekind (Inst_Par) = E_Generic_Package
5061 and then Nkind (Parent (Gen_Id)) = N_Formal_Package_Declaration
5062 then
5063 -- A formal package may be a real child package, and not the
5064 -- implicit instance within a parent. In this case the child is
5065 -- not visible and has to be retrieved explicitly as well.
5067 Gen_Par := Inst_Par;
5068 end if;
5070 if Present (Gen_Par) then
5072 -- The prefix denotes an instantiation. The entity itself may be a
5073 -- nested generic, or a child unit.
5075 E := Find_Generic_Child (Gen_Par, S);
5077 if Present (E) then
5078 Change_Selected_Component_To_Expanded_Name (Gen_Id);
5079 Set_Entity (Gen_Id, E);
5080 Set_Etype (Gen_Id, Etype (E));
5081 Set_Entity (S, E);
5082 Set_Etype (S, Etype (E));
5084 -- Indicate that this is a reference to the parent
5086 if In_Extended_Main_Source_Unit (Gen_Id) then
5087 Set_Is_Instantiated (Inst_Par);
5088 end if;
5090 -- A common mistake is to replicate the naming scheme of a
5091 -- hierarchy by instantiating a generic child directly, rather
5092 -- than the implicit child in a parent instance:
5094 -- generic .. package Gpar is ..
5095 -- generic .. package Gpar.Child is ..
5096 -- package Par is new Gpar ();
5098 -- with Gpar.Child;
5099 -- package Par.Child is new Gpar.Child ();
5100 -- rather than Par.Child
5102 -- In this case the instantiation is within Par, which is an
5103 -- instance, but Gpar does not denote Par because we are not IN
5104 -- the instance of Gpar, so this is illegal. The test below
5105 -- recognizes this particular case.
5107 if Is_Child_Unit (E)
5108 and then not Comes_From_Source (Entity (Prefix (Gen_Id)))
5109 and then (not In_Instance
5110 or else Nkind (Parent (Parent (Gen_Id))) =
5111 N_Compilation_Unit)
5112 then
5113 Error_Msg_N
5114 ("prefix of generic child unit must be instance of parent",
5115 Gen_Id);
5116 end if;
5118 if not In_Open_Scopes (Inst_Par)
5119 and then Nkind (Parent (Gen_Id)) not in
5120 N_Generic_Renaming_Declaration
5121 then
5122 Install_Parent (Inst_Par);
5123 Parent_Installed := True;
5125 elsif In_Open_Scopes (Inst_Par) then
5127 -- If the parent is already installed verify that the
5128 -- actuals for its formal packages declared with a box
5129 -- are already installed. This is necessary when the
5130 -- child instance is a child of the parent instance.
5131 -- In this case the parent is placed on the scope stack
5132 -- but the formal packages are not made visible.
5134 Install_Formal_Packages (Inst_Par);
5135 end if;
5137 else
5138 -- If the generic parent does not contain an entity that
5139 -- corresponds to the selector, the instance doesn't either.
5140 -- Analyzing the node will yield the appropriate error message.
5141 -- If the entity is not a child unit, then it is an inner
5142 -- generic in the parent.
5144 Analyze (Gen_Id);
5145 end if;
5147 else
5148 Analyze (Gen_Id);
5150 if Is_Child_Unit (Entity (Gen_Id))
5151 and then
5152 Nkind (Parent (Gen_Id)) not in N_Generic_Renaming_Declaration
5153 and then not In_Open_Scopes (Inst_Par)
5154 then
5155 Install_Parent (Inst_Par);
5156 Parent_Installed := True;
5157 end if;
5158 end if;
5160 elsif Nkind (Gen_Id) = N_Expanded_Name then
5162 -- Entity already present, analyze prefix, whose meaning may be
5163 -- an instance in the current context. If it is an instance of
5164 -- a relative within another, the proper parent may still have
5165 -- to be installed, if they are not of the same generation.
5167 Analyze (Prefix (Gen_Id));
5169 -- In the unlikely case that a local declaration hides the name
5170 -- of the parent package, locate it on the homonym chain. If the
5171 -- context is an instance of the parent, the renaming entity is
5172 -- flagged as such.
5174 Inst_Par := Entity (Prefix (Gen_Id));
5175 while Present (Inst_Par)
5176 and then Ekind (Inst_Par) /= E_Package
5177 and then Ekind (Inst_Par) /= E_Generic_Package
5178 loop
5179 Inst_Par := Homonym (Inst_Par);
5180 end loop;
5182 pragma Assert (Present (Inst_Par));
5183 Set_Entity (Prefix (Gen_Id), Inst_Par);
5185 if In_Enclosing_Instance then
5186 null;
5188 elsif Present (Entity (Gen_Id))
5189 and then Is_Child_Unit (Entity (Gen_Id))
5190 and then not In_Open_Scopes (Inst_Par)
5191 then
5192 Install_Parent (Inst_Par);
5193 Parent_Installed := True;
5194 end if;
5196 elsif In_Enclosing_Instance then
5198 -- The child unit is found in some enclosing scope
5200 null;
5202 else
5203 Analyze (Gen_Id);
5205 -- If this is the renaming of the implicit child in a parent
5206 -- instance, recover the parent name and install it.
5208 if Is_Entity_Name (Gen_Id) then
5209 E := Entity (Gen_Id);
5211 if Is_Generic_Unit (E)
5212 and then Nkind (Parent (E)) in N_Generic_Renaming_Declaration
5213 and then Is_Child_Unit (Renamed_Object (E))
5214 and then Is_Generic_Unit (Scope (Renamed_Object (E)))
5215 and then Nkind (Name (Parent (E))) = N_Expanded_Name
5216 then
5217 Rewrite (Gen_Id,
5218 New_Copy_Tree (Name (Parent (E))));
5219 Inst_Par := Entity (Prefix (Gen_Id));
5221 if not In_Open_Scopes (Inst_Par) then
5222 Install_Parent (Inst_Par);
5223 Parent_Installed := True;
5224 end if;
5226 -- If it is a child unit of a non-generic parent, it may be
5227 -- use-visible and given by a direct name. Install parent as
5228 -- for other cases.
5230 elsif Is_Generic_Unit (E)
5231 and then Is_Child_Unit (E)
5232 and then
5233 Nkind (Parent (Gen_Id)) not in N_Generic_Renaming_Declaration
5234 and then not Is_Generic_Unit (Scope (E))
5235 then
5236 if not In_Open_Scopes (Scope (E)) then
5237 Install_Parent (Scope (E));
5238 Parent_Installed := True;
5239 end if;
5240 end if;
5241 end if;
5242 end if;
5243 end Check_Generic_Child_Unit;
5245 -----------------------------
5246 -- Check_Hidden_Child_Unit --
5247 -----------------------------
5249 procedure Check_Hidden_Child_Unit
5250 (N : Node_Id;
5251 Gen_Unit : Entity_Id;
5252 Act_Decl_Id : Entity_Id)
5254 Gen_Id : constant Node_Id := Name (N);
5256 begin
5257 if Is_Child_Unit (Gen_Unit)
5258 and then Is_Child_Unit (Act_Decl_Id)
5259 and then Nkind (Gen_Id) = N_Expanded_Name
5260 and then Entity (Prefix (Gen_Id)) = Scope (Act_Decl_Id)
5261 and then Chars (Gen_Unit) = Chars (Act_Decl_Id)
5262 then
5263 Error_Msg_Node_2 := Scope (Act_Decl_Id);
5264 Error_Msg_NE
5265 ("generic unit & is implicitly declared in &",
5266 Defining_Unit_Name (N), Gen_Unit);
5267 Error_Msg_N ("\instance must have different name",
5268 Defining_Unit_Name (N));
5269 end if;
5270 end Check_Hidden_Child_Unit;
5272 ------------------------
5273 -- Check_Private_View --
5274 ------------------------
5276 procedure Check_Private_View (N : Node_Id) is
5277 T : constant Entity_Id := Etype (N);
5278 BT : Entity_Id;
5280 begin
5281 -- Exchange views if the type was not private in the generic but is
5282 -- private at the point of instantiation. Do not exchange views if
5283 -- the scope of the type is in scope. This can happen if both generic
5284 -- and instance are sibling units, or if type is defined in a parent.
5285 -- In this case the visibility of the type will be correct for all
5286 -- semantic checks.
5288 if Present (T) then
5289 BT := Base_Type (T);
5291 if Is_Private_Type (T)
5292 and then not Has_Private_View (N)
5293 and then Present (Full_View (T))
5294 and then not In_Open_Scopes (Scope (T))
5295 then
5296 -- In the generic, the full type was visible. Save the private
5297 -- entity, for subsequent exchange.
5299 Switch_View (T);
5301 elsif Has_Private_View (N)
5302 and then not Is_Private_Type (T)
5303 and then not Has_Been_Exchanged (T)
5304 and then Etype (Get_Associated_Node (N)) /= T
5305 then
5306 -- Only the private declaration was visible in the generic. If
5307 -- the type appears in a subtype declaration, the subtype in the
5308 -- instance must have a view compatible with that of its parent,
5309 -- which must be exchanged (see corresponding code in Restore_
5310 -- Private_Views). Otherwise, if the type is defined in a parent
5311 -- unit, leave full visibility within instance, which is safe.
5313 if In_Open_Scopes (Scope (Base_Type (T)))
5314 and then not Is_Private_Type (Base_Type (T))
5315 and then Comes_From_Source (Base_Type (T))
5316 then
5317 null;
5319 elsif Nkind (Parent (N)) = N_Subtype_Declaration
5320 or else not In_Private_Part (Scope (Base_Type (T)))
5321 then
5322 Prepend_Elmt (T, Exchanged_Views);
5323 Exchange_Declarations (Etype (Get_Associated_Node (N)));
5324 end if;
5326 -- For composite types with inconsistent representation exchange
5327 -- component types accordingly.
5329 elsif Is_Access_Type (T)
5330 and then Is_Private_Type (Designated_Type (T))
5331 and then not Has_Private_View (N)
5332 and then Present (Full_View (Designated_Type (T)))
5333 then
5334 Switch_View (Designated_Type (T));
5336 elsif Is_Array_Type (T) then
5337 if Is_Private_Type (Component_Type (T))
5338 and then not Has_Private_View (N)
5339 and then Present (Full_View (Component_Type (T)))
5340 then
5341 Switch_View (Component_Type (T));
5342 end if;
5344 -- The normal exchange mechanism relies on the setting of a
5345 -- flag on the reference in the generic. However, an additional
5346 -- mechanism is needed for types that are not explicitly mentioned
5347 -- in the generic, but may be needed in expanded code in the
5348 -- instance. This includes component types of arrays and
5349 -- designated types of access types. This processing must also
5350 -- include the index types of arrays which we take care of here.
5352 declare
5353 Indx : Node_Id;
5354 Typ : Entity_Id;
5356 begin
5357 Indx := First_Index (T);
5358 Typ := Base_Type (Etype (Indx));
5359 while Present (Indx) loop
5360 if Is_Private_Type (Typ)
5361 and then Present (Full_View (Typ))
5362 then
5363 Switch_View (Typ);
5364 end if;
5366 Next_Index (Indx);
5367 end loop;
5368 end;
5370 elsif Is_Private_Type (T)
5371 and then Present (Full_View (T))
5372 and then Is_Array_Type (Full_View (T))
5373 and then Is_Private_Type (Component_Type (Full_View (T)))
5374 then
5375 Switch_View (T);
5377 -- Finally, a non-private subtype may have a private base type, which
5378 -- must be exchanged for consistency. This can happen when a package
5379 -- body is instantiated, when the scope stack is empty but in fact
5380 -- the subtype and the base type are declared in an enclosing scope.
5382 -- Note that in this case we introduce an inconsistency in the view
5383 -- set, because we switch the base type BT, but there could be some
5384 -- private dependent subtypes of BT which remain unswitched. Such
5385 -- subtypes might need to be switched at a later point (see specific
5386 -- provision for that case in Switch_View).
5388 elsif not Is_Private_Type (T)
5389 and then not Has_Private_View (N)
5390 and then Is_Private_Type (BT)
5391 and then Present (Full_View (BT))
5392 and then not Is_Generic_Type (BT)
5393 and then not In_Open_Scopes (BT)
5394 then
5395 Prepend_Elmt (Full_View (BT), Exchanged_Views);
5396 Exchange_Declarations (BT);
5397 end if;
5398 end if;
5399 end Check_Private_View;
5401 --------------------------
5402 -- Contains_Instance_Of --
5403 --------------------------
5405 function Contains_Instance_Of
5406 (Inner : Entity_Id;
5407 Outer : Entity_Id;
5408 N : Node_Id) return Boolean
5410 Elmt : Elmt_Id;
5411 Scop : Entity_Id;
5413 begin
5414 Scop := Outer;
5416 -- Verify that there are no circular instantiations. We check whether
5417 -- the unit contains an instance of the current scope or some enclosing
5418 -- scope (in case one of the instances appears in a subunit). Longer
5419 -- circularities involving subunits might seem too pathological to
5420 -- consider, but they were not too pathological for the authors of
5421 -- DEC bc30vsq, so we loop over all enclosing scopes, and mark all
5422 -- enclosing generic scopes as containing an instance.
5424 loop
5425 -- Within a generic subprogram body, the scope is not generic, to
5426 -- allow for recursive subprograms. Use the declaration to determine
5427 -- whether this is a generic unit.
5429 if Ekind (Scop) = E_Generic_Package
5430 or else (Is_Subprogram (Scop)
5431 and then Nkind (Unit_Declaration_Node (Scop)) =
5432 N_Generic_Subprogram_Declaration)
5433 then
5434 Elmt := First_Elmt (Inner_Instances (Inner));
5436 while Present (Elmt) loop
5437 if Node (Elmt) = Scop then
5438 Error_Msg_Node_2 := Inner;
5439 Error_Msg_NE
5440 ("circular Instantiation: & instantiated within &!",
5441 N, Scop);
5442 return True;
5444 elsif Node (Elmt) = Inner then
5445 return True;
5447 elsif Contains_Instance_Of (Node (Elmt), Scop, N) then
5448 Error_Msg_Node_2 := Inner;
5449 Error_Msg_NE
5450 ("circular Instantiation: & instantiated within &!",
5451 N, Node (Elmt));
5452 return True;
5453 end if;
5455 Next_Elmt (Elmt);
5456 end loop;
5458 -- Indicate that Inner is being instantiated within Scop
5460 Append_Elmt (Inner, Inner_Instances (Scop));
5461 end if;
5463 if Scop = Standard_Standard then
5464 exit;
5465 else
5466 Scop := Scope (Scop);
5467 end if;
5468 end loop;
5470 return False;
5471 end Contains_Instance_Of;
5473 -----------------------
5474 -- Copy_Generic_Node --
5475 -----------------------
5477 function Copy_Generic_Node
5478 (N : Node_Id;
5479 Parent_Id : Node_Id;
5480 Instantiating : Boolean) return Node_Id
5482 Ent : Entity_Id;
5483 New_N : Node_Id;
5485 function Copy_Generic_Descendant (D : Union_Id) return Union_Id;
5486 -- Check the given value of one of the Fields referenced by the
5487 -- current node to determine whether to copy it recursively. The
5488 -- field may hold a Node_Id, a List_Id, or an Elist_Id, or a plain
5489 -- value (Sloc, Uint, Char) in which case it need not be copied.
5491 procedure Copy_Descendants;
5492 -- Common utility for various nodes
5494 function Copy_Generic_Elist (E : Elist_Id) return Elist_Id;
5495 -- Make copy of element list
5497 function Copy_Generic_List
5498 (L : List_Id;
5499 Parent_Id : Node_Id) return List_Id;
5500 -- Apply Copy_Node recursively to the members of a node list
5502 function In_Defining_Unit_Name (Nam : Node_Id) return Boolean;
5503 -- True if an identifier is part of the defining program unit name
5504 -- of a child unit. The entity of such an identifier must be kept
5505 -- (for ASIS use) even though as the name of an enclosing generic
5506 -- it would otherwise not be preserved in the generic tree.
5508 ----------------------
5509 -- Copy_Descendants --
5510 ----------------------
5512 procedure Copy_Descendants is
5514 use Atree.Unchecked_Access;
5515 -- This code section is part of the implementation of an untyped
5516 -- tree traversal, so it needs direct access to node fields.
5518 begin
5519 Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
5520 Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
5521 Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
5522 Set_Field4 (New_N, Copy_Generic_Descendant (Field4 (N)));
5523 Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
5524 end Copy_Descendants;
5526 -----------------------------
5527 -- Copy_Generic_Descendant --
5528 -----------------------------
5530 function Copy_Generic_Descendant (D : Union_Id) return Union_Id is
5531 begin
5532 if D = Union_Id (Empty) then
5533 return D;
5535 elsif D in Node_Range then
5536 return Union_Id
5537 (Copy_Generic_Node (Node_Id (D), New_N, Instantiating));
5539 elsif D in List_Range then
5540 return Union_Id (Copy_Generic_List (List_Id (D), New_N));
5542 elsif D in Elist_Range then
5543 return Union_Id (Copy_Generic_Elist (Elist_Id (D)));
5545 -- Nothing else is copyable (e.g. Uint values), return as is
5547 else
5548 return D;
5549 end if;
5550 end Copy_Generic_Descendant;
5552 ------------------------
5553 -- Copy_Generic_Elist --
5554 ------------------------
5556 function Copy_Generic_Elist (E : Elist_Id) return Elist_Id is
5557 M : Elmt_Id;
5558 L : Elist_Id;
5560 begin
5561 if Present (E) then
5562 L := New_Elmt_List;
5563 M := First_Elmt (E);
5564 while Present (M) loop
5565 Append_Elmt
5566 (Copy_Generic_Node (Node (M), Empty, Instantiating), L);
5567 Next_Elmt (M);
5568 end loop;
5570 return L;
5572 else
5573 return No_Elist;
5574 end if;
5575 end Copy_Generic_Elist;
5577 -----------------------
5578 -- Copy_Generic_List --
5579 -----------------------
5581 function Copy_Generic_List
5582 (L : List_Id;
5583 Parent_Id : Node_Id) return List_Id
5585 N : Node_Id;
5586 New_L : List_Id;
5588 begin
5589 if Present (L) then
5590 New_L := New_List;
5591 Set_Parent (New_L, Parent_Id);
5593 N := First (L);
5594 while Present (N) loop
5595 Append (Copy_Generic_Node (N, Empty, Instantiating), New_L);
5596 Next (N);
5597 end loop;
5599 return New_L;
5601 else
5602 return No_List;
5603 end if;
5604 end Copy_Generic_List;
5606 ---------------------------
5607 -- In_Defining_Unit_Name --
5608 ---------------------------
5610 function In_Defining_Unit_Name (Nam : Node_Id) return Boolean is
5611 begin
5612 return Present (Parent (Nam))
5613 and then (Nkind (Parent (Nam)) = N_Defining_Program_Unit_Name
5614 or else
5615 (Nkind (Parent (Nam)) = N_Expanded_Name
5616 and then In_Defining_Unit_Name (Parent (Nam))));
5617 end In_Defining_Unit_Name;
5619 -- Start of processing for Copy_Generic_Node
5621 begin
5622 if N = Empty then
5623 return N;
5624 end if;
5626 New_N := New_Copy (N);
5628 if Instantiating then
5629 Adjust_Instantiation_Sloc (New_N, S_Adjustment);
5630 end if;
5632 if not Is_List_Member (N) then
5633 Set_Parent (New_N, Parent_Id);
5634 end if;
5636 -- If defining identifier, then all fields have been copied already
5638 if Nkind (New_N) in N_Entity then
5639 null;
5641 -- Special casing for identifiers and other entity names and operators
5643 elsif Nkind_In (New_N, N_Identifier,
5644 N_Character_Literal,
5645 N_Expanded_Name,
5646 N_Operator_Symbol)
5647 or else Nkind (New_N) in N_Op
5648 then
5649 if not Instantiating then
5651 -- Link both nodes in order to assign subsequently the
5652 -- entity of the copy to the original node, in case this
5653 -- is a global reference.
5655 Set_Associated_Node (N, New_N);
5657 -- If we are within an instantiation, this is a nested generic
5658 -- that has already been analyzed at the point of definition. We
5659 -- must preserve references that were global to the enclosing
5660 -- parent at that point. Other occurrences, whether global or
5661 -- local to the current generic, must be resolved anew, so we
5662 -- reset the entity in the generic copy. A global reference has a
5663 -- smaller depth than the parent, or else the same depth in case
5664 -- both are distinct compilation units.
5665 -- A child unit is implicitly declared within the enclosing parent
5666 -- but is in fact global to it, and must be preserved.
5668 -- It is also possible for Current_Instantiated_Parent to be
5669 -- defined, and for this not to be a nested generic, namely if the
5670 -- unit is loaded through Rtsfind. In that case, the entity of
5671 -- New_N is only a link to the associated node, and not a defining
5672 -- occurrence.
5674 -- The entities for parent units in the defining_program_unit of a
5675 -- generic child unit are established when the context of the unit
5676 -- is first analyzed, before the generic copy is made. They are
5677 -- preserved in the copy for use in ASIS queries.
5679 Ent := Entity (New_N);
5681 if No (Current_Instantiated_Parent.Gen_Id) then
5682 if No (Ent)
5683 or else Nkind (Ent) /= N_Defining_Identifier
5684 or else not In_Defining_Unit_Name (N)
5685 then
5686 Set_Associated_Node (New_N, Empty);
5687 end if;
5689 elsif No (Ent)
5690 or else
5691 not Nkind_In (Ent, N_Defining_Identifier,
5692 N_Defining_Character_Literal,
5693 N_Defining_Operator_Symbol)
5694 or else No (Scope (Ent))
5695 or else
5696 (Scope (Ent) = Current_Instantiated_Parent.Gen_Id
5697 and then not Is_Child_Unit (Ent))
5698 or else
5699 (Scope_Depth (Scope (Ent)) >
5700 Scope_Depth (Current_Instantiated_Parent.Gen_Id)
5701 and then
5702 Get_Source_Unit (Ent) =
5703 Get_Source_Unit (Current_Instantiated_Parent.Gen_Id))
5704 then
5705 Set_Associated_Node (New_N, Empty);
5706 end if;
5708 -- Case of instantiating identifier or some other name or operator
5710 else
5711 -- If the associated node is still defined, the entity in it is
5712 -- global, and must be copied to the instance. If this copy is
5713 -- being made for a body to inline, it is applied to an
5714 -- instantiated tree, and the entity is already present and must
5715 -- be also preserved.
5717 declare
5718 Assoc : constant Node_Id := Get_Associated_Node (N);
5720 begin
5721 if Present (Assoc) then
5722 if Nkind (Assoc) = Nkind (N) then
5723 Set_Entity (New_N, Entity (Assoc));
5724 Check_Private_View (N);
5726 elsif Nkind (Assoc) = N_Function_Call then
5727 Set_Entity (New_N, Entity (Name (Assoc)));
5729 elsif Nkind_In (Assoc, N_Defining_Identifier,
5730 N_Defining_Character_Literal,
5731 N_Defining_Operator_Symbol)
5732 and then Expander_Active
5733 then
5734 -- Inlining case: we are copying a tree that contains
5735 -- global entities, which are preserved in the copy to be
5736 -- used for subsequent inlining.
5738 null;
5740 else
5741 Set_Entity (New_N, Empty);
5742 end if;
5743 end if;
5744 end;
5745 end if;
5747 -- For expanded name, we must copy the Prefix and Selector_Name
5749 if Nkind (N) = N_Expanded_Name then
5750 Set_Prefix
5751 (New_N, Copy_Generic_Node (Prefix (N), New_N, Instantiating));
5753 Set_Selector_Name (New_N,
5754 Copy_Generic_Node (Selector_Name (N), New_N, Instantiating));
5756 -- For operators, we must copy the right operand
5758 elsif Nkind (N) in N_Op then
5759 Set_Right_Opnd (New_N,
5760 Copy_Generic_Node (Right_Opnd (N), New_N, Instantiating));
5762 -- And for binary operators, the left operand as well
5764 if Nkind (N) in N_Binary_Op then
5765 Set_Left_Opnd (New_N,
5766 Copy_Generic_Node (Left_Opnd (N), New_N, Instantiating));
5767 end if;
5768 end if;
5770 -- Special casing for stubs
5772 elsif Nkind (N) in N_Body_Stub then
5774 -- In any case, we must copy the specification or defining
5775 -- identifier as appropriate.
5777 if Nkind (N) = N_Subprogram_Body_Stub then
5778 Set_Specification (New_N,
5779 Copy_Generic_Node (Specification (N), New_N, Instantiating));
5781 else
5782 Set_Defining_Identifier (New_N,
5783 Copy_Generic_Node
5784 (Defining_Identifier (N), New_N, Instantiating));
5785 end if;
5787 -- If we are not instantiating, then this is where we load and
5788 -- analyze subunits, i.e. at the point where the stub occurs. A
5789 -- more permissible system might defer this analysis to the point
5790 -- of instantiation, but this seems to complicated for now.
5792 if not Instantiating then
5793 declare
5794 Subunit_Name : constant Unit_Name_Type := Get_Unit_Name (N);
5795 Subunit : Node_Id;
5796 Unum : Unit_Number_Type;
5797 New_Body : Node_Id;
5799 begin
5800 Unum :=
5801 Load_Unit
5802 (Load_Name => Subunit_Name,
5803 Required => False,
5804 Subunit => True,
5805 Error_Node => N);
5807 -- If the proper body is not found, a warning message will be
5808 -- emitted when analyzing the stub, or later at the point
5809 -- of instantiation. Here we just leave the stub as is.
5811 if Unum = No_Unit then
5812 Subunits_Missing := True;
5813 goto Subunit_Not_Found;
5814 end if;
5816 Subunit := Cunit (Unum);
5818 if Nkind (Unit (Subunit)) /= N_Subunit then
5819 Error_Msg_N
5820 ("found child unit instead of expected SEPARATE subunit",
5821 Subunit);
5822 Error_Msg_Sloc := Sloc (N);
5823 Error_Msg_N ("\to complete stub #", Subunit);
5824 goto Subunit_Not_Found;
5825 end if;
5827 -- We must create a generic copy of the subunit, in order to
5828 -- perform semantic analysis on it, and we must replace the
5829 -- stub in the original generic unit with the subunit, in order
5830 -- to preserve non-local references within.
5832 -- Only the proper body needs to be copied. Library_Unit and
5833 -- context clause are simply inherited by the generic copy.
5834 -- Note that the copy (which may be recursive if there are
5835 -- nested subunits) must be done first, before attaching it to
5836 -- the enclosing generic.
5838 New_Body :=
5839 Copy_Generic_Node
5840 (Proper_Body (Unit (Subunit)),
5841 Empty, Instantiating => False);
5843 -- Now place the original proper body in the original generic
5844 -- unit. This is a body, not a compilation unit.
5846 Rewrite (N, Proper_Body (Unit (Subunit)));
5847 Set_Is_Compilation_Unit (Defining_Entity (N), False);
5848 Set_Was_Originally_Stub (N);
5850 -- Finally replace the body of the subunit with its copy, and
5851 -- make this new subunit into the library unit of the generic
5852 -- copy, which does not have stubs any longer.
5854 Set_Proper_Body (Unit (Subunit), New_Body);
5855 Set_Library_Unit (New_N, Subunit);
5856 Inherit_Context (Unit (Subunit), N);
5857 end;
5859 -- If we are instantiating, this must be an error case, since
5860 -- otherwise we would have replaced the stub node by the proper body
5861 -- that corresponds. So just ignore it in the copy (i.e. we have
5862 -- copied it, and that is good enough).
5864 else
5865 null;
5866 end if;
5868 <<Subunit_Not_Found>> null;
5870 -- If the node is a compilation unit, it is the subunit of a stub, which
5871 -- has been loaded already (see code below). In this case, the library
5872 -- unit field of N points to the parent unit (which is a compilation
5873 -- unit) and need not (and cannot!) be copied.
5875 -- When the proper body of the stub is analyzed, the library_unit link
5876 -- is used to establish the proper context (see sem_ch10).
5878 -- The other fields of a compilation unit are copied as usual
5880 elsif Nkind (N) = N_Compilation_Unit then
5882 -- This code can only be executed when not instantiating, because in
5883 -- the copy made for an instantiation, the compilation unit node has
5884 -- disappeared at the point that a stub is replaced by its proper
5885 -- body.
5887 pragma Assert (not Instantiating);
5889 Set_Context_Items (New_N,
5890 Copy_Generic_List (Context_Items (N), New_N));
5892 Set_Unit (New_N,
5893 Copy_Generic_Node (Unit (N), New_N, False));
5895 Set_First_Inlined_Subprogram (New_N,
5896 Copy_Generic_Node
5897 (First_Inlined_Subprogram (N), New_N, False));
5899 Set_Aux_Decls_Node (New_N,
5900 Copy_Generic_Node (Aux_Decls_Node (N), New_N, False));
5902 -- For an assignment node, the assignment is known to be semantically
5903 -- legal if we are instantiating the template. This avoids incorrect
5904 -- diagnostics in generated code.
5906 elsif Nkind (N) = N_Assignment_Statement then
5908 -- Copy name and expression fields in usual manner
5910 Set_Name (New_N,
5911 Copy_Generic_Node (Name (N), New_N, Instantiating));
5913 Set_Expression (New_N,
5914 Copy_Generic_Node (Expression (N), New_N, Instantiating));
5916 if Instantiating then
5917 Set_Assignment_OK (Name (New_N), True);
5918 end if;
5920 elsif Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
5921 if not Instantiating then
5922 Set_Associated_Node (N, New_N);
5924 else
5925 if Present (Get_Associated_Node (N))
5926 and then Nkind (Get_Associated_Node (N)) = Nkind (N)
5927 then
5928 -- In the generic the aggregate has some composite type. If at
5929 -- the point of instantiation the type has a private view,
5930 -- install the full view (and that of its ancestors, if any).
5932 declare
5933 T : Entity_Id := (Etype (Get_Associated_Node (New_N)));
5934 Rt : Entity_Id;
5936 begin
5937 if Present (T)
5938 and then Is_Private_Type (T)
5939 then
5940 Switch_View (T);
5941 end if;
5943 if Present (T)
5944 and then Is_Tagged_Type (T)
5945 and then Is_Derived_Type (T)
5946 then
5947 Rt := Root_Type (T);
5949 loop
5950 T := Etype (T);
5952 if Is_Private_Type (T) then
5953 Switch_View (T);
5954 end if;
5956 exit when T = Rt;
5957 end loop;
5958 end if;
5959 end;
5960 end if;
5961 end if;
5963 -- Do not copy the associated node, which points to
5964 -- the generic copy of the aggregate.
5966 declare
5967 use Atree.Unchecked_Access;
5968 -- This code section is part of the implementation of an untyped
5969 -- tree traversal, so it needs direct access to node fields.
5971 begin
5972 Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
5973 Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
5974 Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
5975 Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
5976 end;
5978 -- Allocators do not have an identifier denoting the access type,
5979 -- so we must locate it through the expression to check whether
5980 -- the views are consistent.
5982 elsif Nkind (N) = N_Allocator
5983 and then Nkind (Expression (N)) = N_Qualified_Expression
5984 and then Is_Entity_Name (Subtype_Mark (Expression (N)))
5985 and then Instantiating
5986 then
5987 declare
5988 T : constant Node_Id :=
5989 Get_Associated_Node (Subtype_Mark (Expression (N)));
5990 Acc_T : Entity_Id;
5992 begin
5993 if Present (T) then
5995 -- Retrieve the allocator node in the generic copy
5997 Acc_T := Etype (Parent (Parent (T)));
5998 if Present (Acc_T)
5999 and then Is_Private_Type (Acc_T)
6000 then
6001 Switch_View (Acc_T);
6002 end if;
6003 end if;
6005 Copy_Descendants;
6006 end;
6008 -- For a proper body, we must catch the case of a proper body that
6009 -- replaces a stub. This represents the point at which a separate
6010 -- compilation unit, and hence template file, may be referenced, so we
6011 -- must make a new source instantiation entry for the template of the
6012 -- subunit, and ensure that all nodes in the subunit are adjusted using
6013 -- this new source instantiation entry.
6015 elsif Nkind (N) in N_Proper_Body then
6016 declare
6017 Save_Adjustment : constant Sloc_Adjustment := S_Adjustment;
6019 begin
6020 if Instantiating and then Was_Originally_Stub (N) then
6021 Create_Instantiation_Source
6022 (Instantiation_Node,
6023 Defining_Entity (N),
6024 False,
6025 S_Adjustment);
6026 end if;
6028 -- Now copy the fields of the proper body, using the new
6029 -- adjustment factor if one was needed as per test above.
6031 Copy_Descendants;
6033 -- Restore the original adjustment factor in case changed
6035 S_Adjustment := Save_Adjustment;
6036 end;
6038 -- Don't copy Ident or Comment pragmas, since the comment belongs to the
6039 -- generic unit, not to the instantiating unit.
6041 elsif Nkind (N) = N_Pragma
6042 and then Instantiating
6043 then
6044 declare
6045 Prag_Id : constant Pragma_Id := Get_Pragma_Id (N);
6046 begin
6047 if Prag_Id = Pragma_Ident
6048 or else Prag_Id = Pragma_Comment
6049 then
6050 New_N := Make_Null_Statement (Sloc (N));
6051 else
6052 Copy_Descendants;
6053 end if;
6054 end;
6056 elsif Nkind_In (N, N_Integer_Literal,
6057 N_Real_Literal,
6058 N_String_Literal)
6059 then
6060 -- No descendant fields need traversing
6062 null;
6064 -- For the remaining nodes, copy recursively their descendants
6066 else
6067 Copy_Descendants;
6069 if Instantiating
6070 and then Nkind (N) = N_Subprogram_Body
6071 then
6072 Set_Generic_Parent (Specification (New_N), N);
6073 end if;
6074 end if;
6076 return New_N;
6077 end Copy_Generic_Node;
6079 ----------------------------
6080 -- Denotes_Formal_Package --
6081 ----------------------------
6083 function Denotes_Formal_Package
6084 (Pack : Entity_Id;
6085 On_Exit : Boolean := False) return Boolean
6087 Par : Entity_Id;
6088 Scop : constant Entity_Id := Scope (Pack);
6089 E : Entity_Id;
6091 begin
6092 if On_Exit then
6093 Par :=
6094 Instance_Envs.Table
6095 (Instance_Envs.Last).Instantiated_Parent.Act_Id;
6096 else
6097 Par := Current_Instantiated_Parent.Act_Id;
6098 end if;
6100 if Ekind (Scop) = E_Generic_Package
6101 or else Nkind (Unit_Declaration_Node (Scop)) =
6102 N_Generic_Subprogram_Declaration
6103 then
6104 return True;
6106 elsif Nkind (Original_Node (Unit_Declaration_Node (Pack))) =
6107 N_Formal_Package_Declaration
6108 then
6109 return True;
6111 elsif No (Par) then
6112 return False;
6114 else
6115 -- Check whether this package is associated with a formal package of
6116 -- the enclosing instantiation. Iterate over the list of renamings.
6118 E := First_Entity (Par);
6119 while Present (E) loop
6120 if Ekind (E) /= E_Package
6121 or else Nkind (Parent (E)) /= N_Package_Renaming_Declaration
6122 then
6123 null;
6125 elsif Renamed_Object (E) = Par then
6126 return False;
6128 elsif Renamed_Object (E) = Pack then
6129 return True;
6130 end if;
6132 Next_Entity (E);
6133 end loop;
6135 return False;
6136 end if;
6137 end Denotes_Formal_Package;
6139 -----------------
6140 -- End_Generic --
6141 -----------------
6143 procedure End_Generic is
6144 begin
6145 -- ??? More things could be factored out in this routine. Should
6146 -- probably be done at a later stage.
6148 Inside_A_Generic := Generic_Flags.Table (Generic_Flags.Last);
6149 Generic_Flags.Decrement_Last;
6151 Expander_Mode_Restore;
6152 end End_Generic;
6154 ----------------------
6155 -- Find_Actual_Type --
6156 ----------------------
6158 function Find_Actual_Type
6159 (Typ : Entity_Id;
6160 Gen_Type : Entity_Id) return Entity_Id
6162 Gen_Scope : constant Entity_Id := Scope (Gen_Type);
6163 T : Entity_Id;
6165 begin
6166 -- Special processing only applies to child units
6168 if not Is_Child_Unit (Gen_Scope) then
6169 return Get_Instance_Of (Typ);
6171 -- If designated or component type is itself a formal of the child unit,
6172 -- its instance is available.
6174 elsif Scope (Typ) = Gen_Scope then
6175 return Get_Instance_Of (Typ);
6177 -- If the array or access type is not declared in the parent unit,
6178 -- no special processing needed.
6180 elsif not Is_Generic_Type (Typ)
6181 and then Scope (Gen_Scope) /= Scope (Typ)
6182 then
6183 return Get_Instance_Of (Typ);
6185 -- Otherwise, retrieve designated or component type by visibility
6187 else
6188 T := Current_Entity (Typ);
6189 while Present (T) loop
6190 if In_Open_Scopes (Scope (T)) then
6191 return T;
6193 elsif Is_Generic_Actual_Type (T) then
6194 return T;
6195 end if;
6197 T := Homonym (T);
6198 end loop;
6200 return Typ;
6201 end if;
6202 end Find_Actual_Type;
6204 ----------------------------
6205 -- Freeze_Subprogram_Body --
6206 ----------------------------
6208 procedure Freeze_Subprogram_Body
6209 (Inst_Node : Node_Id;
6210 Gen_Body : Node_Id;
6211 Pack_Id : Entity_Id)
6213 F_Node : Node_Id;
6214 Gen_Unit : constant Entity_Id := Get_Generic_Entity (Inst_Node);
6215 Par : constant Entity_Id := Scope (Gen_Unit);
6216 Enc_G : Entity_Id;
6217 Enc_I : Node_Id;
6218 E_G_Id : Entity_Id;
6220 function Earlier (N1, N2 : Node_Id) return Boolean;
6221 -- Yields True if N1 and N2 appear in the same compilation unit,
6222 -- ignoring subunits, and if N1 is to the left of N2 in a left-to-right
6223 -- traversal of the tree for the unit.
6225 function Enclosing_Body (N : Node_Id) return Node_Id;
6226 -- Find innermost package body that encloses the given node, and which
6227 -- is not a compilation unit. Freeze nodes for the instance, or for its
6228 -- enclosing body, may be inserted after the enclosing_body of the
6229 -- generic unit.
6231 function Package_Freeze_Node (B : Node_Id) return Node_Id;
6232 -- Find entity for given package body, and locate or create a freeze
6233 -- node for it.
6235 function True_Parent (N : Node_Id) return Node_Id;
6236 -- For a subunit, return parent of corresponding stub
6238 -------------
6239 -- Earlier --
6240 -------------
6242 function Earlier (N1, N2 : Node_Id) return Boolean is
6243 D1 : Integer := 0;
6244 D2 : Integer := 0;
6245 P1 : Node_Id := N1;
6246 P2 : Node_Id := N2;
6248 procedure Find_Depth (P : in out Node_Id; D : in out Integer);
6249 -- Find distance from given node to enclosing compilation unit
6251 ----------------
6252 -- Find_Depth --
6253 ----------------
6255 procedure Find_Depth (P : in out Node_Id; D : in out Integer) is
6256 begin
6257 while Present (P)
6258 and then Nkind (P) /= N_Compilation_Unit
6259 loop
6260 P := True_Parent (P);
6261 D := D + 1;
6262 end loop;
6263 end Find_Depth;
6265 -- Start of processing for Earlier
6267 begin
6268 Find_Depth (P1, D1);
6269 Find_Depth (P2, D2);
6271 if P1 /= P2 then
6272 return False;
6273 else
6274 P1 := N1;
6275 P2 := N2;
6276 end if;
6278 while D1 > D2 loop
6279 P1 := True_Parent (P1);
6280 D1 := D1 - 1;
6281 end loop;
6283 while D2 > D1 loop
6284 P2 := True_Parent (P2);
6285 D2 := D2 - 1;
6286 end loop;
6288 -- At this point P1 and P2 are at the same distance from the root.
6289 -- We examine their parents until we find a common declarative
6290 -- list, at which point we can establish their relative placement
6291 -- by comparing their ultimate slocs. If we reach the root,
6292 -- N1 and N2 do not descend from the same declarative list (e.g.
6293 -- one is nested in the declarative part and the other is in a block
6294 -- in the statement part) and the earlier one is already frozen.
6296 while not Is_List_Member (P1)
6297 or else not Is_List_Member (P2)
6298 or else List_Containing (P1) /= List_Containing (P2)
6299 loop
6300 P1 := True_Parent (P1);
6301 P2 := True_Parent (P2);
6303 if Nkind (Parent (P1)) = N_Subunit then
6304 P1 := Corresponding_Stub (Parent (P1));
6305 end if;
6307 if Nkind (Parent (P2)) = N_Subunit then
6308 P2 := Corresponding_Stub (Parent (P2));
6309 end if;
6311 if P1 = P2 then
6312 return False;
6313 end if;
6314 end loop;
6316 return
6317 Top_Level_Location (Sloc (P1)) < Top_Level_Location (Sloc (P2));
6318 end Earlier;
6320 --------------------
6321 -- Enclosing_Body --
6322 --------------------
6324 function Enclosing_Body (N : Node_Id) return Node_Id is
6325 P : Node_Id := Parent (N);
6327 begin
6328 while Present (P)
6329 and then Nkind (Parent (P)) /= N_Compilation_Unit
6330 loop
6331 if Nkind (P) = N_Package_Body then
6333 if Nkind (Parent (P)) = N_Subunit then
6334 return Corresponding_Stub (Parent (P));
6335 else
6336 return P;
6337 end if;
6338 end if;
6340 P := True_Parent (P);
6341 end loop;
6343 return Empty;
6344 end Enclosing_Body;
6346 -------------------------
6347 -- Package_Freeze_Node --
6348 -------------------------
6350 function Package_Freeze_Node (B : Node_Id) return Node_Id is
6351 Id : Entity_Id;
6353 begin
6354 if Nkind (B) = N_Package_Body then
6355 Id := Corresponding_Spec (B);
6357 else pragma Assert (Nkind (B) = N_Package_Body_Stub);
6358 Id := Corresponding_Spec (Proper_Body (Unit (Library_Unit (B))));
6359 end if;
6361 Ensure_Freeze_Node (Id);
6362 return Freeze_Node (Id);
6363 end Package_Freeze_Node;
6365 -----------------
6366 -- True_Parent --
6367 -----------------
6369 function True_Parent (N : Node_Id) return Node_Id is
6370 begin
6371 if Nkind (Parent (N)) = N_Subunit then
6372 return Parent (Corresponding_Stub (Parent (N)));
6373 else
6374 return Parent (N);
6375 end if;
6376 end True_Parent;
6378 -- Start of processing of Freeze_Subprogram_Body
6380 begin
6381 -- If the instance and the generic body appear within the same unit, and
6382 -- the instance precedes the generic, the freeze node for the instance
6383 -- must appear after that of the generic. If the generic is nested
6384 -- within another instance I2, then current instance must be frozen
6385 -- after I2. In both cases, the freeze nodes are those of enclosing
6386 -- packages. Otherwise, the freeze node is placed at the end of the
6387 -- current declarative part.
6389 Enc_G := Enclosing_Body (Gen_Body);
6390 Enc_I := Enclosing_Body (Inst_Node);
6391 Ensure_Freeze_Node (Pack_Id);
6392 F_Node := Freeze_Node (Pack_Id);
6394 if Is_Generic_Instance (Par)
6395 and then Present (Freeze_Node (Par))
6396 and then
6397 In_Same_Declarative_Part (Freeze_Node (Par), Inst_Node)
6398 then
6399 if ABE_Is_Certain (Get_Package_Instantiation_Node (Par)) then
6401 -- The parent was a premature instantiation. Insert freeze node at
6402 -- the end the current declarative part.
6404 Insert_After_Last_Decl (Inst_Node, F_Node);
6406 else
6407 Insert_After (Freeze_Node (Par), F_Node);
6408 end if;
6410 -- The body enclosing the instance should be frozen after the body that
6411 -- includes the generic, because the body of the instance may make
6412 -- references to entities therein. If the two are not in the same
6413 -- declarative part, or if the one enclosing the instance is frozen
6414 -- already, freeze the instance at the end of the current declarative
6415 -- part.
6417 elsif Is_Generic_Instance (Par)
6418 and then Present (Freeze_Node (Par))
6419 and then Present (Enc_I)
6420 then
6421 if In_Same_Declarative_Part (Freeze_Node (Par), Enc_I)
6422 or else
6423 (Nkind (Enc_I) = N_Package_Body
6424 and then
6425 In_Same_Declarative_Part (Freeze_Node (Par), Parent (Enc_I)))
6426 then
6427 -- The enclosing package may contain several instances. Rather
6428 -- than computing the earliest point at which to insert its
6429 -- freeze node, we place it at the end of the declarative part
6430 -- of the parent of the generic.
6432 Insert_After_Last_Decl
6433 (Freeze_Node (Par), Package_Freeze_Node (Enc_I));
6434 end if;
6436 Insert_After_Last_Decl (Inst_Node, F_Node);
6438 elsif Present (Enc_G)
6439 and then Present (Enc_I)
6440 and then Enc_G /= Enc_I
6441 and then Earlier (Inst_Node, Gen_Body)
6442 then
6443 if Nkind (Enc_G) = N_Package_Body then
6444 E_G_Id := Corresponding_Spec (Enc_G);
6445 else pragma Assert (Nkind (Enc_G) = N_Package_Body_Stub);
6446 E_G_Id :=
6447 Corresponding_Spec (Proper_Body (Unit (Library_Unit (Enc_G))));
6448 end if;
6450 -- Freeze package that encloses instance, and place node after
6451 -- package that encloses generic. If enclosing package is already
6452 -- frozen we have to assume it is at the proper place. This may be
6453 -- a potential ABE that requires dynamic checking. Do not add a
6454 -- freeze node if the package that encloses the generic is inside
6455 -- the body that encloses the instance, because the freeze node
6456 -- would be in the wrong scope. Additional contortions needed if
6457 -- the bodies are within a subunit.
6459 declare
6460 Enclosing_Body : Node_Id;
6462 begin
6463 if Nkind (Enc_I) = N_Package_Body_Stub then
6464 Enclosing_Body := Proper_Body (Unit (Library_Unit (Enc_I)));
6465 else
6466 Enclosing_Body := Enc_I;
6467 end if;
6469 if Parent (List_Containing (Enc_G)) /= Enclosing_Body then
6470 Insert_After_Last_Decl (Enc_G, Package_Freeze_Node (Enc_I));
6471 end if;
6472 end;
6474 -- Freeze enclosing subunit before instance
6476 Ensure_Freeze_Node (E_G_Id);
6478 if not Is_List_Member (Freeze_Node (E_G_Id)) then
6479 Insert_After (Enc_G, Freeze_Node (E_G_Id));
6480 end if;
6482 Insert_After_Last_Decl (Inst_Node, F_Node);
6484 else
6485 -- If none of the above, insert freeze node at the end of the current
6486 -- declarative part.
6488 Insert_After_Last_Decl (Inst_Node, F_Node);
6489 end if;
6490 end Freeze_Subprogram_Body;
6492 ----------------
6493 -- Get_Gen_Id --
6494 ----------------
6496 function Get_Gen_Id (E : Assoc_Ptr) return Entity_Id is
6497 begin
6498 return Generic_Renamings.Table (E).Gen_Id;
6499 end Get_Gen_Id;
6501 ---------------------
6502 -- Get_Instance_Of --
6503 ---------------------
6505 function Get_Instance_Of (A : Entity_Id) return Entity_Id is
6506 Res : constant Assoc_Ptr := Generic_Renamings_HTable.Get (A);
6508 begin
6509 if Res /= Assoc_Null then
6510 return Generic_Renamings.Table (Res).Act_Id;
6511 else
6512 -- On exit, entity is not instantiated: not a generic parameter, or
6513 -- else parameter of an inner generic unit.
6515 return A;
6516 end if;
6517 end Get_Instance_Of;
6519 ------------------------------------
6520 -- Get_Package_Instantiation_Node --
6521 ------------------------------------
6523 function Get_Package_Instantiation_Node (A : Entity_Id) return Node_Id is
6524 Decl : Node_Id := Unit_Declaration_Node (A);
6525 Inst : Node_Id;
6527 begin
6528 -- If the Package_Instantiation attribute has been set on the package
6529 -- entity, then use it directly when it (or its Original_Node) refers
6530 -- to an N_Package_Instantiation node. In principle it should be
6531 -- possible to have this field set in all cases, which should be
6532 -- investigated, and would allow this function to be significantly
6533 -- simplified. ???
6535 if Present (Package_Instantiation (A)) then
6536 if Nkind (Package_Instantiation (A)) = N_Package_Instantiation then
6537 return Package_Instantiation (A);
6539 elsif Nkind (Original_Node (Package_Instantiation (A))) =
6540 N_Package_Instantiation
6541 then
6542 return Original_Node (Package_Instantiation (A));
6543 end if;
6544 end if;
6546 -- If the instantiation is a compilation unit that does not need body
6547 -- then the instantiation node has been rewritten as a package
6548 -- declaration for the instance, and we return the original node.
6550 -- If it is a compilation unit and the instance node has not been
6551 -- rewritten, then it is still the unit of the compilation. Finally, if
6552 -- a body is present, this is a parent of the main unit whose body has
6553 -- been compiled for inlining purposes, and the instantiation node has
6554 -- been rewritten with the instance body.
6556 -- Otherwise the instantiation node appears after the declaration. If
6557 -- the entity is a formal package, the declaration may have been
6558 -- rewritten as a generic declaration (in the case of a formal with box)
6559 -- or left as a formal package declaration if it has actuals, and is
6560 -- found with a forward search.
6562 if Nkind (Parent (Decl)) = N_Compilation_Unit then
6563 if Nkind (Decl) = N_Package_Declaration
6564 and then Present (Corresponding_Body (Decl))
6565 then
6566 Decl := Unit_Declaration_Node (Corresponding_Body (Decl));
6567 end if;
6569 if Nkind (Original_Node (Decl)) = N_Package_Instantiation then
6570 return Original_Node (Decl);
6571 else
6572 return Unit (Parent (Decl));
6573 end if;
6575 elsif Nkind (Decl) = N_Package_Declaration
6576 and then Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration
6577 then
6578 return Original_Node (Decl);
6580 else
6581 Inst := Next (Decl);
6582 while not Nkind_In (Inst, N_Package_Instantiation,
6583 N_Formal_Package_Declaration)
6584 loop
6585 Next (Inst);
6586 end loop;
6588 return Inst;
6589 end if;
6590 end Get_Package_Instantiation_Node;
6592 ------------------------
6593 -- Has_Been_Exchanged --
6594 ------------------------
6596 function Has_Been_Exchanged (E : Entity_Id) return Boolean is
6597 Next : Elmt_Id;
6599 begin
6600 Next := First_Elmt (Exchanged_Views);
6601 while Present (Next) loop
6602 if Full_View (Node (Next)) = E then
6603 return True;
6604 end if;
6606 Next_Elmt (Next);
6607 end loop;
6609 return False;
6610 end Has_Been_Exchanged;
6612 ----------
6613 -- Hash --
6614 ----------
6616 function Hash (F : Entity_Id) return HTable_Range is
6617 begin
6618 return HTable_Range (F mod HTable_Size);
6619 end Hash;
6621 ------------------------
6622 -- Hide_Current_Scope --
6623 ------------------------
6625 procedure Hide_Current_Scope is
6626 C : constant Entity_Id := Current_Scope;
6627 E : Entity_Id;
6629 begin
6630 Set_Is_Hidden_Open_Scope (C);
6632 E := First_Entity (C);
6633 while Present (E) loop
6634 if Is_Immediately_Visible (E) then
6635 Set_Is_Immediately_Visible (E, False);
6636 Append_Elmt (E, Hidden_Entities);
6637 end if;
6639 Next_Entity (E);
6640 end loop;
6642 -- Make the scope name invisible as well. This is necessary, but might
6643 -- conflict with calls to Rtsfind later on, in case the scope is a
6644 -- predefined one. There is no clean solution to this problem, so for
6645 -- now we depend on the user not redefining Standard itself in one of
6646 -- the parent units.
6648 if Is_Immediately_Visible (C)
6649 and then C /= Standard_Standard
6650 then
6651 Set_Is_Immediately_Visible (C, False);
6652 Append_Elmt (C, Hidden_Entities);
6653 end if;
6655 end Hide_Current_Scope;
6657 --------------
6658 -- Init_Env --
6659 --------------
6661 procedure Init_Env is
6662 Saved : Instance_Env;
6664 begin
6665 Saved.Instantiated_Parent := Current_Instantiated_Parent;
6666 Saved.Exchanged_Views := Exchanged_Views;
6667 Saved.Hidden_Entities := Hidden_Entities;
6668 Saved.Current_Sem_Unit := Current_Sem_Unit;
6669 Saved.Parent_Unit_Visible := Parent_Unit_Visible;
6670 Saved.Instance_Parent_Unit := Instance_Parent_Unit;
6672 -- Save configuration switches. These may be reset if the unit is a
6673 -- predefined unit, and the current mode is not Ada 2005.
6675 Save_Opt_Config_Switches (Saved.Switches);
6677 Instance_Envs.Append (Saved);
6679 Exchanged_Views := New_Elmt_List;
6680 Hidden_Entities := New_Elmt_List;
6682 -- Make dummy entry for Instantiated parent. If generic unit is legal,
6683 -- this is set properly in Set_Instance_Env.
6685 Current_Instantiated_Parent :=
6686 (Current_Scope, Current_Scope, Assoc_Null);
6687 end Init_Env;
6689 ------------------------------
6690 -- In_Same_Declarative_Part --
6691 ------------------------------
6693 function In_Same_Declarative_Part
6694 (F_Node : Node_Id;
6695 Inst : Node_Id) return Boolean
6697 Decls : constant Node_Id := Parent (F_Node);
6698 Nod : Node_Id := Parent (Inst);
6700 begin
6701 while Present (Nod) loop
6702 if Nod = Decls then
6703 return True;
6705 elsif Nkind_In (Nod, N_Subprogram_Body,
6706 N_Package_Body,
6707 N_Task_Body,
6708 N_Protected_Body,
6709 N_Block_Statement)
6710 then
6711 return False;
6713 elsif Nkind (Nod) = N_Subunit then
6714 Nod := Corresponding_Stub (Nod);
6716 elsif Nkind (Nod) = N_Compilation_Unit then
6717 return False;
6719 else
6720 Nod := Parent (Nod);
6721 end if;
6722 end loop;
6724 return False;
6725 end In_Same_Declarative_Part;
6727 ---------------------
6728 -- In_Main_Context --
6729 ---------------------
6731 function In_Main_Context (E : Entity_Id) return Boolean is
6732 Context : List_Id;
6733 Clause : Node_Id;
6734 Nam : Node_Id;
6736 begin
6737 if not Is_Compilation_Unit (E)
6738 or else Ekind (E) /= E_Package
6739 or else In_Private_Part (E)
6740 then
6741 return False;
6742 end if;
6744 Context := Context_Items (Cunit (Main_Unit));
6746 Clause := First (Context);
6747 while Present (Clause) loop
6748 if Nkind (Clause) = N_With_Clause then
6749 Nam := Name (Clause);
6751 -- If the current scope is part of the context of the main unit,
6752 -- analysis of the corresponding with_clause is not complete, and
6753 -- the entity is not set. We use the Chars field directly, which
6754 -- might produce false positives in rare cases, but guarantees
6755 -- that we produce all the instance bodies we will need.
6757 if (Is_Entity_Name (Nam)
6758 and then Chars (Nam) = Chars (E))
6759 or else (Nkind (Nam) = N_Selected_Component
6760 and then Chars (Selector_Name (Nam)) = Chars (E))
6761 then
6762 return True;
6763 end if;
6764 end if;
6766 Next (Clause);
6767 end loop;
6769 return False;
6770 end In_Main_Context;
6772 ---------------------
6773 -- Inherit_Context --
6774 ---------------------
6776 procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id) is
6777 Current_Context : List_Id;
6778 Current_Unit : Node_Id;
6779 Item : Node_Id;
6780 New_I : Node_Id;
6782 begin
6783 if Nkind (Parent (Gen_Decl)) = N_Compilation_Unit then
6785 -- The inherited context is attached to the enclosing compilation
6786 -- unit. This is either the main unit, or the declaration for the
6787 -- main unit (in case the instantiation appears within the package
6788 -- declaration and the main unit is its body).
6790 Current_Unit := Parent (Inst);
6791 while Present (Current_Unit)
6792 and then Nkind (Current_Unit) /= N_Compilation_Unit
6793 loop
6794 Current_Unit := Parent (Current_Unit);
6795 end loop;
6797 Current_Context := Context_Items (Current_Unit);
6799 Item := First (Context_Items (Parent (Gen_Decl)));
6800 while Present (Item) loop
6801 if Nkind (Item) = N_With_Clause then
6802 New_I := New_Copy (Item);
6803 Set_Implicit_With (New_I, True);
6804 Append (New_I, Current_Context);
6805 end if;
6807 Next (Item);
6808 end loop;
6809 end if;
6810 end Inherit_Context;
6812 ----------------
6813 -- Initialize --
6814 ----------------
6816 procedure Initialize is
6817 begin
6818 Generic_Renamings.Init;
6819 Instance_Envs.Init;
6820 Generic_Flags.Init;
6821 Generic_Renamings_HTable.Reset;
6822 Circularity_Detected := False;
6823 Exchanged_Views := No_Elist;
6824 Hidden_Entities := No_Elist;
6825 end Initialize;
6827 ----------------------------
6828 -- Insert_After_Last_Decl --
6829 ----------------------------
6831 procedure Insert_After_Last_Decl (N : Node_Id; F_Node : Node_Id) is
6832 L : List_Id := List_Containing (N);
6833 P : constant Node_Id := Parent (L);
6835 begin
6836 if not Is_List_Member (F_Node) then
6837 if Nkind (P) = N_Package_Specification
6838 and then L = Visible_Declarations (P)
6839 and then Present (Private_Declarations (P))
6840 and then not Is_Empty_List (Private_Declarations (P))
6841 then
6842 L := Private_Declarations (P);
6843 end if;
6845 Insert_After (Last (L), F_Node);
6846 end if;
6847 end Insert_After_Last_Decl;
6849 ------------------
6850 -- Install_Body --
6851 ------------------
6853 procedure Install_Body
6854 (Act_Body : Node_Id;
6855 N : Node_Id;
6856 Gen_Body : Node_Id;
6857 Gen_Decl : Node_Id)
6859 Act_Id : constant Entity_Id := Corresponding_Spec (Act_Body);
6860 Act_Unit : constant Node_Id := Unit (Cunit (Get_Source_Unit (N)));
6861 Gen_Id : constant Entity_Id := Corresponding_Spec (Gen_Body);
6862 Par : constant Entity_Id := Scope (Gen_Id);
6863 Gen_Unit : constant Node_Id :=
6864 Unit (Cunit (Get_Source_Unit (Gen_Decl)));
6865 Orig_Body : Node_Id := Gen_Body;
6866 F_Node : Node_Id;
6867 Body_Unit : Node_Id;
6869 Must_Delay : Boolean;
6871 function Enclosing_Subp (Id : Entity_Id) return Entity_Id;
6872 -- Find subprogram (if any) that encloses instance and/or generic body
6874 function True_Sloc (N : Node_Id) return Source_Ptr;
6875 -- If the instance is nested inside a generic unit, the Sloc of the
6876 -- instance indicates the place of the original definition, not the
6877 -- point of the current enclosing instance. Pending a better usage of
6878 -- Slocs to indicate instantiation places, we determine the place of
6879 -- origin of a node by finding the maximum sloc of any ancestor node.
6880 -- Why is this not equivalent to Top_Level_Location ???
6882 --------------------
6883 -- Enclosing_Subp --
6884 --------------------
6886 function Enclosing_Subp (Id : Entity_Id) return Entity_Id is
6887 Scop : Entity_Id := Scope (Id);
6889 begin
6890 while Scop /= Standard_Standard
6891 and then not Is_Overloadable (Scop)
6892 loop
6893 Scop := Scope (Scop);
6894 end loop;
6896 return Scop;
6897 end Enclosing_Subp;
6899 ---------------
6900 -- True_Sloc --
6901 ---------------
6903 function True_Sloc (N : Node_Id) return Source_Ptr is
6904 Res : Source_Ptr;
6905 N1 : Node_Id;
6907 begin
6908 Res := Sloc (N);
6909 N1 := N;
6910 while Present (N1) and then N1 /= Act_Unit loop
6911 if Sloc (N1) > Res then
6912 Res := Sloc (N1);
6913 end if;
6915 N1 := Parent (N1);
6916 end loop;
6918 return Res;
6919 end True_Sloc;
6921 -- Start of processing for Install_Body
6923 begin
6925 -- If the body is a subunit, the freeze point is the corresponding
6926 -- stub in the current compilation, not the subunit itself.
6928 if Nkind (Parent (Gen_Body)) = N_Subunit then
6929 Orig_Body := Corresponding_Stub (Parent (Gen_Body));
6930 else
6931 Orig_Body := Gen_Body;
6932 end if;
6934 Body_Unit := Unit (Cunit (Get_Source_Unit (Orig_Body)));
6936 -- If the instantiation and the generic definition appear in the same
6937 -- package declaration, this is an early instantiation. If they appear
6938 -- in the same declarative part, it is an early instantiation only if
6939 -- the generic body appears textually later, and the generic body is
6940 -- also in the main unit.
6942 -- If instance is nested within a subprogram, and the generic body is
6943 -- not, the instance is delayed because the enclosing body is. If
6944 -- instance and body are within the same scope, or the same sub-
6945 -- program body, indicate explicitly that the instance is delayed.
6947 Must_Delay :=
6948 (Gen_Unit = Act_Unit
6949 and then (Nkind_In (Gen_Unit, N_Package_Declaration,
6950 N_Generic_Package_Declaration)
6951 or else (Gen_Unit = Body_Unit
6952 and then True_Sloc (N) < Sloc (Orig_Body)))
6953 and then Is_In_Main_Unit (Gen_Unit)
6954 and then (Scope (Act_Id) = Scope (Gen_Id)
6955 or else
6956 Enclosing_Subp (Act_Id) = Enclosing_Subp (Gen_Id)));
6958 -- If this is an early instantiation, the freeze node is placed after
6959 -- the generic body. Otherwise, if the generic appears in an instance,
6960 -- we cannot freeze the current instance until the outer one is frozen.
6961 -- This is only relevant if the current instance is nested within some
6962 -- inner scope not itself within the outer instance. If this scope is
6963 -- a package body in the same declarative part as the outer instance,
6964 -- then that body needs to be frozen after the outer instance. Finally,
6965 -- if no delay is needed, we place the freeze node at the end of the
6966 -- current declarative part.
6968 if Expander_Active then
6969 Ensure_Freeze_Node (Act_Id);
6970 F_Node := Freeze_Node (Act_Id);
6972 if Must_Delay then
6973 Insert_After (Orig_Body, F_Node);
6975 elsif Is_Generic_Instance (Par)
6976 and then Present (Freeze_Node (Par))
6977 and then Scope (Act_Id) /= Par
6978 then
6979 -- Freeze instance of inner generic after instance of enclosing
6980 -- generic.
6982 if In_Same_Declarative_Part (Freeze_Node (Par), N) then
6983 Insert_After (Freeze_Node (Par), F_Node);
6985 -- Freeze package enclosing instance of inner generic after
6986 -- instance of enclosing generic.
6988 elsif Nkind (Parent (N)) = N_Package_Body
6989 and then In_Same_Declarative_Part (Freeze_Node (Par), Parent (N))
6990 then
6992 declare
6993 Enclosing : constant Entity_Id :=
6994 Corresponding_Spec (Parent (N));
6996 begin
6997 Insert_After_Last_Decl (N, F_Node);
6998 Ensure_Freeze_Node (Enclosing);
7000 if not Is_List_Member (Freeze_Node (Enclosing)) then
7001 Insert_After (Freeze_Node (Par), Freeze_Node (Enclosing));
7002 end if;
7003 end;
7005 else
7006 Insert_After_Last_Decl (N, F_Node);
7007 end if;
7009 else
7010 Insert_After_Last_Decl (N, F_Node);
7011 end if;
7012 end if;
7014 Set_Is_Frozen (Act_Id);
7015 Insert_Before (N, Act_Body);
7016 Mark_Rewrite_Insertion (Act_Body);
7017 end Install_Body;
7019 -----------------------------
7020 -- Install_Formal_Packages --
7021 -----------------------------
7023 procedure Install_Formal_Packages (Par : Entity_Id) is
7024 E : Entity_Id;
7026 begin
7027 E := First_Entity (Par);
7028 while Present (E) loop
7029 if Ekind (E) = E_Package
7030 and then Nkind (Parent (E)) = N_Package_Renaming_Declaration
7031 then
7032 -- If this is the renaming for the parent instance, done
7034 if Renamed_Object (E) = Par then
7035 exit;
7037 -- The visibility of a formal of an enclosing generic is
7038 -- already correct.
7040 elsif Denotes_Formal_Package (E) then
7041 null;
7043 elsif Present (Associated_Formal_Package (E))
7044 and then Box_Present (Parent (Associated_Formal_Package (E)))
7045 then
7046 Check_Generic_Actuals (Renamed_Object (E), True);
7047 Set_Is_Hidden (E, False);
7048 end if;
7049 end if;
7051 Next_Entity (E);
7052 end loop;
7053 end Install_Formal_Packages;
7055 --------------------
7056 -- Install_Parent --
7057 --------------------
7059 procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False) is
7060 Ancestors : constant Elist_Id := New_Elmt_List;
7061 S : constant Entity_Id := Current_Scope;
7062 Inst_Par : Entity_Id;
7063 First_Par : Entity_Id;
7064 Inst_Node : Node_Id;
7065 Gen_Par : Entity_Id;
7066 First_Gen : Entity_Id;
7067 Elmt : Elmt_Id;
7069 procedure Install_Noninstance_Specs (Par : Entity_Id);
7070 -- Install the scopes of noninstance parent units ending with Par
7072 procedure Install_Spec (Par : Entity_Id);
7073 -- The child unit is within the declarative part of the parent, so
7074 -- the declarations within the parent are immediately visible.
7076 -------------------------------
7077 -- Install_Noninstance_Specs --
7078 -------------------------------
7080 procedure Install_Noninstance_Specs (Par : Entity_Id) is
7081 begin
7082 if Present (Par)
7083 and then Par /= Standard_Standard
7084 and then not In_Open_Scopes (Par)
7085 then
7086 Install_Noninstance_Specs (Scope (Par));
7087 Install_Spec (Par);
7088 end if;
7089 end Install_Noninstance_Specs;
7091 ------------------
7092 -- Install_Spec --
7093 ------------------
7095 procedure Install_Spec (Par : Entity_Id) is
7096 Spec : constant Node_Id :=
7097 Specification (Unit_Declaration_Node (Par));
7099 begin
7100 -- If this parent of the child instance is a top-level unit,
7101 -- then record the unit and its visibility for later resetting
7102 -- in Remove_Parent. We exclude units that are generic instances,
7103 -- as we only want to record this information for the ultimate
7104 -- top-level noninstance parent (is that always correct???).
7106 if Scope (Par) = Standard_Standard
7107 and then not Is_Generic_Instance (Par)
7108 then
7109 Parent_Unit_Visible := Is_Immediately_Visible (Par);
7110 Instance_Parent_Unit := Par;
7111 end if;
7113 -- Open the parent scope and make it and its declarations visible.
7114 -- If this point is not within a body, then only the visible
7115 -- declarations should be made visible, and installation of the
7116 -- private declarations is deferred until the appropriate point
7117 -- within analysis of the spec being instantiated (see the handling
7118 -- of parent visibility in Analyze_Package_Specification). This is
7119 -- relaxed in the case where the parent unit is Ada.Tags, to avoid
7120 -- private view problems that occur when compiling instantiations of
7121 -- a generic child of that package (Generic_Dispatching_Constructor).
7122 -- If the instance freezes a tagged type, inlinings of operations
7123 -- from Ada.Tags may need the full view of type Tag. If inlining took
7124 -- proper account of establishing visibility of inlined subprograms'
7125 -- parents then it should be possible to remove this
7126 -- special check. ???
7128 Push_Scope (Par);
7129 Set_Is_Immediately_Visible (Par);
7130 Install_Visible_Declarations (Par);
7131 Set_Use (Visible_Declarations (Spec));
7133 if In_Body or else Is_RTU (Par, Ada_Tags) then
7134 Install_Private_Declarations (Par);
7135 Set_Use (Private_Declarations (Spec));
7136 end if;
7137 end Install_Spec;
7139 -- Start of processing for Install_Parent
7141 begin
7142 -- We need to install the parent instance to compile the instantiation
7143 -- of the child, but the child instance must appear in the current
7144 -- scope. Given that we cannot place the parent above the current scope
7145 -- in the scope stack, we duplicate the current scope and unstack both
7146 -- after the instantiation is complete.
7148 -- If the parent is itself the instantiation of a child unit, we must
7149 -- also stack the instantiation of its parent, and so on. Each such
7150 -- ancestor is the prefix of the name in a prior instantiation.
7152 -- If this is a nested instance, the parent unit itself resolves to
7153 -- a renaming of the parent instance, whose declaration we need.
7155 -- Finally, the parent may be a generic (not an instance) when the
7156 -- child unit appears as a formal package.
7158 Inst_Par := P;
7160 if Present (Renamed_Entity (Inst_Par)) then
7161 Inst_Par := Renamed_Entity (Inst_Par);
7162 end if;
7164 First_Par := Inst_Par;
7166 Gen_Par :=
7167 Generic_Parent (Specification (Unit_Declaration_Node (Inst_Par)));
7169 First_Gen := Gen_Par;
7171 while Present (Gen_Par)
7172 and then Is_Child_Unit (Gen_Par)
7173 loop
7174 -- Load grandparent instance as well
7176 Inst_Node := Get_Package_Instantiation_Node (Inst_Par);
7178 if Nkind (Name (Inst_Node)) = N_Expanded_Name then
7179 Inst_Par := Entity (Prefix (Name (Inst_Node)));
7181 if Present (Renamed_Entity (Inst_Par)) then
7182 Inst_Par := Renamed_Entity (Inst_Par);
7183 end if;
7185 Gen_Par :=
7186 Generic_Parent
7187 (Specification (Unit_Declaration_Node (Inst_Par)));
7189 if Present (Gen_Par) then
7190 Prepend_Elmt (Inst_Par, Ancestors);
7192 else
7193 -- Parent is not the name of an instantiation
7195 Install_Noninstance_Specs (Inst_Par);
7197 exit;
7198 end if;
7200 else
7201 -- Previous error
7203 exit;
7204 end if;
7205 end loop;
7207 if Present (First_Gen) then
7208 Append_Elmt (First_Par, Ancestors);
7210 else
7211 Install_Noninstance_Specs (First_Par);
7212 end if;
7214 if not Is_Empty_Elmt_List (Ancestors) then
7215 Elmt := First_Elmt (Ancestors);
7217 while Present (Elmt) loop
7218 Install_Spec (Node (Elmt));
7219 Install_Formal_Packages (Node (Elmt));
7221 Next_Elmt (Elmt);
7222 end loop;
7223 end if;
7225 if not In_Body then
7226 Push_Scope (S);
7227 end if;
7228 end Install_Parent;
7230 --------------------------------
7231 -- Instantiate_Formal_Package --
7232 --------------------------------
7234 function Instantiate_Formal_Package
7235 (Formal : Node_Id;
7236 Actual : Node_Id;
7237 Analyzed_Formal : Node_Id) return List_Id
7239 Loc : constant Source_Ptr := Sloc (Actual);
7240 Actual_Pack : Entity_Id;
7241 Formal_Pack : Entity_Id;
7242 Gen_Parent : Entity_Id;
7243 Decls : List_Id;
7244 Nod : Node_Id;
7245 Parent_Spec : Node_Id;
7247 procedure Find_Matching_Actual
7248 (F : Node_Id;
7249 Act : in out Entity_Id);
7250 -- We need to associate each formal entity in the formal package
7251 -- with the corresponding entity in the actual package. The actual
7252 -- package has been analyzed and possibly expanded, and as a result
7253 -- there is no one-to-one correspondence between the two lists (for
7254 -- example, the actual may include subtypes, itypes, and inherited
7255 -- primitive operations, interspersed among the renaming declarations
7256 -- for the actuals) . We retrieve the corresponding actual by name
7257 -- because each actual has the same name as the formal, and they do
7258 -- appear in the same order.
7260 function Get_Formal_Entity (N : Node_Id) return Entity_Id;
7261 -- Retrieve entity of defining entity of generic formal parameter.
7262 -- Only the declarations of formals need to be considered when
7263 -- linking them to actuals, but the declarative list may include
7264 -- internal entities generated during analysis, and those are ignored.
7266 procedure Match_Formal_Entity
7267 (Formal_Node : Node_Id;
7268 Formal_Ent : Entity_Id;
7269 Actual_Ent : Entity_Id);
7270 -- Associates the formal entity with the actual. In the case
7271 -- where Formal_Ent is a formal package, this procedure iterates
7272 -- through all of its formals and enters associations between the
7273 -- actuals occurring in the formal package's corresponding actual
7274 -- package (given by Actual_Ent) and the formal package's formal
7275 -- parameters. This procedure recurses if any of the parameters is
7276 -- itself a package.
7278 function Is_Instance_Of
7279 (Act_Spec : Entity_Id;
7280 Gen_Anc : Entity_Id) return Boolean;
7281 -- The actual can be an instantiation of a generic within another
7282 -- instance, in which case there is no direct link from it to the
7283 -- original generic ancestor. In that case, we recognize that the
7284 -- ultimate ancestor is the same by examining names and scopes.
7286 procedure Map_Entities (Form : Entity_Id; Act : Entity_Id);
7287 -- Within the generic part, entities in the formal package are
7288 -- visible. To validate subsequent type declarations, indicate
7289 -- the correspondence between the entities in the analyzed formal,
7290 -- and the entities in the actual package. There are three packages
7291 -- involved in the instantiation of a formal package: the parent
7292 -- generic P1 which appears in the generic declaration, the fake
7293 -- instantiation P2 which appears in the analyzed generic, and whose
7294 -- visible entities may be used in subsequent formals, and the actual
7295 -- P3 in the instance. To validate subsequent formals, me indicate
7296 -- that the entities in P2 are mapped into those of P3. The mapping of
7297 -- entities has to be done recursively for nested packages.
7299 procedure Process_Nested_Formal (Formal : Entity_Id);
7300 -- If the current formal is declared with a box, its own formals are
7301 -- visible in the instance, as they were in the generic, and their
7302 -- Hidden flag must be reset. If some of these formals are themselves
7303 -- packages declared with a box, the processing must be recursive.
7305 --------------------------
7306 -- Find_Matching_Actual --
7307 --------------------------
7309 procedure Find_Matching_Actual
7310 (F : Node_Id;
7311 Act : in out Entity_Id)
7313 Formal_Ent : Entity_Id;
7315 begin
7316 case Nkind (Original_Node (F)) is
7317 when N_Formal_Object_Declaration |
7318 N_Formal_Type_Declaration =>
7319 Formal_Ent := Defining_Identifier (F);
7321 while Chars (Act) /= Chars (Formal_Ent) loop
7322 Next_Entity (Act);
7323 end loop;
7325 when N_Formal_Subprogram_Declaration |
7326 N_Formal_Package_Declaration |
7327 N_Package_Declaration |
7328 N_Generic_Package_Declaration =>
7329 Formal_Ent := Defining_Entity (F);
7331 while Chars (Act) /= Chars (Formal_Ent) loop
7332 Next_Entity (Act);
7333 end loop;
7335 when others =>
7336 raise Program_Error;
7337 end case;
7338 end Find_Matching_Actual;
7340 -------------------------
7341 -- Match_Formal_Entity --
7342 -------------------------
7344 procedure Match_Formal_Entity
7345 (Formal_Node : Node_Id;
7346 Formal_Ent : Entity_Id;
7347 Actual_Ent : Entity_Id)
7349 Act_Pkg : Entity_Id;
7351 begin
7352 Set_Instance_Of (Formal_Ent, Actual_Ent);
7354 if Ekind (Actual_Ent) = E_Package then
7356 -- Record associations for each parameter
7358 Act_Pkg := Actual_Ent;
7360 declare
7361 A_Ent : Entity_Id := First_Entity (Act_Pkg);
7362 F_Ent : Entity_Id;
7363 F_Node : Node_Id;
7365 Gen_Decl : Node_Id;
7366 Formals : List_Id;
7367 Actual : Entity_Id;
7369 begin
7370 -- Retrieve the actual given in the formal package declaration
7372 Actual := Entity (Name (Original_Node (Formal_Node)));
7374 -- The actual in the formal package declaration may be a
7375 -- renamed generic package, in which case we want to retrieve
7376 -- the original generic in order to traverse its formal part.
7378 if Present (Renamed_Entity (Actual)) then
7379 Gen_Decl := Unit_Declaration_Node (Renamed_Entity (Actual));
7380 else
7381 Gen_Decl := Unit_Declaration_Node (Actual);
7382 end if;
7384 Formals := Generic_Formal_Declarations (Gen_Decl);
7386 if Present (Formals) then
7387 F_Node := First_Non_Pragma (Formals);
7388 else
7389 F_Node := Empty;
7390 end if;
7392 while Present (A_Ent)
7393 and then Present (F_Node)
7394 and then A_Ent /= First_Private_Entity (Act_Pkg)
7395 loop
7396 F_Ent := Get_Formal_Entity (F_Node);
7398 if Present (F_Ent) then
7400 -- This is a formal of the original package. Record
7401 -- association and recurse.
7403 Find_Matching_Actual (F_Node, A_Ent);
7404 Match_Formal_Entity (F_Node, F_Ent, A_Ent);
7405 Next_Entity (A_Ent);
7406 end if;
7408 Next_Non_Pragma (F_Node);
7409 end loop;
7410 end;
7411 end if;
7412 end Match_Formal_Entity;
7414 -----------------------
7415 -- Get_Formal_Entity --
7416 -----------------------
7418 function Get_Formal_Entity (N : Node_Id) return Entity_Id is
7419 Kind : constant Node_Kind := Nkind (Original_Node (N));
7420 begin
7421 case Kind is
7422 when N_Formal_Object_Declaration =>
7423 return Defining_Identifier (N);
7425 when N_Formal_Type_Declaration =>
7426 return Defining_Identifier (N);
7428 when N_Formal_Subprogram_Declaration =>
7429 return Defining_Unit_Name (Specification (N));
7431 when N_Formal_Package_Declaration =>
7432 return Defining_Identifier (Original_Node (N));
7434 when N_Generic_Package_Declaration =>
7435 return Defining_Identifier (Original_Node (N));
7437 -- All other declarations are introduced by semantic analysis and
7438 -- have no match in the actual.
7440 when others =>
7441 return Empty;
7442 end case;
7443 end Get_Formal_Entity;
7445 --------------------
7446 -- Is_Instance_Of --
7447 --------------------
7449 function Is_Instance_Of
7450 (Act_Spec : Entity_Id;
7451 Gen_Anc : Entity_Id) return Boolean
7453 Gen_Par : constant Entity_Id := Generic_Parent (Act_Spec);
7455 begin
7456 if No (Gen_Par) then
7457 return False;
7459 -- Simplest case: the generic parent of the actual is the formal
7461 elsif Gen_Par = Gen_Anc then
7462 return True;
7464 elsif Chars (Gen_Par) /= Chars (Gen_Anc) then
7465 return False;
7467 -- The actual may be obtained through several instantiations. Its
7468 -- scope must itself be an instance of a generic declared in the
7469 -- same scope as the formal. Any other case is detected above.
7471 elsif not Is_Generic_Instance (Scope (Gen_Par)) then
7472 return False;
7474 else
7475 return Generic_Parent (Parent (Scope (Gen_Par))) = Scope (Gen_Anc);
7476 end if;
7477 end Is_Instance_Of;
7479 ------------------
7480 -- Map_Entities --
7481 ------------------
7483 procedure Map_Entities (Form : Entity_Id; Act : Entity_Id) is
7484 E1 : Entity_Id;
7485 E2 : Entity_Id;
7487 begin
7488 Set_Instance_Of (Form, Act);
7490 -- Traverse formal and actual package to map the corresponding
7491 -- entities. We skip over internal entities that may be generated
7492 -- during semantic analysis, and find the matching entities by
7493 -- name, given that they must appear in the same order.
7495 E1 := First_Entity (Form);
7496 E2 := First_Entity (Act);
7497 while Present (E1)
7498 and then E1 /= First_Private_Entity (Form)
7499 loop
7500 -- Could this test be a single condition???
7501 -- Seems like it could, and isn't FPE (Form) a constant anyway???
7503 if not Is_Internal (E1)
7504 and then Present (Parent (E1))
7505 and then not Is_Class_Wide_Type (E1)
7506 and then not Is_Internal_Name (Chars (E1))
7507 then
7508 while Present (E2)
7509 and then Chars (E2) /= Chars (E1)
7510 loop
7511 Next_Entity (E2);
7512 end loop;
7514 if No (E2) then
7515 exit;
7516 else
7517 Set_Instance_Of (E1, E2);
7519 if Is_Type (E1)
7520 and then Is_Tagged_Type (E2)
7521 then
7522 Set_Instance_Of
7523 (Class_Wide_Type (E1), Class_Wide_Type (E2));
7524 end if;
7526 if Ekind (E1) = E_Package
7527 and then No (Renamed_Object (E1))
7528 then
7529 Map_Entities (E1, E2);
7530 end if;
7531 end if;
7532 end if;
7534 Next_Entity (E1);
7535 end loop;
7536 end Map_Entities;
7538 ---------------------------
7539 -- Process_Nested_Formal --
7540 ---------------------------
7542 procedure Process_Nested_Formal (Formal : Entity_Id) is
7543 Ent : Entity_Id;
7545 begin
7546 if Present (Associated_Formal_Package (Formal))
7547 and then Box_Present (Parent (Associated_Formal_Package (Formal)))
7548 then
7549 Ent := First_Entity (Formal);
7550 while Present (Ent) loop
7551 Set_Is_Hidden (Ent, False);
7552 Set_Is_Visible_Formal (Ent);
7553 Set_Is_Potentially_Use_Visible
7554 (Ent, Is_Potentially_Use_Visible (Formal));
7556 if Ekind (Ent) = E_Package then
7557 exit when Renamed_Entity (Ent) = Renamed_Entity (Formal);
7558 Process_Nested_Formal (Ent);
7559 end if;
7561 Next_Entity (Ent);
7562 end loop;
7563 end if;
7564 end Process_Nested_Formal;
7566 -- Start of processing for Instantiate_Formal_Package
7568 begin
7569 Analyze (Actual);
7571 if not Is_Entity_Name (Actual)
7572 or else Ekind (Entity (Actual)) /= E_Package
7573 then
7574 Error_Msg_N
7575 ("expect package instance to instantiate formal", Actual);
7576 Abandon_Instantiation (Actual);
7577 raise Program_Error;
7579 else
7580 Actual_Pack := Entity (Actual);
7581 Set_Is_Instantiated (Actual_Pack);
7583 -- The actual may be a renamed package, or an outer generic formal
7584 -- package whose instantiation is converted into a renaming.
7586 if Present (Renamed_Object (Actual_Pack)) then
7587 Actual_Pack := Renamed_Object (Actual_Pack);
7588 end if;
7590 if Nkind (Analyzed_Formal) = N_Formal_Package_Declaration then
7591 Gen_Parent := Get_Instance_Of (Entity (Name (Analyzed_Formal)));
7592 Formal_Pack := Defining_Identifier (Analyzed_Formal);
7593 else
7594 Gen_Parent :=
7595 Generic_Parent (Specification (Analyzed_Formal));
7596 Formal_Pack :=
7597 Defining_Unit_Name (Specification (Analyzed_Formal));
7598 end if;
7600 if Nkind (Parent (Actual_Pack)) = N_Defining_Program_Unit_Name then
7601 Parent_Spec := Specification (Unit_Declaration_Node (Actual_Pack));
7602 else
7603 Parent_Spec := Parent (Actual_Pack);
7604 end if;
7606 if Gen_Parent = Any_Id then
7607 Error_Msg_N
7608 ("previous error in declaration of formal package", Actual);
7609 Abandon_Instantiation (Actual);
7611 elsif
7612 Is_Instance_Of (Parent_Spec, Get_Instance_Of (Gen_Parent))
7613 then
7614 null;
7616 else
7617 Error_Msg_NE
7618 ("actual parameter must be instance of&", Actual, Gen_Parent);
7619 Abandon_Instantiation (Actual);
7620 end if;
7622 Set_Instance_Of (Defining_Identifier (Formal), Actual_Pack);
7623 Map_Entities (Formal_Pack, Actual_Pack);
7625 Nod :=
7626 Make_Package_Renaming_Declaration (Loc,
7627 Defining_Unit_Name => New_Copy (Defining_Identifier (Formal)),
7628 Name => New_Reference_To (Actual_Pack, Loc));
7630 Set_Associated_Formal_Package (Defining_Unit_Name (Nod),
7631 Defining_Identifier (Formal));
7632 Decls := New_List (Nod);
7634 -- If the formal F has a box, then the generic declarations are
7635 -- visible in the generic G. In an instance of G, the corresponding
7636 -- entities in the actual for F (which are the actuals for the
7637 -- instantiation of the generic that F denotes) must also be made
7638 -- visible for analysis of the current instance. On exit from the
7639 -- current instance, those entities are made private again. If the
7640 -- actual is currently in use, these entities are also use-visible.
7642 -- The loop through the actual entities also steps through the formal
7643 -- entities and enters associations from formals to actuals into the
7644 -- renaming map. This is necessary to properly handle checking of
7645 -- actual parameter associations for later formals that depend on
7646 -- actuals declared in the formal package.
7648 -- In Ada 2005, partial parametrization requires that we make visible
7649 -- the actuals corresponding to formals that were defaulted in the
7650 -- formal package. There formals are identified because they remain
7651 -- formal generics within the formal package, rather than being
7652 -- renamings of the actuals supplied.
7654 declare
7655 Gen_Decl : constant Node_Id :=
7656 Unit_Declaration_Node (Gen_Parent);
7657 Formals : constant List_Id :=
7658 Generic_Formal_Declarations (Gen_Decl);
7660 Actual_Ent : Entity_Id;
7661 Actual_Of_Formal : Node_Id;
7662 Formal_Node : Node_Id;
7663 Formal_Ent : Entity_Id;
7665 begin
7666 if Present (Formals) then
7667 Formal_Node := First_Non_Pragma (Formals);
7668 else
7669 Formal_Node := Empty;
7670 end if;
7672 Actual_Ent := First_Entity (Actual_Pack);
7673 Actual_Of_Formal :=
7674 First (Visible_Declarations (Specification (Analyzed_Formal)));
7675 while Present (Actual_Ent)
7676 and then Actual_Ent /= First_Private_Entity (Actual_Pack)
7677 loop
7678 if Present (Formal_Node) then
7679 Formal_Ent := Get_Formal_Entity (Formal_Node);
7681 if Present (Formal_Ent) then
7682 Find_Matching_Actual (Formal_Node, Actual_Ent);
7683 Match_Formal_Entity
7684 (Formal_Node, Formal_Ent, Actual_Ent);
7686 -- We iterate at the same time over the actuals of the
7687 -- local package created for the formal, to determine
7688 -- which one of the formals of the original generic were
7689 -- defaulted in the formal. The corresponding actual
7690 -- entities are visible in the enclosing instance.
7692 if Box_Present (Formal)
7693 or else
7694 (Present (Actual_Of_Formal)
7695 and then
7696 Is_Generic_Formal
7697 (Get_Formal_Entity (Actual_Of_Formal)))
7698 then
7699 Set_Is_Hidden (Actual_Ent, False);
7700 Set_Is_Visible_Formal (Actual_Ent);
7701 Set_Is_Potentially_Use_Visible
7702 (Actual_Ent, In_Use (Actual_Pack));
7704 if Ekind (Actual_Ent) = E_Package then
7705 Process_Nested_Formal (Actual_Ent);
7706 end if;
7708 else
7709 Set_Is_Hidden (Actual_Ent);
7710 Set_Is_Potentially_Use_Visible (Actual_Ent, False);
7711 end if;
7712 end if;
7714 Next_Non_Pragma (Formal_Node);
7715 Next (Actual_Of_Formal);
7717 else
7718 -- No further formals to match, but the generic part may
7719 -- contain inherited operation that are not hidden in the
7720 -- enclosing instance.
7722 Next_Entity (Actual_Ent);
7723 end if;
7724 end loop;
7726 -- Inherited subprograms generated by formal derived types are
7727 -- also visible if the types are.
7729 Actual_Ent := First_Entity (Actual_Pack);
7730 while Present (Actual_Ent)
7731 and then Actual_Ent /= First_Private_Entity (Actual_Pack)
7732 loop
7733 if Is_Overloadable (Actual_Ent)
7734 and then
7735 Nkind (Parent (Actual_Ent)) = N_Subtype_Declaration
7736 and then
7737 not Is_Hidden (Defining_Identifier (Parent (Actual_Ent)))
7738 then
7739 Set_Is_Hidden (Actual_Ent, False);
7740 Set_Is_Potentially_Use_Visible
7741 (Actual_Ent, In_Use (Actual_Pack));
7742 end if;
7744 Next_Entity (Actual_Ent);
7745 end loop;
7746 end;
7748 -- If the formal is not declared with a box, reanalyze it as an
7749 -- abbreviated instantiation, to verify the matching rules of 12.7.
7750 -- The actual checks are performed after the generic associations
7751 -- have been analyzed, to guarantee the same visibility for this
7752 -- instantiation and for the actuals.
7754 -- In Ada 2005, the generic associations for the formal can include
7755 -- defaulted parameters. These are ignored during check. This
7756 -- internal instantiation is removed from the tree after conformance
7757 -- checking, because it contains formal declarations for those
7758 -- defaulted parameters, and those should not reach the back-end.
7760 if not Box_Present (Formal) then
7761 declare
7762 I_Pack : constant Entity_Id :=
7763 Make_Defining_Identifier (Sloc (Actual),
7764 Chars => New_Internal_Name ('P'));
7766 begin
7767 Set_Is_Internal (I_Pack);
7769 Append_To (Decls,
7770 Make_Package_Instantiation (Sloc (Actual),
7771 Defining_Unit_Name => I_Pack,
7772 Name =>
7773 New_Occurrence_Of
7774 (Get_Instance_Of (Gen_Parent), Sloc (Actual)),
7775 Generic_Associations =>
7776 Generic_Associations (Formal)));
7777 end;
7778 end if;
7780 return Decls;
7781 end if;
7782 end Instantiate_Formal_Package;
7784 -----------------------------------
7785 -- Instantiate_Formal_Subprogram --
7786 -----------------------------------
7788 function Instantiate_Formal_Subprogram
7789 (Formal : Node_Id;
7790 Actual : Node_Id;
7791 Analyzed_Formal : Node_Id) return Node_Id
7793 Loc : Source_Ptr;
7794 Formal_Sub : constant Entity_Id :=
7795 Defining_Unit_Name (Specification (Formal));
7796 Analyzed_S : constant Entity_Id :=
7797 Defining_Unit_Name (Specification (Analyzed_Formal));
7798 Decl_Node : Node_Id;
7799 Nam : Node_Id;
7800 New_Spec : Node_Id;
7802 function From_Parent_Scope (Subp : Entity_Id) return Boolean;
7803 -- If the generic is a child unit, the parent has been installed on the
7804 -- scope stack, but a default subprogram cannot resolve to something on
7805 -- the parent because that parent is not really part of the visible
7806 -- context (it is there to resolve explicit local entities). If the
7807 -- default has resolved in this way, we remove the entity from
7808 -- immediate visibility and analyze the node again to emit an error
7809 -- message or find another visible candidate.
7811 procedure Valid_Actual_Subprogram (Act : Node_Id);
7812 -- Perform legality check and raise exception on failure
7814 -----------------------
7815 -- From_Parent_Scope --
7816 -----------------------
7818 function From_Parent_Scope (Subp : Entity_Id) return Boolean is
7819 Gen_Scope : Node_Id;
7821 begin
7822 Gen_Scope := Scope (Analyzed_S);
7823 while Present (Gen_Scope)
7824 and then Is_Child_Unit (Gen_Scope)
7825 loop
7826 if Scope (Subp) = Scope (Gen_Scope) then
7827 return True;
7828 end if;
7830 Gen_Scope := Scope (Gen_Scope);
7831 end loop;
7833 return False;
7834 end From_Parent_Scope;
7836 -----------------------------
7837 -- Valid_Actual_Subprogram --
7838 -----------------------------
7840 procedure Valid_Actual_Subprogram (Act : Node_Id) is
7841 Act_E : Entity_Id;
7843 begin
7844 if Is_Entity_Name (Act) then
7845 Act_E := Entity (Act);
7847 elsif Nkind (Act) = N_Selected_Component
7848 and then Is_Entity_Name (Selector_Name (Act))
7849 then
7850 Act_E := Entity (Selector_Name (Act));
7852 else
7853 Act_E := Empty;
7854 end if;
7856 if (Present (Act_E) and then Is_Overloadable (Act_E))
7857 or else Nkind_In (Act, N_Attribute_Reference,
7858 N_Indexed_Component,
7859 N_Character_Literal,
7860 N_Explicit_Dereference)
7861 then
7862 return;
7863 end if;
7865 Error_Msg_NE
7866 ("expect subprogram or entry name in instantiation of&",
7867 Instantiation_Node, Formal_Sub);
7868 Abandon_Instantiation (Instantiation_Node);
7870 end Valid_Actual_Subprogram;
7872 -- Start of processing for Instantiate_Formal_Subprogram
7874 begin
7875 New_Spec := New_Copy_Tree (Specification (Formal));
7877 -- The tree copy has created the proper instantiation sloc for the
7878 -- new specification. Use this location for all other constructed
7879 -- declarations.
7881 Loc := Sloc (Defining_Unit_Name (New_Spec));
7883 -- Create new entity for the actual (New_Copy_Tree does not)
7885 Set_Defining_Unit_Name
7886 (New_Spec, Make_Defining_Identifier (Loc, Chars (Formal_Sub)));
7888 -- Create new entities for the each of the formals in the
7889 -- specification of the renaming declaration built for the actual.
7891 if Present (Parameter_Specifications (New_Spec)) then
7892 declare
7893 F : Node_Id;
7894 begin
7895 F := First (Parameter_Specifications (New_Spec));
7896 while Present (F) loop
7897 Set_Defining_Identifier (F,
7898 Make_Defining_Identifier (Sloc (F),
7899 Chars => Chars (Defining_Identifier (F))));
7900 Next (F);
7901 end loop;
7902 end;
7903 end if;
7905 -- Find entity of actual. If the actual is an attribute reference, it
7906 -- cannot be resolved here (its formal is missing) but is handled
7907 -- instead in Attribute_Renaming. If the actual is overloaded, it is
7908 -- fully resolved subsequently, when the renaming declaration for the
7909 -- formal is analyzed. If it is an explicit dereference, resolve the
7910 -- prefix but not the actual itself, to prevent interpretation as call.
7912 if Present (Actual) then
7913 Loc := Sloc (Actual);
7914 Set_Sloc (New_Spec, Loc);
7916 if Nkind (Actual) = N_Operator_Symbol then
7917 Find_Direct_Name (Actual);
7919 elsif Nkind (Actual) = N_Explicit_Dereference then
7920 Analyze (Prefix (Actual));
7922 elsif Nkind (Actual) /= N_Attribute_Reference then
7923 Analyze (Actual);
7924 end if;
7926 Valid_Actual_Subprogram (Actual);
7927 Nam := Actual;
7929 elsif Present (Default_Name (Formal)) then
7930 if not Nkind_In (Default_Name (Formal), N_Attribute_Reference,
7931 N_Selected_Component,
7932 N_Indexed_Component,
7933 N_Character_Literal)
7934 and then Present (Entity (Default_Name (Formal)))
7935 then
7936 Nam := New_Occurrence_Of (Entity (Default_Name (Formal)), Loc);
7937 else
7938 Nam := New_Copy (Default_Name (Formal));
7939 Set_Sloc (Nam, Loc);
7940 end if;
7942 elsif Box_Present (Formal) then
7944 -- Actual is resolved at the point of instantiation. Create an
7945 -- identifier or operator with the same name as the formal.
7947 if Nkind (Formal_Sub) = N_Defining_Operator_Symbol then
7948 Nam := Make_Operator_Symbol (Loc,
7949 Chars => Chars (Formal_Sub),
7950 Strval => No_String);
7951 else
7952 Nam := Make_Identifier (Loc, Chars (Formal_Sub));
7953 end if;
7955 elsif Nkind (Specification (Formal)) = N_Procedure_Specification
7956 and then Null_Present (Specification (Formal))
7957 then
7958 -- Generate null body for procedure, for use in the instance
7960 Decl_Node :=
7961 Make_Subprogram_Body (Loc,
7962 Specification => New_Spec,
7963 Declarations => New_List,
7964 Handled_Statement_Sequence =>
7965 Make_Handled_Sequence_Of_Statements (Loc,
7966 Statements => New_List (Make_Null_Statement (Loc))));
7968 Set_Is_Intrinsic_Subprogram (Defining_Unit_Name (New_Spec));
7969 return Decl_Node;
7971 else
7972 Error_Msg_Sloc := Sloc (Scope (Analyzed_S));
7973 Error_Msg_NE
7974 ("missing actual&", Instantiation_Node, Formal_Sub);
7975 Error_Msg_NE
7976 ("\in instantiation of & declared#",
7977 Instantiation_Node, Scope (Analyzed_S));
7978 Abandon_Instantiation (Instantiation_Node);
7979 end if;
7981 Decl_Node :=
7982 Make_Subprogram_Renaming_Declaration (Loc,
7983 Specification => New_Spec,
7984 Name => Nam);
7986 -- If we do not have an actual and the formal specified <> then set to
7987 -- get proper default.
7989 if No (Actual) and then Box_Present (Formal) then
7990 Set_From_Default (Decl_Node);
7991 end if;
7993 -- Gather possible interpretations for the actual before analyzing the
7994 -- instance. If overloaded, it will be resolved when analyzing the
7995 -- renaming declaration.
7997 if Box_Present (Formal)
7998 and then No (Actual)
7999 then
8000 Analyze (Nam);
8002 if Is_Child_Unit (Scope (Analyzed_S))
8003 and then Present (Entity (Nam))
8004 then
8005 if not Is_Overloaded (Nam) then
8007 if From_Parent_Scope (Entity (Nam)) then
8008 Set_Is_Immediately_Visible (Entity (Nam), False);
8009 Set_Entity (Nam, Empty);
8010 Set_Etype (Nam, Empty);
8012 Analyze (Nam);
8014 Set_Is_Immediately_Visible (Entity (Nam));
8015 end if;
8017 else
8018 declare
8019 I : Interp_Index;
8020 It : Interp;
8022 begin
8023 Get_First_Interp (Nam, I, It);
8025 while Present (It.Nam) loop
8026 if From_Parent_Scope (It.Nam) then
8027 Remove_Interp (I);
8028 end if;
8030 Get_Next_Interp (I, It);
8031 end loop;
8032 end;
8033 end if;
8034 end if;
8035 end if;
8037 -- The generic instantiation freezes the actual. This can only be done
8038 -- once the actual is resolved, in the analysis of the renaming
8039 -- declaration. To make the formal subprogram entity available, we set
8040 -- Corresponding_Formal_Spec to point to the formal subprogram entity.
8041 -- This is also needed in Analyze_Subprogram_Renaming for the processing
8042 -- of formal abstract subprograms.
8044 Set_Corresponding_Formal_Spec (Decl_Node, Analyzed_S);
8046 -- We cannot analyze the renaming declaration, and thus find the actual,
8047 -- until all the actuals are assembled in the instance. For subsequent
8048 -- checks of other actuals, indicate the node that will hold the
8049 -- instance of this formal.
8051 Set_Instance_Of (Analyzed_S, Nam);
8053 if Nkind (Actual) = N_Selected_Component
8054 and then Is_Task_Type (Etype (Prefix (Actual)))
8055 and then not Is_Frozen (Etype (Prefix (Actual)))
8056 then
8057 -- The renaming declaration will create a body, which must appear
8058 -- outside of the instantiation, We move the renaming declaration
8059 -- out of the instance, and create an additional renaming inside,
8060 -- to prevent freezing anomalies.
8062 declare
8063 Anon_Id : constant Entity_Id :=
8064 Make_Defining_Identifier
8065 (Loc, New_Internal_Name ('E'));
8066 begin
8067 Set_Defining_Unit_Name (New_Spec, Anon_Id);
8068 Insert_Before (Instantiation_Node, Decl_Node);
8069 Analyze (Decl_Node);
8071 -- Now create renaming within the instance
8073 Decl_Node :=
8074 Make_Subprogram_Renaming_Declaration (Loc,
8075 Specification => New_Copy_Tree (New_Spec),
8076 Name => New_Occurrence_Of (Anon_Id, Loc));
8078 Set_Defining_Unit_Name (Specification (Decl_Node),
8079 Make_Defining_Identifier (Loc, Chars (Formal_Sub)));
8080 end;
8081 end if;
8083 return Decl_Node;
8084 end Instantiate_Formal_Subprogram;
8086 ------------------------
8087 -- Instantiate_Object --
8088 ------------------------
8090 function Instantiate_Object
8091 (Formal : Node_Id;
8092 Actual : Node_Id;
8093 Analyzed_Formal : Node_Id) return List_Id
8095 Acc_Def : Node_Id := Empty;
8096 Act_Assoc : constant Node_Id := Parent (Actual);
8097 Actual_Decl : Node_Id := Empty;
8098 Formal_Id : constant Entity_Id := Defining_Identifier (Formal);
8099 Decl_Node : Node_Id;
8100 Def : Node_Id;
8101 Ftyp : Entity_Id;
8102 List : constant List_Id := New_List;
8103 Loc : constant Source_Ptr := Sloc (Actual);
8104 Orig_Ftyp : constant Entity_Id :=
8105 Etype (Defining_Identifier (Analyzed_Formal));
8106 Subt_Decl : Node_Id := Empty;
8107 Subt_Mark : Node_Id := Empty;
8109 begin
8110 if Present (Subtype_Mark (Formal)) then
8111 Subt_Mark := Subtype_Mark (Formal);
8112 else
8113 Check_Access_Definition (Formal);
8114 Acc_Def := Access_Definition (Formal);
8115 end if;
8117 -- Sloc for error message on missing actual
8119 Error_Msg_Sloc := Sloc (Scope (Defining_Identifier (Analyzed_Formal)));
8121 if Get_Instance_Of (Formal_Id) /= Formal_Id then
8122 Error_Msg_N ("duplicate instantiation of generic parameter", Actual);
8123 end if;
8125 Set_Parent (List, Parent (Actual));
8127 -- OUT present
8129 if Out_Present (Formal) then
8131 -- An IN OUT generic actual must be a name. The instantiation is a
8132 -- renaming declaration. The actual is the name being renamed. We
8133 -- use the actual directly, rather than a copy, because it is not
8134 -- used further in the list of actuals, and because a copy or a use
8135 -- of relocate_node is incorrect if the instance is nested within a
8136 -- generic. In order to simplify ASIS searches, the Generic_Parent
8137 -- field links the declaration to the generic association.
8139 if No (Actual) then
8140 Error_Msg_NE
8141 ("missing actual&",
8142 Instantiation_Node, Formal_Id);
8143 Error_Msg_NE
8144 ("\in instantiation of & declared#",
8145 Instantiation_Node,
8146 Scope (Defining_Identifier (Analyzed_Formal)));
8147 Abandon_Instantiation (Instantiation_Node);
8148 end if;
8150 if Present (Subt_Mark) then
8151 Decl_Node :=
8152 Make_Object_Renaming_Declaration (Loc,
8153 Defining_Identifier => New_Copy (Formal_Id),
8154 Subtype_Mark => New_Copy_Tree (Subt_Mark),
8155 Name => Actual);
8157 else pragma Assert (Present (Acc_Def));
8158 Decl_Node :=
8159 Make_Object_Renaming_Declaration (Loc,
8160 Defining_Identifier => New_Copy (Formal_Id),
8161 Access_Definition => New_Copy_Tree (Acc_Def),
8162 Name => Actual);
8163 end if;
8165 Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc);
8167 -- The analysis of the actual may produce insert_action nodes, so
8168 -- the declaration must have a context in which to attach them.
8170 Append (Decl_Node, List);
8171 Analyze (Actual);
8173 -- Return if the analysis of the actual reported some error
8175 if Etype (Actual) = Any_Type then
8176 return List;
8177 end if;
8179 -- This check is performed here because Analyze_Object_Renaming will
8180 -- not check it when Comes_From_Source is False. Note though that the
8181 -- check for the actual being the name of an object will be performed
8182 -- in Analyze_Object_Renaming.
8184 if Is_Object_Reference (Actual)
8185 and then Is_Dependent_Component_Of_Mutable_Object (Actual)
8186 then
8187 Error_Msg_N
8188 ("illegal discriminant-dependent component for in out parameter",
8189 Actual);
8190 end if;
8192 -- The actual has to be resolved in order to check that it is a
8193 -- variable (due to cases such as F(1), where F returns
8194 -- access to an array, and for overloaded prefixes).
8196 Ftyp :=
8197 Get_Instance_Of (Etype (Defining_Identifier (Analyzed_Formal)));
8199 if Is_Private_Type (Ftyp)
8200 and then not Is_Private_Type (Etype (Actual))
8201 and then (Base_Type (Full_View (Ftyp)) = Base_Type (Etype (Actual))
8202 or else Base_Type (Etype (Actual)) = Ftyp)
8203 then
8204 -- If the actual has the type of the full view of the formal, or
8205 -- else a non-private subtype of the formal, then the visibility
8206 -- of the formal type has changed. Add to the actuals a subtype
8207 -- declaration that will force the exchange of views in the body
8208 -- of the instance as well.
8210 Subt_Decl :=
8211 Make_Subtype_Declaration (Loc,
8212 Defining_Identifier =>
8213 Make_Defining_Identifier (Loc, New_Internal_Name ('P')),
8214 Subtype_Indication => New_Occurrence_Of (Ftyp, Loc));
8216 Prepend (Subt_Decl, List);
8218 Prepend_Elmt (Full_View (Ftyp), Exchanged_Views);
8219 Exchange_Declarations (Ftyp);
8220 end if;
8222 Resolve (Actual, Ftyp);
8224 if not Denotes_Variable (Actual) then
8225 Error_Msg_NE
8226 ("actual for& must be a variable", Actual, Formal_Id);
8228 elsif Base_Type (Ftyp) /= Base_Type (Etype (Actual)) then
8230 -- Ada 2005 (AI-423): For a generic formal object of mode in out,
8231 -- the type of the actual shall resolve to a specific anonymous
8232 -- access type.
8234 if Ada_Version < Ada_05
8235 or else
8236 Ekind (Base_Type (Ftyp)) /=
8237 E_Anonymous_Access_Type
8238 or else
8239 Ekind (Base_Type (Etype (Actual))) /=
8240 E_Anonymous_Access_Type
8241 then
8242 Error_Msg_NE ("type of actual does not match type of&",
8243 Actual, Formal_Id);
8244 end if;
8245 end if;
8247 Note_Possible_Modification (Actual, Sure => True);
8249 -- Check for instantiation of atomic/volatile actual for
8250 -- non-atomic/volatile formal (RM C.6 (12)).
8252 if Is_Atomic_Object (Actual)
8253 and then not Is_Atomic (Orig_Ftyp)
8254 then
8255 Error_Msg_N
8256 ("cannot instantiate non-atomic formal object " &
8257 "with atomic actual", Actual);
8259 elsif Is_Volatile_Object (Actual)
8260 and then not Is_Volatile (Orig_Ftyp)
8261 then
8262 Error_Msg_N
8263 ("cannot instantiate non-volatile formal object " &
8264 "with volatile actual", Actual);
8265 end if;
8267 -- OUT not present
8269 else
8270 -- The instantiation of a generic formal in-parameter is constant
8271 -- declaration. The actual is the expression for that declaration.
8273 if Present (Actual) then
8274 if Present (Subt_Mark) then
8275 Def := Subt_Mark;
8276 else pragma Assert (Present (Acc_Def));
8277 Def := Acc_Def;
8278 end if;
8280 Decl_Node :=
8281 Make_Object_Declaration (Loc,
8282 Defining_Identifier => New_Copy (Formal_Id),
8283 Constant_Present => True,
8284 Object_Definition => New_Copy_Tree (Def),
8285 Expression => Actual);
8287 Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc);
8289 -- A generic formal object of a tagged type is defined to be
8290 -- aliased so the new constant must also be treated as aliased.
8292 if Is_Tagged_Type
8293 (Etype (Defining_Identifier (Analyzed_Formal)))
8294 then
8295 Set_Aliased_Present (Decl_Node);
8296 end if;
8298 Append (Decl_Node, List);
8300 -- No need to repeat (pre-)analysis of some expression nodes
8301 -- already handled in Preanalyze_Actuals.
8303 if Nkind (Actual) /= N_Allocator then
8304 Analyze (Actual);
8306 -- Return if the analysis of the actual reported some error
8308 if Etype (Actual) = Any_Type then
8309 return List;
8310 end if;
8311 end if;
8313 declare
8314 Typ : constant Entity_Id :=
8315 Get_Instance_Of
8316 (Etype (Defining_Identifier (Analyzed_Formal)));
8318 begin
8319 Freeze_Before (Instantiation_Node, Typ);
8321 -- If the actual is an aggregate, perform name resolution on
8322 -- its components (the analysis of an aggregate does not do it)
8323 -- to capture local names that may be hidden if the generic is
8324 -- a child unit.
8326 if Nkind (Actual) = N_Aggregate then
8327 Preanalyze_And_Resolve (Actual, Typ);
8328 end if;
8330 if Is_Limited_Type (Typ)
8331 and then not OK_For_Limited_Init (Actual)
8332 then
8333 Error_Msg_N
8334 ("initialization not allowed for limited types", Actual);
8335 Explain_Limited_Type (Typ, Actual);
8336 end if;
8337 end;
8339 elsif Present (Default_Expression (Formal)) then
8341 -- Use default to construct declaration
8343 if Present (Subt_Mark) then
8344 Def := Subt_Mark;
8345 else pragma Assert (Present (Acc_Def));
8346 Def := Acc_Def;
8347 end if;
8349 Decl_Node :=
8350 Make_Object_Declaration (Sloc (Formal),
8351 Defining_Identifier => New_Copy (Formal_Id),
8352 Constant_Present => True,
8353 Object_Definition => New_Copy (Def),
8354 Expression => New_Copy_Tree (Default_Expression
8355 (Formal)));
8357 Append (Decl_Node, List);
8358 Set_Analyzed (Expression (Decl_Node), False);
8360 else
8361 Error_Msg_NE
8362 ("missing actual&",
8363 Instantiation_Node, Formal_Id);
8364 Error_Msg_NE ("\in instantiation of & declared#",
8365 Instantiation_Node,
8366 Scope (Defining_Identifier (Analyzed_Formal)));
8368 if Is_Scalar_Type
8369 (Etype (Defining_Identifier (Analyzed_Formal)))
8370 then
8371 -- Create dummy constant declaration so that instance can be
8372 -- analyzed, to minimize cascaded visibility errors.
8374 if Present (Subt_Mark) then
8375 Def := Subt_Mark;
8376 else pragma Assert (Present (Acc_Def));
8377 Def := Acc_Def;
8378 end if;
8380 Decl_Node :=
8381 Make_Object_Declaration (Loc,
8382 Defining_Identifier => New_Copy (Formal_Id),
8383 Constant_Present => True,
8384 Object_Definition => New_Copy (Def),
8385 Expression =>
8386 Make_Attribute_Reference (Sloc (Formal_Id),
8387 Attribute_Name => Name_First,
8388 Prefix => New_Copy (Def)));
8390 Append (Decl_Node, List);
8392 else
8393 Abandon_Instantiation (Instantiation_Node);
8394 end if;
8395 end if;
8396 end if;
8398 if Nkind (Actual) in N_Has_Entity then
8399 Actual_Decl := Parent (Entity (Actual));
8400 end if;
8402 -- Ada 2005 (AI-423): For a formal object declaration with a null
8403 -- exclusion or an access definition that has a null exclusion: If the
8404 -- actual matching the formal object declaration denotes a generic
8405 -- formal object of another generic unit G, and the instantiation
8406 -- containing the actual occurs within the body of G or within the body
8407 -- of a generic unit declared within the declarative region of G, then
8408 -- the declaration of the formal object of G must have a null exclusion.
8409 -- Otherwise, the subtype of the actual matching the formal object
8410 -- declaration shall exclude null.
8412 if Ada_Version >= Ada_05
8413 and then Present (Actual_Decl)
8414 and then
8415 Nkind_In (Actual_Decl, N_Formal_Object_Declaration,
8416 N_Object_Declaration)
8417 and then Nkind (Analyzed_Formal) = N_Formal_Object_Declaration
8418 and then not Has_Null_Exclusion (Actual_Decl)
8419 and then Has_Null_Exclusion (Analyzed_Formal)
8420 then
8421 Error_Msg_Sloc := Sloc (Analyzed_Formal);
8422 Error_Msg_N
8423 ("actual must exclude null to match generic formal#", Actual);
8424 end if;
8426 return List;
8427 end Instantiate_Object;
8429 ------------------------------
8430 -- Instantiate_Package_Body --
8431 ------------------------------
8433 procedure Instantiate_Package_Body
8434 (Body_Info : Pending_Body_Info;
8435 Inlined_Body : Boolean := False;
8436 Body_Optional : Boolean := False)
8438 Act_Decl : constant Node_Id := Body_Info.Act_Decl;
8439 Inst_Node : constant Node_Id := Body_Info.Inst_Node;
8440 Loc : constant Source_Ptr := Sloc (Inst_Node);
8442 Gen_Id : constant Node_Id := Name (Inst_Node);
8443 Gen_Unit : constant Entity_Id := Get_Generic_Entity (Inst_Node);
8444 Gen_Decl : constant Node_Id := Unit_Declaration_Node (Gen_Unit);
8445 Act_Spec : constant Node_Id := Specification (Act_Decl);
8446 Act_Decl_Id : constant Entity_Id := Defining_Entity (Act_Spec);
8448 Act_Body_Name : Node_Id;
8449 Gen_Body : Node_Id;
8450 Gen_Body_Id : Node_Id;
8451 Act_Body : Node_Id;
8452 Act_Body_Id : Entity_Id;
8454 Parent_Installed : Boolean := False;
8455 Save_Style_Check : constant Boolean := Style_Check;
8457 begin
8458 Gen_Body_Id := Corresponding_Body (Gen_Decl);
8460 -- The instance body may already have been processed, as the parent of
8461 -- another instance that is inlined (Load_Parent_Of_Generic).
8463 if Present (Corresponding_Body (Instance_Spec (Inst_Node))) then
8464 return;
8465 end if;
8467 Expander_Mode_Save_And_Set (Body_Info.Expander_Status);
8469 -- Re-establish the state of information on which checks are suppressed.
8470 -- This information was set in Body_Info at the point of instantiation,
8471 -- and now we restore it so that the instance is compiled using the
8472 -- check status at the instantiation (RM 11.5 (7.2/2), AI95-00224-01).
8474 Local_Suppress_Stack_Top := Body_Info.Local_Suppress_Stack_Top;
8475 Scope_Suppress := Body_Info.Scope_Suppress;
8477 if No (Gen_Body_Id) then
8478 Load_Parent_Of_Generic
8479 (Inst_Node, Specification (Gen_Decl), Body_Optional);
8480 Gen_Body_Id := Corresponding_Body (Gen_Decl);
8481 end if;
8483 -- Establish global variable for sloc adjustment and for error recovery
8485 Instantiation_Node := Inst_Node;
8487 if Present (Gen_Body_Id) then
8488 Save_Env (Gen_Unit, Act_Decl_Id);
8489 Style_Check := False;
8490 Current_Sem_Unit := Body_Info.Current_Sem_Unit;
8492 Gen_Body := Unit_Declaration_Node (Gen_Body_Id);
8494 Create_Instantiation_Source
8495 (Inst_Node, Gen_Body_Id, False, S_Adjustment);
8497 Act_Body :=
8498 Copy_Generic_Node
8499 (Original_Node (Gen_Body), Empty, Instantiating => True);
8501 -- Build new name (possibly qualified) for body declaration
8503 Act_Body_Id := New_Copy (Act_Decl_Id);
8505 -- Some attributes of spec entity are not inherited by body entity
8507 Set_Handler_Records (Act_Body_Id, No_List);
8509 if Nkind (Defining_Unit_Name (Act_Spec)) =
8510 N_Defining_Program_Unit_Name
8511 then
8512 Act_Body_Name :=
8513 Make_Defining_Program_Unit_Name (Loc,
8514 Name => New_Copy_Tree (Name (Defining_Unit_Name (Act_Spec))),
8515 Defining_Identifier => Act_Body_Id);
8516 else
8517 Act_Body_Name := Act_Body_Id;
8518 end if;
8520 Set_Defining_Unit_Name (Act_Body, Act_Body_Name);
8522 Set_Corresponding_Spec (Act_Body, Act_Decl_Id);
8523 Check_Generic_Actuals (Act_Decl_Id, False);
8525 -- If it is a child unit, make the parent instance (which is an
8526 -- instance of the parent of the generic) visible. The parent
8527 -- instance is the prefix of the name of the generic unit.
8529 if Ekind (Scope (Gen_Unit)) = E_Generic_Package
8530 and then Nkind (Gen_Id) = N_Expanded_Name
8531 then
8532 Install_Parent (Entity (Prefix (Gen_Id)), In_Body => True);
8533 Parent_Installed := True;
8535 elsif Is_Child_Unit (Gen_Unit) then
8536 Install_Parent (Scope (Gen_Unit), In_Body => True);
8537 Parent_Installed := True;
8538 end if;
8540 -- If the instantiation is a library unit, and this is the main unit,
8541 -- then build the resulting compilation unit nodes for the instance.
8542 -- If this is a compilation unit but it is not the main unit, then it
8543 -- is the body of a unit in the context, that is being compiled
8544 -- because it is encloses some inlined unit or another generic unit
8545 -- being instantiated. In that case, this body is not part of the
8546 -- current compilation, and is not attached to the tree, but its
8547 -- parent must be set for analysis.
8549 if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
8551 -- Replace instance node with body of instance, and create new
8552 -- node for corresponding instance declaration.
8554 Build_Instance_Compilation_Unit_Nodes
8555 (Inst_Node, Act_Body, Act_Decl);
8556 Analyze (Inst_Node);
8558 if Parent (Inst_Node) = Cunit (Main_Unit) then
8560 -- If the instance is a child unit itself, then set the scope
8561 -- of the expanded body to be the parent of the instantiation
8562 -- (ensuring that the fully qualified name will be generated
8563 -- for the elaboration subprogram).
8565 if Nkind (Defining_Unit_Name (Act_Spec)) =
8566 N_Defining_Program_Unit_Name
8567 then
8568 Set_Scope
8569 (Defining_Entity (Inst_Node), Scope (Act_Decl_Id));
8570 end if;
8571 end if;
8573 -- Case where instantiation is not a library unit
8575 else
8576 -- If this is an early instantiation, i.e. appears textually
8577 -- before the corresponding body and must be elaborated first,
8578 -- indicate that the body instance is to be delayed.
8580 Install_Body (Act_Body, Inst_Node, Gen_Body, Gen_Decl);
8582 -- Now analyze the body. We turn off all checks if this is an
8583 -- internal unit, since there is no reason to have checks on for
8584 -- any predefined run-time library code. All such code is designed
8585 -- to be compiled with checks off.
8587 -- Note that we do NOT apply this criterion to children of GNAT
8588 -- (or on VMS, children of DEC). The latter units must suppress
8589 -- checks explicitly if this is needed.
8591 if Is_Predefined_File_Name
8592 (Unit_File_Name (Get_Source_Unit (Gen_Decl)))
8593 then
8594 Analyze (Act_Body, Suppress => All_Checks);
8595 else
8596 Analyze (Act_Body);
8597 end if;
8598 end if;
8600 Inherit_Context (Gen_Body, Inst_Node);
8602 -- Remove the parent instances if they have been placed on the scope
8603 -- stack to compile the body.
8605 if Parent_Installed then
8606 Remove_Parent (In_Body => True);
8607 end if;
8609 Restore_Private_Views (Act_Decl_Id);
8611 -- Remove the current unit from visibility if this is an instance
8612 -- that is not elaborated on the fly for inlining purposes.
8614 if not Inlined_Body then
8615 Set_Is_Immediately_Visible (Act_Decl_Id, False);
8616 end if;
8618 Restore_Env;
8619 Style_Check := Save_Style_Check;
8621 -- If we have no body, and the unit requires a body, then complain. This
8622 -- complaint is suppressed if we have detected other errors (since a
8623 -- common reason for missing the body is that it had errors).
8625 elsif Unit_Requires_Body (Gen_Unit)
8626 and then not Body_Optional
8627 then
8628 if Serious_Errors_Detected = 0 then
8629 Error_Msg_NE
8630 ("cannot find body of generic package &", Inst_Node, Gen_Unit);
8632 -- Don't attempt to perform any cleanup actions if some other error
8633 -- was already detected, since this can cause blowups.
8635 else
8636 return;
8637 end if;
8639 -- Case of package that does not need a body
8641 else
8642 -- If the instantiation of the declaration is a library unit, rewrite
8643 -- the original package instantiation as a package declaration in the
8644 -- compilation unit node.
8646 if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
8647 Set_Parent_Spec (Act_Decl, Parent_Spec (Inst_Node));
8648 Rewrite (Inst_Node, Act_Decl);
8650 -- Generate elaboration entity, in case spec has elaboration code.
8651 -- This cannot be done when the instance is analyzed, because it
8652 -- is not known yet whether the body exists.
8654 Set_Elaboration_Entity_Required (Act_Decl_Id, False);
8655 Build_Elaboration_Entity (Parent (Inst_Node), Act_Decl_Id);
8657 -- If the instantiation is not a library unit, then append the
8658 -- declaration to the list of implicitly generated entities, unless
8659 -- it is already a list member which means that it was already
8660 -- processed
8662 elsif not Is_List_Member (Act_Decl) then
8663 Mark_Rewrite_Insertion (Act_Decl);
8664 Insert_Before (Inst_Node, Act_Decl);
8665 end if;
8666 end if;
8668 Expander_Mode_Restore;
8669 end Instantiate_Package_Body;
8671 ---------------------------------
8672 -- Instantiate_Subprogram_Body --
8673 ---------------------------------
8675 procedure Instantiate_Subprogram_Body
8676 (Body_Info : Pending_Body_Info;
8677 Body_Optional : Boolean := False)
8679 Act_Decl : constant Node_Id := Body_Info.Act_Decl;
8680 Inst_Node : constant Node_Id := Body_Info.Inst_Node;
8681 Loc : constant Source_Ptr := Sloc (Inst_Node);
8682 Gen_Id : constant Node_Id := Name (Inst_Node);
8683 Gen_Unit : constant Entity_Id := Get_Generic_Entity (Inst_Node);
8684 Gen_Decl : constant Node_Id := Unit_Declaration_Node (Gen_Unit);
8685 Anon_Id : constant Entity_Id :=
8686 Defining_Unit_Name (Specification (Act_Decl));
8687 Pack_Id : constant Entity_Id :=
8688 Defining_Unit_Name (Parent (Act_Decl));
8689 Decls : List_Id;
8690 Gen_Body : Node_Id;
8691 Gen_Body_Id : Node_Id;
8692 Act_Body : Node_Id;
8693 Pack_Body : Node_Id;
8694 Prev_Formal : Entity_Id;
8695 Ret_Expr : Node_Id;
8696 Unit_Renaming : Node_Id;
8698 Parent_Installed : Boolean := False;
8699 Save_Style_Check : constant Boolean := Style_Check;
8701 begin
8702 Gen_Body_Id := Corresponding_Body (Gen_Decl);
8704 Expander_Mode_Save_And_Set (Body_Info.Expander_Status);
8706 -- Re-establish the state of information on which checks are suppressed.
8707 -- This information was set in Body_Info at the point of instantiation,
8708 -- and now we restore it so that the instance is compiled using the
8709 -- check status at the instantiation (RM 11.5 (7.2/2), AI95-00224-01).
8711 Local_Suppress_Stack_Top := Body_Info.Local_Suppress_Stack_Top;
8712 Scope_Suppress := Body_Info.Scope_Suppress;
8714 if No (Gen_Body_Id) then
8716 -- For imported generic subprogram, no body to compile, complete
8717 -- the spec entity appropriately.
8719 if Is_Imported (Gen_Unit) then
8720 Set_Is_Imported (Anon_Id);
8721 Set_First_Rep_Item (Anon_Id, First_Rep_Item (Gen_Unit));
8722 Set_Interface_Name (Anon_Id, Interface_Name (Gen_Unit));
8723 Set_Convention (Anon_Id, Convention (Gen_Unit));
8724 Set_Has_Completion (Anon_Id);
8725 return;
8727 -- For other cases, compile the body
8729 else
8730 Load_Parent_Of_Generic
8731 (Inst_Node, Specification (Gen_Decl), Body_Optional);
8732 Gen_Body_Id := Corresponding_Body (Gen_Decl);
8733 end if;
8734 end if;
8736 Instantiation_Node := Inst_Node;
8738 if Present (Gen_Body_Id) then
8739 Gen_Body := Unit_Declaration_Node (Gen_Body_Id);
8741 if Nkind (Gen_Body) = N_Subprogram_Body_Stub then
8743 -- Either body is not present, or context is non-expanding, as
8744 -- when compiling a subunit. Mark the instance as completed, and
8745 -- diagnose a missing body when needed.
8747 if Expander_Active
8748 and then Operating_Mode = Generate_Code
8749 then
8750 Error_Msg_N
8751 ("missing proper body for instantiation", Gen_Body);
8752 end if;
8754 Set_Has_Completion (Anon_Id);
8755 return;
8756 end if;
8758 Save_Env (Gen_Unit, Anon_Id);
8759 Style_Check := False;
8760 Current_Sem_Unit := Body_Info.Current_Sem_Unit;
8761 Create_Instantiation_Source
8762 (Inst_Node,
8763 Gen_Body_Id,
8764 False,
8765 S_Adjustment);
8767 Act_Body :=
8768 Copy_Generic_Node
8769 (Original_Node (Gen_Body), Empty, Instantiating => True);
8771 -- Create proper defining name for the body, to correspond to
8772 -- the one in the spec.
8774 Set_Defining_Unit_Name (Specification (Act_Body),
8775 Make_Defining_Identifier
8776 (Sloc (Defining_Entity (Inst_Node)), Chars (Anon_Id)));
8777 Set_Corresponding_Spec (Act_Body, Anon_Id);
8778 Set_Has_Completion (Anon_Id);
8779 Check_Generic_Actuals (Pack_Id, False);
8781 -- Generate a reference to link the visible subprogram instance to
8782 -- the generic body, which for navigation purposes is the only
8783 -- available source for the instance.
8785 Generate_Reference
8786 (Related_Instance (Pack_Id),
8787 Gen_Body_Id, 'b', Set_Ref => False, Force => True);
8789 -- If it is a child unit, make the parent instance (which is an
8790 -- instance of the parent of the generic) visible. The parent
8791 -- instance is the prefix of the name of the generic unit.
8793 if Ekind (Scope (Gen_Unit)) = E_Generic_Package
8794 and then Nkind (Gen_Id) = N_Expanded_Name
8795 then
8796 Install_Parent (Entity (Prefix (Gen_Id)), In_Body => True);
8797 Parent_Installed := True;
8799 elsif Is_Child_Unit (Gen_Unit) then
8800 Install_Parent (Scope (Gen_Unit), In_Body => True);
8801 Parent_Installed := True;
8802 end if;
8804 -- Inside its body, a reference to the generic unit is a reference
8805 -- to the instance. The corresponding renaming is the first
8806 -- declaration in the body.
8808 Unit_Renaming :=
8809 Make_Subprogram_Renaming_Declaration (Loc,
8810 Specification =>
8811 Copy_Generic_Node (
8812 Specification (Original_Node (Gen_Body)),
8813 Empty,
8814 Instantiating => True),
8815 Name => New_Occurrence_Of (Anon_Id, Loc));
8817 -- If there is a formal subprogram with the same name as the unit
8818 -- itself, do not add this renaming declaration. This is a temporary
8819 -- fix for one ACVC test. ???
8821 Prev_Formal := First_Entity (Pack_Id);
8822 while Present (Prev_Formal) loop
8823 if Chars (Prev_Formal) = Chars (Gen_Unit)
8824 and then Is_Overloadable (Prev_Formal)
8825 then
8826 exit;
8827 end if;
8829 Next_Entity (Prev_Formal);
8830 end loop;
8832 if Present (Prev_Formal) then
8833 Decls := New_List (Act_Body);
8834 else
8835 Decls := New_List (Unit_Renaming, Act_Body);
8836 end if;
8838 -- The subprogram body is placed in the body of a dummy package body,
8839 -- whose spec contains the subprogram declaration as well as the
8840 -- renaming declarations for the generic parameters.
8842 Pack_Body := Make_Package_Body (Loc,
8843 Defining_Unit_Name => New_Copy (Pack_Id),
8844 Declarations => Decls);
8846 Set_Corresponding_Spec (Pack_Body, Pack_Id);
8848 -- If the instantiation is a library unit, then build resulting
8849 -- compilation unit nodes for the instance. The declaration of
8850 -- the enclosing package is the grandparent of the subprogram
8851 -- declaration. First replace the instantiation node as the unit
8852 -- of the corresponding compilation.
8854 if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then
8855 if Parent (Inst_Node) = Cunit (Main_Unit) then
8856 Set_Unit (Parent (Inst_Node), Inst_Node);
8857 Build_Instance_Compilation_Unit_Nodes
8858 (Inst_Node, Pack_Body, Parent (Parent (Act_Decl)));
8859 Analyze (Inst_Node);
8860 else
8861 Set_Parent (Pack_Body, Parent (Inst_Node));
8862 Analyze (Pack_Body);
8863 end if;
8865 else
8866 Insert_Before (Inst_Node, Pack_Body);
8867 Mark_Rewrite_Insertion (Pack_Body);
8868 Analyze (Pack_Body);
8870 if Expander_Active then
8871 Freeze_Subprogram_Body (Inst_Node, Gen_Body, Pack_Id);
8872 end if;
8873 end if;
8875 Inherit_Context (Gen_Body, Inst_Node);
8877 Restore_Private_Views (Pack_Id, False);
8879 if Parent_Installed then
8880 Remove_Parent (In_Body => True);
8881 end if;
8883 Restore_Env;
8884 Style_Check := Save_Style_Check;
8886 -- Body not found. Error was emitted already. If there were no previous
8887 -- errors, this may be an instance whose scope is a premature instance.
8888 -- In that case we must insure that the (legal) program does raise
8889 -- program error if executed. We generate a subprogram body for this
8890 -- purpose. See DEC ac30vso.
8892 -- Should not reference proprietary DEC tests in comments ???
8894 elsif Serious_Errors_Detected = 0
8895 and then Nkind (Parent (Inst_Node)) /= N_Compilation_Unit
8896 then
8897 if Body_Optional then
8898 return;
8900 elsif Ekind (Anon_Id) = E_Procedure then
8901 Act_Body :=
8902 Make_Subprogram_Body (Loc,
8903 Specification =>
8904 Make_Procedure_Specification (Loc,
8905 Defining_Unit_Name =>
8906 Make_Defining_Identifier (Loc, Chars (Anon_Id)),
8907 Parameter_Specifications =>
8908 New_Copy_List
8909 (Parameter_Specifications (Parent (Anon_Id)))),
8911 Declarations => Empty_List,
8912 Handled_Statement_Sequence =>
8913 Make_Handled_Sequence_Of_Statements (Loc,
8914 Statements =>
8915 New_List (
8916 Make_Raise_Program_Error (Loc,
8917 Reason =>
8918 PE_Access_Before_Elaboration))));
8920 else
8921 Ret_Expr :=
8922 Make_Raise_Program_Error (Loc,
8923 Reason => PE_Access_Before_Elaboration);
8925 Set_Etype (Ret_Expr, (Etype (Anon_Id)));
8926 Set_Analyzed (Ret_Expr);
8928 Act_Body :=
8929 Make_Subprogram_Body (Loc,
8930 Specification =>
8931 Make_Function_Specification (Loc,
8932 Defining_Unit_Name =>
8933 Make_Defining_Identifier (Loc, Chars (Anon_Id)),
8934 Parameter_Specifications =>
8935 New_Copy_List
8936 (Parameter_Specifications (Parent (Anon_Id))),
8937 Result_Definition =>
8938 New_Occurrence_Of (Etype (Anon_Id), Loc)),
8940 Declarations => Empty_List,
8941 Handled_Statement_Sequence =>
8942 Make_Handled_Sequence_Of_Statements (Loc,
8943 Statements =>
8944 New_List
8945 (Make_Simple_Return_Statement (Loc, Ret_Expr))));
8946 end if;
8948 Pack_Body := Make_Package_Body (Loc,
8949 Defining_Unit_Name => New_Copy (Pack_Id),
8950 Declarations => New_List (Act_Body));
8952 Insert_After (Inst_Node, Pack_Body);
8953 Set_Corresponding_Spec (Pack_Body, Pack_Id);
8954 Analyze (Pack_Body);
8955 end if;
8957 Expander_Mode_Restore;
8958 end Instantiate_Subprogram_Body;
8960 ----------------------
8961 -- Instantiate_Type --
8962 ----------------------
8964 function Instantiate_Type
8965 (Formal : Node_Id;
8966 Actual : Node_Id;
8967 Analyzed_Formal : Node_Id;
8968 Actual_Decls : List_Id) return List_Id
8970 Gen_T : constant Entity_Id := Defining_Identifier (Formal);
8971 A_Gen_T : constant Entity_Id :=
8972 Defining_Identifier (Analyzed_Formal);
8973 Ancestor : Entity_Id := Empty;
8974 Def : constant Node_Id := Formal_Type_Definition (Formal);
8975 Act_T : Entity_Id;
8976 Decl_Node : Node_Id;
8977 Decl_Nodes : List_Id;
8978 Loc : Source_Ptr;
8979 Subt : Entity_Id;
8981 procedure Validate_Array_Type_Instance;
8982 procedure Validate_Access_Subprogram_Instance;
8983 procedure Validate_Access_Type_Instance;
8984 procedure Validate_Derived_Type_Instance;
8985 procedure Validate_Derived_Interface_Type_Instance;
8986 procedure Validate_Interface_Type_Instance;
8987 procedure Validate_Private_Type_Instance;
8988 -- These procedures perform validation tests for the named case
8990 function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean;
8991 -- Check that base types are the same and that the subtypes match
8992 -- statically. Used in several of the above.
8994 --------------------
8995 -- Subtypes_Match --
8996 --------------------
8998 function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean is
8999 T : constant Entity_Id := Get_Instance_Of (Gen_T);
9001 begin
9002 return (Base_Type (T) = Base_Type (Act_T)
9003 and then Subtypes_Statically_Match (T, Act_T))
9005 or else (Is_Class_Wide_Type (Gen_T)
9006 and then Is_Class_Wide_Type (Act_T)
9007 and then
9008 Subtypes_Match
9009 (Get_Instance_Of (Root_Type (Gen_T)),
9010 Root_Type (Act_T)))
9012 or else
9013 ((Ekind (Gen_T) = E_Anonymous_Access_Subprogram_Type
9014 or else Ekind (Gen_T) = E_Anonymous_Access_Type)
9015 and then Ekind (Act_T) = Ekind (Gen_T)
9016 and then
9017 Subtypes_Statically_Match
9018 (Designated_Type (Gen_T), Designated_Type (Act_T)));
9019 end Subtypes_Match;
9021 -----------------------------------------
9022 -- Validate_Access_Subprogram_Instance --
9023 -----------------------------------------
9025 procedure Validate_Access_Subprogram_Instance is
9026 begin
9027 if not Is_Access_Type (Act_T)
9028 or else Ekind (Designated_Type (Act_T)) /= E_Subprogram_Type
9029 then
9030 Error_Msg_NE
9031 ("expect access type in instantiation of &", Actual, Gen_T);
9032 Abandon_Instantiation (Actual);
9033 end if;
9035 Check_Mode_Conformant
9036 (Designated_Type (Act_T),
9037 Designated_Type (A_Gen_T),
9038 Actual,
9039 Get_Inst => True);
9041 if Ekind (Base_Type (Act_T)) = E_Access_Protected_Subprogram_Type then
9042 if Ekind (A_Gen_T) = E_Access_Subprogram_Type then
9043 Error_Msg_NE
9044 ("protected access type not allowed for formal &",
9045 Actual, Gen_T);
9046 end if;
9048 elsif Ekind (A_Gen_T) = E_Access_Protected_Subprogram_Type then
9049 Error_Msg_NE
9050 ("expect protected access type for formal &",
9051 Actual, Gen_T);
9052 end if;
9053 end Validate_Access_Subprogram_Instance;
9055 -----------------------------------
9056 -- Validate_Access_Type_Instance --
9057 -----------------------------------
9059 procedure Validate_Access_Type_Instance is
9060 Desig_Type : constant Entity_Id :=
9061 Find_Actual_Type (Designated_Type (A_Gen_T), A_Gen_T);
9062 Desig_Act : Entity_Id;
9064 begin
9065 if not Is_Access_Type (Act_T) then
9066 Error_Msg_NE
9067 ("expect access type in instantiation of &", Actual, Gen_T);
9068 Abandon_Instantiation (Actual);
9069 end if;
9071 if Is_Access_Constant (A_Gen_T) then
9072 if not Is_Access_Constant (Act_T) then
9073 Error_Msg_N
9074 ("actual type must be access-to-constant type", Actual);
9075 Abandon_Instantiation (Actual);
9076 end if;
9077 else
9078 if Is_Access_Constant (Act_T) then
9079 Error_Msg_N
9080 ("actual type must be access-to-variable type", Actual);
9081 Abandon_Instantiation (Actual);
9083 elsif Ekind (A_Gen_T) = E_General_Access_Type
9084 and then Ekind (Base_Type (Act_T)) /= E_General_Access_Type
9085 then
9086 Error_Msg_N ("actual must be general access type!", Actual);
9087 Error_Msg_NE ("add ALL to }!", Actual, Act_T);
9088 Abandon_Instantiation (Actual);
9089 end if;
9090 end if;
9092 -- The designated subtypes, that is to say the subtypes introduced
9093 -- by an access type declaration (and not by a subtype declaration)
9094 -- must match.
9096 Desig_Act := Designated_Type (Base_Type (Act_T));
9098 -- The designated type may have been introduced through a limited_
9099 -- with clause, in which case retrieve the non-limited view. This
9100 -- applies to incomplete types as well as to class-wide types.
9102 if From_With_Type (Desig_Act) then
9103 Desig_Act := Available_View (Desig_Act);
9104 end if;
9106 if not Subtypes_Match
9107 (Desig_Type, Desig_Act) then
9108 Error_Msg_NE
9109 ("designated type of actual does not match that of formal &",
9110 Actual, Gen_T);
9111 Abandon_Instantiation (Actual);
9113 elsif Is_Access_Type (Designated_Type (Act_T))
9114 and then Is_Constrained (Designated_Type (Designated_Type (Act_T)))
9116 Is_Constrained (Designated_Type (Desig_Type))
9117 then
9118 Error_Msg_NE
9119 ("designated type of actual does not match that of formal &",
9120 Actual, Gen_T);
9121 Abandon_Instantiation (Actual);
9122 end if;
9124 -- Ada 2005: null-exclusion indicators of the two types must agree
9126 if Can_Never_Be_Null (A_Gen_T) /= Can_Never_Be_Null (Act_T) then
9127 Error_Msg_NE
9128 ("non null exclusion of actual and formal & do not match",
9129 Actual, Gen_T);
9130 end if;
9131 end Validate_Access_Type_Instance;
9133 ----------------------------------
9134 -- Validate_Array_Type_Instance --
9135 ----------------------------------
9137 procedure Validate_Array_Type_Instance is
9138 I1 : Node_Id;
9139 I2 : Node_Id;
9140 T2 : Entity_Id;
9142 function Formal_Dimensions return Int;
9143 -- Count number of dimensions in array type formal
9145 -----------------------
9146 -- Formal_Dimensions --
9147 -----------------------
9149 function Formal_Dimensions return Int is
9150 Num : Int := 0;
9151 Index : Node_Id;
9153 begin
9154 if Nkind (Def) = N_Constrained_Array_Definition then
9155 Index := First (Discrete_Subtype_Definitions (Def));
9156 else
9157 Index := First (Subtype_Marks (Def));
9158 end if;
9160 while Present (Index) loop
9161 Num := Num + 1;
9162 Next_Index (Index);
9163 end loop;
9165 return Num;
9166 end Formal_Dimensions;
9168 -- Start of processing for Validate_Array_Type_Instance
9170 begin
9171 if not Is_Array_Type (Act_T) then
9172 Error_Msg_NE
9173 ("expect array type in instantiation of &", Actual, Gen_T);
9174 Abandon_Instantiation (Actual);
9176 elsif Nkind (Def) = N_Constrained_Array_Definition then
9177 if not (Is_Constrained (Act_T)) then
9178 Error_Msg_NE
9179 ("expect constrained array in instantiation of &",
9180 Actual, Gen_T);
9181 Abandon_Instantiation (Actual);
9182 end if;
9184 else
9185 if Is_Constrained (Act_T) then
9186 Error_Msg_NE
9187 ("expect unconstrained array in instantiation of &",
9188 Actual, Gen_T);
9189 Abandon_Instantiation (Actual);
9190 end if;
9191 end if;
9193 if Formal_Dimensions /= Number_Dimensions (Act_T) then
9194 Error_Msg_NE
9195 ("dimensions of actual do not match formal &", Actual, Gen_T);
9196 Abandon_Instantiation (Actual);
9197 end if;
9199 I1 := First_Index (A_Gen_T);
9200 I2 := First_Index (Act_T);
9201 for J in 1 .. Formal_Dimensions loop
9203 -- If the indices of the actual were given by a subtype_mark,
9204 -- the index was transformed into a range attribute. Retrieve
9205 -- the original type mark for checking.
9207 if Is_Entity_Name (Original_Node (I2)) then
9208 T2 := Entity (Original_Node (I2));
9209 else
9210 T2 := Etype (I2);
9211 end if;
9213 if not Subtypes_Match
9214 (Find_Actual_Type (Etype (I1), A_Gen_T), T2)
9215 then
9216 Error_Msg_NE
9217 ("index types of actual do not match those of formal &",
9218 Actual, Gen_T);
9219 Abandon_Instantiation (Actual);
9220 end if;
9222 Next_Index (I1);
9223 Next_Index (I2);
9224 end loop;
9226 if not Subtypes_Match
9227 (Find_Actual_Type (Component_Type (A_Gen_T), A_Gen_T),
9228 Component_Type (Act_T))
9229 then
9230 Error_Msg_NE
9231 ("component subtype of actual does not match that of formal &",
9232 Actual, Gen_T);
9233 Abandon_Instantiation (Actual);
9234 end if;
9236 if Has_Aliased_Components (A_Gen_T)
9237 and then not Has_Aliased_Components (Act_T)
9238 then
9239 Error_Msg_NE
9240 ("actual must have aliased components to match formal type &",
9241 Actual, Gen_T);
9242 end if;
9243 end Validate_Array_Type_Instance;
9245 -----------------------------------------------
9246 -- Validate_Derived_Interface_Type_Instance --
9247 -----------------------------------------------
9249 procedure Validate_Derived_Interface_Type_Instance is
9250 Par : constant Entity_Id := Entity (Subtype_Indication (Def));
9251 Elmt : Elmt_Id;
9253 begin
9254 -- First apply interface instance checks
9256 Validate_Interface_Type_Instance;
9258 -- Verify that immediate parent interface is an ancestor of
9259 -- the actual.
9261 if Present (Par)
9262 and then not Interface_Present_In_Ancestor (Act_T, Par)
9263 then
9264 Error_Msg_NE
9265 ("interface actual must include progenitor&", Actual, Par);
9266 end if;
9268 -- Now verify that the actual includes all other ancestors of
9269 -- the formal.
9271 Elmt := First_Elmt (Interfaces (A_Gen_T));
9272 while Present (Elmt) loop
9273 if not Interface_Present_In_Ancestor
9274 (Act_T, Get_Instance_Of (Node (Elmt)))
9275 then
9276 Error_Msg_NE
9277 ("interface actual must include progenitor&",
9278 Actual, Node (Elmt));
9279 end if;
9281 Next_Elmt (Elmt);
9282 end loop;
9283 end Validate_Derived_Interface_Type_Instance;
9285 ------------------------------------
9286 -- Validate_Derived_Type_Instance --
9287 ------------------------------------
9289 procedure Validate_Derived_Type_Instance is
9290 Actual_Discr : Entity_Id;
9291 Ancestor_Discr : Entity_Id;
9293 begin
9294 -- If the parent type in the generic declaration is itself a previous
9295 -- formal type, then it is local to the generic and absent from the
9296 -- analyzed generic definition. In that case the ancestor is the
9297 -- instance of the formal (which must have been instantiated
9298 -- previously), unless the ancestor is itself a formal derived type.
9299 -- In this latter case (which is the subject of Corrigendum 8652/0038
9300 -- (AI-202) the ancestor of the formals is the ancestor of its
9301 -- parent. Otherwise, the analyzed generic carries the parent type.
9302 -- If the parent type is defined in a previous formal package, then
9303 -- the scope of that formal package is that of the generic type
9304 -- itself, and it has already been mapped into the corresponding type
9305 -- in the actual package.
9307 -- Common case: parent type defined outside of the generic
9309 if Is_Entity_Name (Subtype_Mark (Def))
9310 and then Present (Entity (Subtype_Mark (Def)))
9311 then
9312 Ancestor := Get_Instance_Of (Entity (Subtype_Mark (Def)));
9314 -- Check whether parent is defined in a previous formal package
9316 elsif
9317 Scope (Scope (Base_Type (Etype (A_Gen_T)))) = Scope (A_Gen_T)
9318 then
9319 Ancestor :=
9320 Get_Instance_Of (Base_Type (Etype (A_Gen_T)));
9322 -- The type may be a local derivation, or a type extension of a
9323 -- previous formal, or of a formal of a parent package.
9325 elsif Is_Derived_Type (Get_Instance_Of (A_Gen_T))
9326 or else
9327 Ekind (Get_Instance_Of (A_Gen_T)) = E_Record_Type_With_Private
9328 then
9329 -- Check whether the parent is another derived formal type in the
9330 -- same generic unit.
9332 if Etype (A_Gen_T) /= A_Gen_T
9333 and then Is_Generic_Type (Etype (A_Gen_T))
9334 and then Scope (Etype (A_Gen_T)) = Scope (A_Gen_T)
9335 and then Etype (Etype (A_Gen_T)) /= Etype (A_Gen_T)
9336 then
9337 -- Locate ancestor of parent from the subtype declaration
9338 -- created for the actual.
9340 declare
9341 Decl : Node_Id;
9343 begin
9344 Decl := First (Actual_Decls);
9345 while Present (Decl) loop
9346 if Nkind (Decl) = N_Subtype_Declaration
9347 and then Chars (Defining_Identifier (Decl)) =
9348 Chars (Etype (A_Gen_T))
9349 then
9350 Ancestor := Generic_Parent_Type (Decl);
9351 exit;
9352 else
9353 Next (Decl);
9354 end if;
9355 end loop;
9356 end;
9358 pragma Assert (Present (Ancestor));
9360 else
9361 Ancestor :=
9362 Get_Instance_Of (Base_Type (Get_Instance_Of (A_Gen_T)));
9363 end if;
9365 else
9366 Ancestor := Get_Instance_Of (Etype (Base_Type (A_Gen_T)));
9367 end if;
9369 -- If the formal derived type has pragma Preelaborable_Initialization
9370 -- then the actual type must have preelaborable initialization.
9372 if Known_To_Have_Preelab_Init (A_Gen_T)
9373 and then not Has_Preelaborable_Initialization (Act_T)
9374 then
9375 Error_Msg_NE
9376 ("actual for & must have preelaborable initialization",
9377 Actual, Gen_T);
9378 end if;
9380 -- Ada 2005 (AI-251)
9382 if Ada_Version >= Ada_05
9383 and then Is_Interface (Ancestor)
9384 then
9385 if not Interface_Present_In_Ancestor (Act_T, Ancestor) then
9386 Error_Msg_NE
9387 ("(Ada 2005) expected type implementing & in instantiation",
9388 Actual, Ancestor);
9389 end if;
9391 elsif not Is_Ancestor (Base_Type (Ancestor), Act_T) then
9392 Error_Msg_NE
9393 ("expect type derived from & in instantiation",
9394 Actual, First_Subtype (Ancestor));
9395 Abandon_Instantiation (Actual);
9396 end if;
9398 -- Ada 2005 (AI-443): Synchronized formal derived type checks. Note
9399 -- that the formal type declaration has been rewritten as a private
9400 -- extension.
9402 if Ada_Version >= Ada_05
9403 and then Nkind (Parent (A_Gen_T)) = N_Private_Extension_Declaration
9404 and then Synchronized_Present (Parent (A_Gen_T))
9405 then
9406 -- The actual must be a synchronized tagged type
9408 if not Is_Tagged_Type (Act_T) then
9409 Error_Msg_N
9410 ("actual of synchronized type must be tagged", Actual);
9411 Abandon_Instantiation (Actual);
9413 elsif Nkind (Parent (Act_T)) = N_Full_Type_Declaration
9414 and then Nkind (Type_Definition (Parent (Act_T))) =
9415 N_Derived_Type_Definition
9416 and then not Synchronized_Present (Type_Definition
9417 (Parent (Act_T)))
9418 then
9419 Error_Msg_N
9420 ("actual of synchronized type must be synchronized", Actual);
9421 Abandon_Instantiation (Actual);
9422 end if;
9423 end if;
9425 -- Perform atomic/volatile checks (RM C.6(12))
9427 if Is_Atomic (Act_T) and then not Is_Atomic (Ancestor) then
9428 Error_Msg_N
9429 ("cannot have atomic actual type for non-atomic formal type",
9430 Actual);
9432 elsif Is_Volatile (Act_T)
9433 and then not Is_Volatile (Ancestor)
9434 and then Is_By_Reference_Type (Ancestor)
9435 then
9436 Error_Msg_N
9437 ("cannot have volatile actual type for non-volatile formal type",
9438 Actual);
9439 end if;
9441 -- It should not be necessary to check for unknown discriminants on
9442 -- Formal, but for some reason Has_Unknown_Discriminants is false for
9443 -- A_Gen_T, so Is_Indefinite_Subtype incorrectly returns False. This
9444 -- needs fixing. ???
9446 if not Is_Indefinite_Subtype (A_Gen_T)
9447 and then not Unknown_Discriminants_Present (Formal)
9448 and then Is_Indefinite_Subtype (Act_T)
9449 then
9450 Error_Msg_N
9451 ("actual subtype must be constrained", Actual);
9452 Abandon_Instantiation (Actual);
9453 end if;
9455 if not Unknown_Discriminants_Present (Formal) then
9456 if Is_Constrained (Ancestor) then
9457 if not Is_Constrained (Act_T) then
9458 Error_Msg_N
9459 ("actual subtype must be constrained", Actual);
9460 Abandon_Instantiation (Actual);
9461 end if;
9463 -- Ancestor is unconstrained, Check if generic formal and actual
9464 -- agree on constrainedness. The check only applies to array types
9465 -- and discriminated types.
9467 elsif Is_Constrained (Act_T) then
9468 if Ekind (Ancestor) = E_Access_Type
9469 or else
9470 (not Is_Constrained (A_Gen_T)
9471 and then Is_Composite_Type (A_Gen_T))
9472 then
9473 Error_Msg_N
9474 ("actual subtype must be unconstrained", Actual);
9475 Abandon_Instantiation (Actual);
9476 end if;
9478 -- A class-wide type is only allowed if the formal has unknown
9479 -- discriminants.
9481 elsif Is_Class_Wide_Type (Act_T)
9482 and then not Has_Unknown_Discriminants (Ancestor)
9483 then
9484 Error_Msg_NE
9485 ("actual for & cannot be a class-wide type", Actual, Gen_T);
9486 Abandon_Instantiation (Actual);
9488 -- Otherwise, the formal and actual shall have the same number
9489 -- of discriminants and each discriminant of the actual must
9490 -- correspond to a discriminant of the formal.
9492 elsif Has_Discriminants (Act_T)
9493 and then not Has_Unknown_Discriminants (Act_T)
9494 and then Has_Discriminants (Ancestor)
9495 then
9496 Actual_Discr := First_Discriminant (Act_T);
9497 Ancestor_Discr := First_Discriminant (Ancestor);
9498 while Present (Actual_Discr)
9499 and then Present (Ancestor_Discr)
9500 loop
9501 if Base_Type (Act_T) /= Base_Type (Ancestor) and then
9502 No (Corresponding_Discriminant (Actual_Discr))
9503 then
9504 Error_Msg_NE
9505 ("discriminant & does not correspond " &
9506 "to ancestor discriminant", Actual, Actual_Discr);
9507 Abandon_Instantiation (Actual);
9508 end if;
9510 Next_Discriminant (Actual_Discr);
9511 Next_Discriminant (Ancestor_Discr);
9512 end loop;
9514 if Present (Actual_Discr) or else Present (Ancestor_Discr) then
9515 Error_Msg_NE
9516 ("actual for & must have same number of discriminants",
9517 Actual, Gen_T);
9518 Abandon_Instantiation (Actual);
9519 end if;
9521 -- This case should be caught by the earlier check for for
9522 -- constrainedness, but the check here is added for completeness.
9524 elsif Has_Discriminants (Act_T)
9525 and then not Has_Unknown_Discriminants (Act_T)
9526 then
9527 Error_Msg_NE
9528 ("actual for & must not have discriminants", Actual, Gen_T);
9529 Abandon_Instantiation (Actual);
9531 elsif Has_Discriminants (Ancestor) then
9532 Error_Msg_NE
9533 ("actual for & must have known discriminants", Actual, Gen_T);
9534 Abandon_Instantiation (Actual);
9535 end if;
9537 if not Subtypes_Statically_Compatible (Act_T, Ancestor) then
9538 Error_Msg_N
9539 ("constraint on actual is incompatible with formal", Actual);
9540 Abandon_Instantiation (Actual);
9541 end if;
9542 end if;
9544 -- If the formal and actual types are abstract, check that there
9545 -- are no abstract primitives of the actual type that correspond to
9546 -- nonabstract primitives of the formal type (second sentence of
9547 -- RM95-3.9.3(9)).
9549 if Is_Abstract_Type (A_Gen_T) and then Is_Abstract_Type (Act_T) then
9550 Check_Abstract_Primitives : declare
9551 Gen_Prims : constant Elist_Id :=
9552 Primitive_Operations (A_Gen_T);
9553 Gen_Elmt : Elmt_Id;
9554 Gen_Subp : Entity_Id;
9555 Anc_Subp : Entity_Id;
9556 Anc_Formal : Entity_Id;
9557 Anc_F_Type : Entity_Id;
9559 Act_Prims : constant Elist_Id := Primitive_Operations (Act_T);
9560 Act_Elmt : Elmt_Id;
9561 Act_Subp : Entity_Id;
9562 Act_Formal : Entity_Id;
9563 Act_F_Type : Entity_Id;
9565 Subprograms_Correspond : Boolean;
9567 function Is_Tagged_Ancestor (T1, T2 : Entity_Id) return Boolean;
9568 -- Returns true if T2 is derived directly or indirectly from
9569 -- T1, including derivations from interfaces. T1 and T2 are
9570 -- required to be specific tagged base types.
9572 ------------------------
9573 -- Is_Tagged_Ancestor --
9574 ------------------------
9576 function Is_Tagged_Ancestor (T1, T2 : Entity_Id) return Boolean
9578 Intfc_Elmt : Elmt_Id;
9580 begin
9581 -- The predicate is satisfied if the types are the same
9583 if T1 = T2 then
9584 return True;
9586 -- If we've reached the top of the derivation chain then
9587 -- we know that T1 is not an ancestor of T2.
9589 elsif Etype (T2) = T2 then
9590 return False;
9592 -- Proceed to check T2's immediate parent
9594 elsif Is_Ancestor (T1, Base_Type (Etype (T2))) then
9595 return True;
9597 -- Finally, check to see if T1 is an ancestor of any of T2's
9598 -- progenitors.
9600 else
9601 Intfc_Elmt := First_Elmt (Interfaces (T2));
9602 while Present (Intfc_Elmt) loop
9603 if Is_Ancestor (T1, Node (Intfc_Elmt)) then
9604 return True;
9605 end if;
9607 Next_Elmt (Intfc_Elmt);
9608 end loop;
9609 end if;
9611 return False;
9612 end Is_Tagged_Ancestor;
9614 -- Start of processing for Check_Abstract_Primitives
9616 begin
9617 -- Loop over all of the formal derived type's primitives
9619 Gen_Elmt := First_Elmt (Gen_Prims);
9620 while Present (Gen_Elmt) loop
9621 Gen_Subp := Node (Gen_Elmt);
9623 -- If the primitive of the formal is not abstract, then
9624 -- determine whether there is a corresponding primitive of
9625 -- the actual type that's abstract.
9627 if not Is_Abstract_Subprogram (Gen_Subp) then
9628 Act_Elmt := First_Elmt (Act_Prims);
9629 while Present (Act_Elmt) loop
9630 Act_Subp := Node (Act_Elmt);
9632 -- If we find an abstract primitive of the actual,
9633 -- then we need to test whether it corresponds to the
9634 -- subprogram from which the generic formal primitive
9635 -- is inherited.
9637 if Is_Abstract_Subprogram (Act_Subp) then
9638 Anc_Subp := Alias (Gen_Subp);
9640 -- Test whether we have a corresponding primitive
9641 -- by comparing names, kinds, formal types, and
9642 -- result types.
9644 if Chars (Anc_Subp) = Chars (Act_Subp)
9645 and then Ekind (Anc_Subp) = Ekind (Act_Subp)
9646 then
9647 Anc_Formal := First_Formal (Anc_Subp);
9648 Act_Formal := First_Formal (Act_Subp);
9649 while Present (Anc_Formal)
9650 and then Present (Act_Formal)
9651 loop
9652 Anc_F_Type := Etype (Anc_Formal);
9653 Act_F_Type := Etype (Act_Formal);
9655 if Ekind (Anc_F_Type)
9656 = E_Anonymous_Access_Type
9657 then
9658 Anc_F_Type := Designated_Type (Anc_F_Type);
9660 if Ekind (Act_F_Type)
9661 = E_Anonymous_Access_Type
9662 then
9663 Act_F_Type :=
9664 Designated_Type (Act_F_Type);
9665 else
9666 exit;
9667 end if;
9669 elsif
9670 Ekind (Act_F_Type) = E_Anonymous_Access_Type
9671 then
9672 exit;
9673 end if;
9675 Anc_F_Type := Base_Type (Anc_F_Type);
9676 Act_F_Type := Base_Type (Act_F_Type);
9678 -- If the formal is controlling, then the
9679 -- the type of the actual primitive's formal
9680 -- must be derived directly or indirectly
9681 -- from the type of the ancestor primitive's
9682 -- formal.
9684 if Is_Controlling_Formal (Anc_Formal) then
9685 if not Is_Tagged_Ancestor
9686 (Anc_F_Type, Act_F_Type)
9687 then
9688 exit;
9689 end if;
9691 -- Otherwise the types of the formals must
9692 -- be the same.
9694 elsif Anc_F_Type /= Act_F_Type then
9695 exit;
9696 end if;
9698 Next_Entity (Anc_Formal);
9699 Next_Entity (Act_Formal);
9700 end loop;
9702 -- If we traversed through all of the formals
9703 -- then so far the subprograms correspond, so
9704 -- now check that any result types correspond.
9706 if No (Anc_Formal)
9707 and then No (Act_Formal)
9708 then
9709 Subprograms_Correspond := True;
9711 if Ekind (Act_Subp) = E_Function then
9712 Anc_F_Type := Etype (Anc_Subp);
9713 Act_F_Type := Etype (Act_Subp);
9715 if Ekind (Anc_F_Type)
9716 = E_Anonymous_Access_Type
9717 then
9718 Anc_F_Type :=
9719 Designated_Type (Anc_F_Type);
9721 if Ekind (Act_F_Type)
9722 = E_Anonymous_Access_Type
9723 then
9724 Act_F_Type :=
9725 Designated_Type (Act_F_Type);
9726 else
9727 Subprograms_Correspond := False;
9728 end if;
9730 elsif
9731 Ekind (Act_F_Type)
9732 = E_Anonymous_Access_Type
9733 then
9734 Subprograms_Correspond := False;
9735 end if;
9737 Anc_F_Type := Base_Type (Anc_F_Type);
9738 Act_F_Type := Base_Type (Act_F_Type);
9740 -- Now either the result types must be
9741 -- the same or, if the result type is
9742 -- controlling, the result type of the
9743 -- actual primitive must descend from the
9744 -- result type of the ancestor primitive.
9746 if Subprograms_Correspond
9747 and then Anc_F_Type /= Act_F_Type
9748 and then
9749 Has_Controlling_Result (Anc_Subp)
9750 and then
9751 not Is_Tagged_Ancestor
9752 (Anc_F_Type, Act_F_Type)
9753 then
9754 Subprograms_Correspond := False;
9755 end if;
9756 end if;
9758 -- Found a matching subprogram belonging to
9759 -- formal ancestor type, so actual subprogram
9760 -- corresponds and this violates 3.9.3(9).
9762 if Subprograms_Correspond then
9763 Error_Msg_NE
9764 ("abstract subprogram & overrides " &
9765 "nonabstract subprogram of ancestor",
9766 Actual,
9767 Act_Subp);
9768 end if;
9769 end if;
9770 end if;
9771 end if;
9773 Next_Elmt (Act_Elmt);
9774 end loop;
9775 end if;
9777 Next_Elmt (Gen_Elmt);
9778 end loop;
9779 end Check_Abstract_Primitives;
9780 end if;
9782 -- Verify that limitedness matches. If parent is a limited
9783 -- interface then the generic formal is not unless declared
9784 -- explicitly so. If not declared limited, the actual cannot be
9785 -- limited (see AI05-0087).
9786 -- Disable check for now, limited interfaces implemented by
9787 -- protected types are common, Need to update tests ???
9789 if Is_Limited_Type (Act_T)
9790 and then not Is_Limited_Type (A_Gen_T)
9791 and then False
9792 then
9793 Error_Msg_NE
9794 ("actual for non-limited & cannot be a limited type", Actual,
9795 Gen_T);
9796 Explain_Limited_Type (Act_T, Actual);
9797 Abandon_Instantiation (Actual);
9798 end if;
9799 end Validate_Derived_Type_Instance;
9801 --------------------------------------
9802 -- Validate_Interface_Type_Instance --
9803 --------------------------------------
9805 procedure Validate_Interface_Type_Instance is
9806 begin
9807 if not Is_Interface (Act_T) then
9808 Error_Msg_NE
9809 ("actual for formal interface type must be an interface",
9810 Actual, Gen_T);
9812 elsif Is_Limited_Type (Act_T) /= Is_Limited_Type (A_Gen_T)
9813 or else
9814 Is_Task_Interface (A_Gen_T) /= Is_Task_Interface (Act_T)
9815 or else
9816 Is_Protected_Interface (A_Gen_T) /=
9817 Is_Protected_Interface (Act_T)
9818 or else
9819 Is_Synchronized_Interface (A_Gen_T) /=
9820 Is_Synchronized_Interface (Act_T)
9821 then
9822 Error_Msg_NE
9823 ("actual for interface& does not match (RM 12.5.5(4))",
9824 Actual, Gen_T);
9825 end if;
9826 end Validate_Interface_Type_Instance;
9828 ------------------------------------
9829 -- Validate_Private_Type_Instance --
9830 ------------------------------------
9832 procedure Validate_Private_Type_Instance is
9833 Formal_Discr : Entity_Id;
9834 Actual_Discr : Entity_Id;
9835 Formal_Subt : Entity_Id;
9837 begin
9838 if Is_Limited_Type (Act_T)
9839 and then not Is_Limited_Type (A_Gen_T)
9840 then
9841 Error_Msg_NE
9842 ("actual for non-limited & cannot be a limited type", Actual,
9843 Gen_T);
9844 Explain_Limited_Type (Act_T, Actual);
9845 Abandon_Instantiation (Actual);
9847 elsif Known_To_Have_Preelab_Init (A_Gen_T)
9848 and then not Has_Preelaborable_Initialization (Act_T)
9849 then
9850 Error_Msg_NE
9851 ("actual for & must have preelaborable initialization", Actual,
9852 Gen_T);
9854 elsif Is_Indefinite_Subtype (Act_T)
9855 and then not Is_Indefinite_Subtype (A_Gen_T)
9856 and then Ada_Version >= Ada_95
9857 then
9858 Error_Msg_NE
9859 ("actual for & must be a definite subtype", Actual, Gen_T);
9861 elsif not Is_Tagged_Type (Act_T)
9862 and then Is_Tagged_Type (A_Gen_T)
9863 then
9864 Error_Msg_NE
9865 ("actual for & must be a tagged type", Actual, Gen_T);
9867 elsif Has_Discriminants (A_Gen_T) then
9868 if not Has_Discriminants (Act_T) then
9869 Error_Msg_NE
9870 ("actual for & must have discriminants", Actual, Gen_T);
9871 Abandon_Instantiation (Actual);
9873 elsif Is_Constrained (Act_T) then
9874 Error_Msg_NE
9875 ("actual for & must be unconstrained", Actual, Gen_T);
9876 Abandon_Instantiation (Actual);
9878 else
9879 Formal_Discr := First_Discriminant (A_Gen_T);
9880 Actual_Discr := First_Discriminant (Act_T);
9881 while Formal_Discr /= Empty loop
9882 if Actual_Discr = Empty then
9883 Error_Msg_NE
9884 ("discriminants on actual do not match formal",
9885 Actual, Gen_T);
9886 Abandon_Instantiation (Actual);
9887 end if;
9889 Formal_Subt := Get_Instance_Of (Etype (Formal_Discr));
9891 -- Access discriminants match if designated types do
9893 if Ekind (Base_Type (Formal_Subt)) = E_Anonymous_Access_Type
9894 and then (Ekind (Base_Type (Etype (Actual_Discr)))) =
9895 E_Anonymous_Access_Type
9896 and then
9897 Get_Instance_Of
9898 (Designated_Type (Base_Type (Formal_Subt))) =
9899 Designated_Type (Base_Type (Etype (Actual_Discr)))
9900 then
9901 null;
9903 elsif Base_Type (Formal_Subt) /=
9904 Base_Type (Etype (Actual_Discr))
9905 then
9906 Error_Msg_NE
9907 ("types of actual discriminants must match formal",
9908 Actual, Gen_T);
9909 Abandon_Instantiation (Actual);
9911 elsif not Subtypes_Statically_Match
9912 (Formal_Subt, Etype (Actual_Discr))
9913 and then Ada_Version >= Ada_95
9914 then
9915 Error_Msg_NE
9916 ("subtypes of actual discriminants must match formal",
9917 Actual, Gen_T);
9918 Abandon_Instantiation (Actual);
9919 end if;
9921 Next_Discriminant (Formal_Discr);
9922 Next_Discriminant (Actual_Discr);
9923 end loop;
9925 if Actual_Discr /= Empty then
9926 Error_Msg_NE
9927 ("discriminants on actual do not match formal",
9928 Actual, Gen_T);
9929 Abandon_Instantiation (Actual);
9930 end if;
9931 end if;
9933 end if;
9935 Ancestor := Gen_T;
9936 end Validate_Private_Type_Instance;
9938 -- Start of processing for Instantiate_Type
9940 begin
9941 if Get_Instance_Of (A_Gen_T) /= A_Gen_T then
9942 Error_Msg_N ("duplicate instantiation of generic type", Actual);
9943 return New_List (Error);
9945 elsif not Is_Entity_Name (Actual)
9946 or else not Is_Type (Entity (Actual))
9947 then
9948 Error_Msg_NE
9949 ("expect valid subtype mark to instantiate &", Actual, Gen_T);
9950 Abandon_Instantiation (Actual);
9952 else
9953 Act_T := Entity (Actual);
9955 -- Ada 2005 (AI-216): An Unchecked_Union subtype shall only be passed
9956 -- as a generic actual parameter if the corresponding formal type
9957 -- does not have a known_discriminant_part, or is a formal derived
9958 -- type that is an Unchecked_Union type.
9960 if Is_Unchecked_Union (Base_Type (Act_T)) then
9961 if not Has_Discriminants (A_Gen_T)
9962 or else
9963 (Is_Derived_Type (A_Gen_T)
9964 and then
9965 Is_Unchecked_Union (A_Gen_T))
9966 then
9967 null;
9968 else
9969 Error_Msg_N ("Unchecked_Union cannot be the actual for a" &
9970 " discriminated formal type", Act_T);
9972 end if;
9973 end if;
9975 -- Deal with fixed/floating restrictions
9977 if Is_Floating_Point_Type (Act_T) then
9978 Check_Restriction (No_Floating_Point, Actual);
9979 elsif Is_Fixed_Point_Type (Act_T) then
9980 Check_Restriction (No_Fixed_Point, Actual);
9981 end if;
9983 -- Deal with error of using incomplete type as generic actual.
9984 -- This includes limited views of a type, even if the non-limited
9985 -- view may be available.
9987 if Ekind (Act_T) = E_Incomplete_Type
9988 or else (Is_Class_Wide_Type (Act_T)
9989 and then
9990 Ekind (Root_Type (Act_T)) = E_Incomplete_Type)
9991 then
9992 if Is_Class_Wide_Type (Act_T)
9993 or else No (Full_View (Act_T))
9994 then
9995 Error_Msg_N ("premature use of incomplete type", Actual);
9996 Abandon_Instantiation (Actual);
9997 else
9998 Act_T := Full_View (Act_T);
9999 Set_Entity (Actual, Act_T);
10001 if Has_Private_Component (Act_T) then
10002 Error_Msg_N
10003 ("premature use of type with private component", Actual);
10004 end if;
10005 end if;
10007 -- Deal with error of premature use of private type as generic actual
10009 elsif Is_Private_Type (Act_T)
10010 and then Is_Private_Type (Base_Type (Act_T))
10011 and then not Is_Generic_Type (Act_T)
10012 and then not Is_Derived_Type (Act_T)
10013 and then No (Full_View (Root_Type (Act_T)))
10014 then
10015 Error_Msg_N ("premature use of private type", Actual);
10017 elsif Has_Private_Component (Act_T) then
10018 Error_Msg_N
10019 ("premature use of type with private component", Actual);
10020 end if;
10022 Set_Instance_Of (A_Gen_T, Act_T);
10024 -- If the type is generic, the class-wide type may also be used
10026 if Is_Tagged_Type (A_Gen_T)
10027 and then Is_Tagged_Type (Act_T)
10028 and then not Is_Class_Wide_Type (A_Gen_T)
10029 then
10030 Set_Instance_Of (Class_Wide_Type (A_Gen_T),
10031 Class_Wide_Type (Act_T));
10032 end if;
10034 if not Is_Abstract_Type (A_Gen_T)
10035 and then Is_Abstract_Type (Act_T)
10036 then
10037 Error_Msg_N
10038 ("actual of non-abstract formal cannot be abstract", Actual);
10039 end if;
10041 -- A generic scalar type is a first subtype for which we generate
10042 -- an anonymous base type. Indicate that the instance of this base
10043 -- is the base type of the actual.
10045 if Is_Scalar_Type (A_Gen_T) then
10046 Set_Instance_Of (Etype (A_Gen_T), Etype (Act_T));
10047 end if;
10048 end if;
10050 if Error_Posted (Act_T) then
10051 null;
10052 else
10053 case Nkind (Def) is
10054 when N_Formal_Private_Type_Definition =>
10055 Validate_Private_Type_Instance;
10057 when N_Formal_Derived_Type_Definition =>
10058 Validate_Derived_Type_Instance;
10060 when N_Formal_Discrete_Type_Definition =>
10061 if not Is_Discrete_Type (Act_T) then
10062 Error_Msg_NE
10063 ("expect discrete type in instantiation of&",
10064 Actual, Gen_T);
10065 Abandon_Instantiation (Actual);
10066 end if;
10068 when N_Formal_Signed_Integer_Type_Definition =>
10069 if not Is_Signed_Integer_Type (Act_T) then
10070 Error_Msg_NE
10071 ("expect signed integer type in instantiation of&",
10072 Actual, Gen_T);
10073 Abandon_Instantiation (Actual);
10074 end if;
10076 when N_Formal_Modular_Type_Definition =>
10077 if not Is_Modular_Integer_Type (Act_T) then
10078 Error_Msg_NE
10079 ("expect modular type in instantiation of &",
10080 Actual, Gen_T);
10081 Abandon_Instantiation (Actual);
10082 end if;
10084 when N_Formal_Floating_Point_Definition =>
10085 if not Is_Floating_Point_Type (Act_T) then
10086 Error_Msg_NE
10087 ("expect float type in instantiation of &", Actual, Gen_T);
10088 Abandon_Instantiation (Actual);
10089 end if;
10091 when N_Formal_Ordinary_Fixed_Point_Definition =>
10092 if not Is_Ordinary_Fixed_Point_Type (Act_T) then
10093 Error_Msg_NE
10094 ("expect ordinary fixed point type in instantiation of &",
10095 Actual, Gen_T);
10096 Abandon_Instantiation (Actual);
10097 end if;
10099 when N_Formal_Decimal_Fixed_Point_Definition =>
10100 if not Is_Decimal_Fixed_Point_Type (Act_T) then
10101 Error_Msg_NE
10102 ("expect decimal type in instantiation of &",
10103 Actual, Gen_T);
10104 Abandon_Instantiation (Actual);
10105 end if;
10107 when N_Array_Type_Definition =>
10108 Validate_Array_Type_Instance;
10110 when N_Access_To_Object_Definition =>
10111 Validate_Access_Type_Instance;
10113 when N_Access_Function_Definition |
10114 N_Access_Procedure_Definition =>
10115 Validate_Access_Subprogram_Instance;
10117 when N_Record_Definition =>
10118 Validate_Interface_Type_Instance;
10120 when N_Derived_Type_Definition =>
10121 Validate_Derived_Interface_Type_Instance;
10123 when others =>
10124 raise Program_Error;
10126 end case;
10127 end if;
10129 Subt := New_Copy (Gen_T);
10131 -- Use adjusted sloc of subtype name as the location for other nodes in
10132 -- the subtype declaration.
10134 Loc := Sloc (Subt);
10136 Decl_Node :=
10137 Make_Subtype_Declaration (Loc,
10138 Defining_Identifier => Subt,
10139 Subtype_Indication => New_Reference_To (Act_T, Loc));
10141 if Is_Private_Type (Act_T) then
10142 Set_Has_Private_View (Subtype_Indication (Decl_Node));
10144 elsif Is_Access_Type (Act_T)
10145 and then Is_Private_Type (Designated_Type (Act_T))
10146 then
10147 Set_Has_Private_View (Subtype_Indication (Decl_Node));
10148 end if;
10150 Decl_Nodes := New_List (Decl_Node);
10152 -- Flag actual derived types so their elaboration produces the
10153 -- appropriate renamings for the primitive operations of the ancestor.
10154 -- Flag actual for formal private types as well, to determine whether
10155 -- operations in the private part may override inherited operations.
10156 -- If the formal has an interface list, the ancestor is not the
10157 -- parent, but the analyzed formal that includes the interface
10158 -- operations of all its progenitors.
10160 if Nkind (Def) = N_Formal_Derived_Type_Definition then
10161 if Present (Interface_List (Def)) then
10162 Set_Generic_Parent_Type (Decl_Node, A_Gen_T);
10163 else
10164 Set_Generic_Parent_Type (Decl_Node, Ancestor);
10165 end if;
10167 elsif Nkind (Def) = N_Formal_Private_Type_Definition then
10168 Set_Generic_Parent_Type (Decl_Node, Ancestor);
10169 end if;
10171 -- If the actual is a synchronized type that implements an interface,
10172 -- the primitive operations are attached to the corresponding record,
10173 -- and we have to treat it as an additional generic actual, so that its
10174 -- primitive operations become visible in the instance. The task or
10175 -- protected type itself does not carry primitive operations.
10177 if Is_Concurrent_Type (Act_T)
10178 and then Is_Tagged_Type (Act_T)
10179 and then Present (Corresponding_Record_Type (Act_T))
10180 and then Present (Ancestor)
10181 and then Is_Interface (Ancestor)
10182 then
10183 declare
10184 Corr_Rec : constant Entity_Id :=
10185 Corresponding_Record_Type (Act_T);
10186 New_Corr : Entity_Id;
10187 Corr_Decl : Node_Id;
10189 begin
10190 New_Corr := Make_Defining_Identifier (Loc,
10191 Chars => New_Internal_Name ('S'));
10192 Corr_Decl :=
10193 Make_Subtype_Declaration (Loc,
10194 Defining_Identifier => New_Corr,
10195 Subtype_Indication =>
10196 New_Reference_To (Corr_Rec, Loc));
10197 Append_To (Decl_Nodes, Corr_Decl);
10199 if Ekind (Act_T) = E_Task_Type then
10200 Set_Ekind (Subt, E_Task_Subtype);
10201 else
10202 Set_Ekind (Subt, E_Protected_Subtype);
10203 end if;
10205 Set_Corresponding_Record_Type (Subt, Corr_Rec);
10206 Set_Generic_Parent_Type (Corr_Decl, Ancestor);
10207 Set_Generic_Parent_Type (Decl_Node, Empty);
10208 end;
10209 end if;
10211 return Decl_Nodes;
10212 end Instantiate_Type;
10214 -----------------------
10215 -- Is_Generic_Formal --
10216 -----------------------
10218 function Is_Generic_Formal (E : Entity_Id) return Boolean is
10219 Kind : Node_Kind;
10220 begin
10221 if No (E) then
10222 return False;
10223 else
10224 Kind := Nkind (Parent (E));
10225 return
10226 Nkind_In (Kind, N_Formal_Object_Declaration,
10227 N_Formal_Package_Declaration,
10228 N_Formal_Type_Declaration)
10229 or else
10230 (Is_Formal_Subprogram (E)
10231 and then
10232 Nkind (Parent (Parent (E))) in
10233 N_Formal_Subprogram_Declaration);
10234 end if;
10235 end Is_Generic_Formal;
10237 ---------------------
10238 -- Is_In_Main_Unit --
10239 ---------------------
10241 function Is_In_Main_Unit (N : Node_Id) return Boolean is
10242 Unum : constant Unit_Number_Type := Get_Source_Unit (N);
10243 Current_Unit : Node_Id;
10245 begin
10246 if Unum = Main_Unit then
10247 return True;
10249 -- If the current unit is a subunit then it is either the main unit or
10250 -- is being compiled as part of the main unit.
10252 elsif Nkind (N) = N_Compilation_Unit then
10253 return Nkind (Unit (N)) = N_Subunit;
10254 end if;
10256 Current_Unit := Parent (N);
10257 while Present (Current_Unit)
10258 and then Nkind (Current_Unit) /= N_Compilation_Unit
10259 loop
10260 Current_Unit := Parent (Current_Unit);
10261 end loop;
10263 -- The instantiation node is in the main unit, or else the current node
10264 -- (perhaps as the result of nested instantiations) is in the main unit,
10265 -- or in the declaration of the main unit, which in this last case must
10266 -- be a body.
10268 return Unum = Main_Unit
10269 or else Current_Unit = Cunit (Main_Unit)
10270 or else Current_Unit = Library_Unit (Cunit (Main_Unit))
10271 or else (Present (Library_Unit (Current_Unit))
10272 and then Is_In_Main_Unit (Library_Unit (Current_Unit)));
10273 end Is_In_Main_Unit;
10275 ----------------------------
10276 -- Load_Parent_Of_Generic --
10277 ----------------------------
10279 procedure Load_Parent_Of_Generic
10280 (N : Node_Id;
10281 Spec : Node_Id;
10282 Body_Optional : Boolean := False)
10284 Comp_Unit : constant Node_Id := Cunit (Get_Source_Unit (Spec));
10285 Save_Style_Check : constant Boolean := Style_Check;
10286 True_Parent : Node_Id;
10287 Inst_Node : Node_Id;
10288 OK : Boolean;
10289 Previous_Instances : constant Elist_Id := New_Elmt_List;
10291 procedure Collect_Previous_Instances (Decls : List_Id);
10292 -- Collect all instantiations in the given list of declarations, that
10293 -- precede the generic that we need to load. If the bodies of these
10294 -- instantiations are available, we must analyze them, to ensure that
10295 -- the public symbols generated are the same when the unit is compiled
10296 -- to generate code, and when it is compiled in the context of a unit
10297 -- that needs a particular nested instance. This process is applied
10298 -- to both package and subprogram instances.
10300 --------------------------------
10301 -- Collect_Previous_Instances --
10302 --------------------------------
10304 procedure Collect_Previous_Instances (Decls : List_Id) is
10305 Decl : Node_Id;
10307 begin
10308 Decl := First (Decls);
10309 while Present (Decl) loop
10310 if Sloc (Decl) >= Sloc (Inst_Node) then
10311 return;
10313 -- If Decl is an instantiation, then record it as requiring
10314 -- instantiation of the corresponding body, except if it is an
10315 -- abbreviated instantiation generated internally for conformance
10316 -- checking purposes only for the case of a formal package
10317 -- declared without a box (see Instantiate_Formal_Package). Such
10318 -- an instantiation does not generate any code (the actual code
10319 -- comes from actual) and thus does not need to be analyzed here.
10321 elsif Nkind (Decl) = N_Package_Instantiation
10322 and then not Is_Internal (Defining_Entity (Decl))
10323 then
10324 Append_Elmt (Decl, Previous_Instances);
10326 -- For a subprogram instantiation, omit instantiations of
10327 -- intrinsic operations (Unchecked_Conversions, etc.) that
10328 -- have no bodies.
10330 elsif Nkind_In (Decl, N_Function_Instantiation,
10331 N_Procedure_Instantiation)
10332 and then not Is_Intrinsic_Subprogram (Entity (Name (Decl)))
10333 then
10334 Append_Elmt (Decl, Previous_Instances);
10336 elsif Nkind (Decl) = N_Package_Declaration then
10337 Collect_Previous_Instances
10338 (Visible_Declarations (Specification (Decl)));
10339 Collect_Previous_Instances
10340 (Private_Declarations (Specification (Decl)));
10342 elsif Nkind (Decl) = N_Package_Body then
10343 Collect_Previous_Instances (Declarations (Decl));
10344 end if;
10346 Next (Decl);
10347 end loop;
10348 end Collect_Previous_Instances;
10350 -- Start of processing for Load_Parent_Of_Generic
10352 begin
10353 if not In_Same_Source_Unit (N, Spec)
10354 or else Nkind (Unit (Comp_Unit)) = N_Package_Declaration
10355 or else (Nkind (Unit (Comp_Unit)) = N_Package_Body
10356 and then not Is_In_Main_Unit (Spec))
10357 then
10358 -- Find body of parent of spec, and analyze it. A special case arises
10359 -- when the parent is an instantiation, that is to say when we are
10360 -- currently instantiating a nested generic. In that case, there is
10361 -- no separate file for the body of the enclosing instance. Instead,
10362 -- the enclosing body must be instantiated as if it were a pending
10363 -- instantiation, in order to produce the body for the nested generic
10364 -- we require now. Note that in that case the generic may be defined
10365 -- in a package body, the instance defined in the same package body,
10366 -- and the original enclosing body may not be in the main unit.
10368 Inst_Node := Empty;
10370 True_Parent := Parent (Spec);
10371 while Present (True_Parent)
10372 and then Nkind (True_Parent) /= N_Compilation_Unit
10373 loop
10374 if Nkind (True_Parent) = N_Package_Declaration
10375 and then
10376 Nkind (Original_Node (True_Parent)) = N_Package_Instantiation
10377 then
10378 -- Parent is a compilation unit that is an instantiation.
10379 -- Instantiation node has been replaced with package decl.
10381 Inst_Node := Original_Node (True_Parent);
10382 exit;
10384 elsif Nkind (True_Parent) = N_Package_Declaration
10385 and then Present (Generic_Parent (Specification (True_Parent)))
10386 and then Nkind (Parent (True_Parent)) /= N_Compilation_Unit
10387 then
10388 -- Parent is an instantiation within another specification.
10389 -- Declaration for instance has been inserted before original
10390 -- instantiation node. A direct link would be preferable?
10392 Inst_Node := Next (True_Parent);
10393 while Present (Inst_Node)
10394 and then Nkind (Inst_Node) /= N_Package_Instantiation
10395 loop
10396 Next (Inst_Node);
10397 end loop;
10399 -- If the instance appears within a generic, and the generic
10400 -- unit is defined within a formal package of the enclosing
10401 -- generic, there is no generic body available, and none
10402 -- needed. A more precise test should be used ???
10404 if No (Inst_Node) then
10405 return;
10406 end if;
10408 exit;
10410 else
10411 True_Parent := Parent (True_Parent);
10412 end if;
10413 end loop;
10415 -- Case where we are currently instantiating a nested generic
10417 if Present (Inst_Node) then
10418 if Nkind (Parent (True_Parent)) = N_Compilation_Unit then
10420 -- Instantiation node and declaration of instantiated package
10421 -- were exchanged when only the declaration was needed.
10422 -- Restore instantiation node before proceeding with body.
10424 Set_Unit (Parent (True_Parent), Inst_Node);
10425 end if;
10427 -- Now complete instantiation of enclosing body, if it appears
10428 -- in some other unit. If it appears in the current unit, the
10429 -- body will have been instantiated already.
10431 if No (Corresponding_Body (Instance_Spec (Inst_Node))) then
10433 -- We need to determine the expander mode to instantiate the
10434 -- enclosing body. Because the generic body we need may use
10435 -- global entities declared in the enclosing package (including
10436 -- aggregates) it is in general necessary to compile this body
10437 -- with expansion enabled. The exception is if we are within a
10438 -- generic package, in which case the usual generic rule
10439 -- applies.
10441 declare
10442 Exp_Status : Boolean := True;
10443 Scop : Entity_Id;
10445 begin
10446 -- Loop through scopes looking for generic package
10448 Scop := Scope (Defining_Entity (Instance_Spec (Inst_Node)));
10449 while Present (Scop)
10450 and then Scop /= Standard_Standard
10451 loop
10452 if Ekind (Scop) = E_Generic_Package then
10453 Exp_Status := False;
10454 exit;
10455 end if;
10457 Scop := Scope (Scop);
10458 end loop;
10460 -- Collect previous instantiations in the unit that
10461 -- contains the desired generic.
10463 if Nkind (Parent (True_Parent)) /= N_Compilation_Unit
10464 and then not Body_Optional
10465 then
10466 declare
10467 Decl : Elmt_Id;
10468 Info : Pending_Body_Info;
10469 Par : Node_Id;
10471 begin
10472 Par := Parent (Inst_Node);
10473 while Present (Par) loop
10474 exit when Nkind (Parent (Par)) = N_Compilation_Unit;
10475 Par := Parent (Par);
10476 end loop;
10478 pragma Assert (Present (Par));
10480 if Nkind (Par) = N_Package_Body then
10481 Collect_Previous_Instances (Declarations (Par));
10483 elsif Nkind (Par) = N_Package_Declaration then
10484 Collect_Previous_Instances
10485 (Visible_Declarations (Specification (Par)));
10486 Collect_Previous_Instances
10487 (Private_Declarations (Specification (Par)));
10489 else
10490 -- Enclosing unit is a subprogram body, In this
10491 -- case all instance bodies are processed in order
10492 -- and there is no need to collect them separately.
10494 null;
10495 end if;
10497 Decl := First_Elmt (Previous_Instances);
10498 while Present (Decl) loop
10499 Info :=
10500 (Inst_Node => Node (Decl),
10501 Act_Decl =>
10502 Instance_Spec (Node (Decl)),
10503 Expander_Status => Exp_Status,
10504 Current_Sem_Unit =>
10505 Get_Code_Unit (Sloc (Node (Decl))),
10506 Scope_Suppress => Scope_Suppress,
10507 Local_Suppress_Stack_Top =>
10508 Local_Suppress_Stack_Top);
10510 -- Package instance
10513 Nkind (Node (Decl)) = N_Package_Instantiation
10514 then
10515 Instantiate_Package_Body
10516 (Info, Body_Optional => True);
10518 -- Subprogram instance
10520 else
10521 -- The instance_spec is the wrapper package,
10522 -- and the subprogram declaration is the last
10523 -- declaration in the wrapper.
10525 Info.Act_Decl :=
10526 Last
10527 (Visible_Declarations
10528 (Specification (Info.Act_Decl)));
10530 Instantiate_Subprogram_Body
10531 (Info, Body_Optional => True);
10532 end if;
10534 Next_Elmt (Decl);
10535 end loop;
10536 end;
10537 end if;
10539 Instantiate_Package_Body
10540 (Body_Info =>
10541 ((Inst_Node => Inst_Node,
10542 Act_Decl => True_Parent,
10543 Expander_Status => Exp_Status,
10544 Current_Sem_Unit =>
10545 Get_Code_Unit (Sloc (Inst_Node)),
10546 Scope_Suppress => Scope_Suppress,
10547 Local_Suppress_Stack_Top =>
10548 Local_Suppress_Stack_Top)),
10549 Body_Optional => Body_Optional);
10550 end;
10551 end if;
10553 -- Case where we are not instantiating a nested generic
10555 else
10556 Opt.Style_Check := False;
10557 Expander_Mode_Save_And_Set (True);
10558 Load_Needed_Body (Comp_Unit, OK);
10559 Opt.Style_Check := Save_Style_Check;
10560 Expander_Mode_Restore;
10562 if not OK
10563 and then Unit_Requires_Body (Defining_Entity (Spec))
10564 and then not Body_Optional
10565 then
10566 declare
10567 Bname : constant Unit_Name_Type :=
10568 Get_Body_Name (Get_Unit_Name (Unit (Comp_Unit)));
10570 begin
10571 Error_Msg_Unit_1 := Bname;
10572 Error_Msg_N ("this instantiation requires$!", N);
10573 Error_Msg_File_1 := Get_File_Name (Bname, Subunit => False);
10574 Error_Msg_N ("\but file{ was not found!", N);
10575 raise Unrecoverable_Error;
10576 end;
10577 end if;
10578 end if;
10579 end if;
10581 -- If loading parent of the generic caused an instantiation circularity,
10582 -- we abandon compilation at this point, because otherwise in some cases
10583 -- we get into trouble with infinite recursions after this point.
10585 if Circularity_Detected then
10586 raise Unrecoverable_Error;
10587 end if;
10588 end Load_Parent_Of_Generic;
10590 -----------------------
10591 -- Move_Freeze_Nodes --
10592 -----------------------
10594 procedure Move_Freeze_Nodes
10595 (Out_Of : Entity_Id;
10596 After : Node_Id;
10597 L : List_Id)
10599 Decl : Node_Id;
10600 Next_Decl : Node_Id;
10601 Next_Node : Node_Id := After;
10602 Spec : Node_Id;
10604 function Is_Outer_Type (T : Entity_Id) return Boolean;
10605 -- Check whether entity is declared in a scope external to that
10606 -- of the generic unit.
10608 -------------------
10609 -- Is_Outer_Type --
10610 -------------------
10612 function Is_Outer_Type (T : Entity_Id) return Boolean is
10613 Scop : Entity_Id := Scope (T);
10615 begin
10616 if Scope_Depth (Scop) < Scope_Depth (Out_Of) then
10617 return True;
10619 else
10620 while Scop /= Standard_Standard loop
10621 if Scop = Out_Of then
10622 return False;
10623 else
10624 Scop := Scope (Scop);
10625 end if;
10626 end loop;
10628 return True;
10629 end if;
10630 end Is_Outer_Type;
10632 -- Start of processing for Move_Freeze_Nodes
10634 begin
10635 if No (L) then
10636 return;
10637 end if;
10639 -- First remove the freeze nodes that may appear before all other
10640 -- declarations.
10642 Decl := First (L);
10643 while Present (Decl)
10644 and then Nkind (Decl) = N_Freeze_Entity
10645 and then Is_Outer_Type (Entity (Decl))
10646 loop
10647 Decl := Remove_Head (L);
10648 Insert_After (Next_Node, Decl);
10649 Set_Analyzed (Decl, False);
10650 Next_Node := Decl;
10651 Decl := First (L);
10652 end loop;
10654 -- Next scan the list of declarations and remove each freeze node that
10655 -- appears ahead of the current node.
10657 while Present (Decl) loop
10658 while Present (Next (Decl))
10659 and then Nkind (Next (Decl)) = N_Freeze_Entity
10660 and then Is_Outer_Type (Entity (Next (Decl)))
10661 loop
10662 Next_Decl := Remove_Next (Decl);
10663 Insert_After (Next_Node, Next_Decl);
10664 Set_Analyzed (Next_Decl, False);
10665 Next_Node := Next_Decl;
10666 end loop;
10668 -- If the declaration is a nested package or concurrent type, then
10669 -- recurse. Nested generic packages will have been processed from the
10670 -- inside out.
10672 if Nkind (Decl) = N_Package_Declaration then
10673 Spec := Specification (Decl);
10675 elsif Nkind (Decl) = N_Task_Type_Declaration then
10676 Spec := Task_Definition (Decl);
10678 elsif Nkind (Decl) = N_Protected_Type_Declaration then
10679 Spec := Protected_Definition (Decl);
10681 else
10682 Spec := Empty;
10683 end if;
10685 if Present (Spec) then
10686 Move_Freeze_Nodes (Out_Of, Next_Node,
10687 Visible_Declarations (Spec));
10688 Move_Freeze_Nodes (Out_Of, Next_Node,
10689 Private_Declarations (Spec));
10690 end if;
10692 Next (Decl);
10693 end loop;
10694 end Move_Freeze_Nodes;
10696 ----------------
10697 -- Next_Assoc --
10698 ----------------
10700 function Next_Assoc (E : Assoc_Ptr) return Assoc_Ptr is
10701 begin
10702 return Generic_Renamings.Table (E).Next_In_HTable;
10703 end Next_Assoc;
10705 ------------------------
10706 -- Preanalyze_Actuals --
10707 ------------------------
10709 procedure Preanalyze_Actuals (N : Node_Id) is
10710 Assoc : Node_Id;
10711 Act : Node_Id;
10712 Errs : constant Int := Serious_Errors_Detected;
10714 begin
10715 Assoc := First (Generic_Associations (N));
10716 while Present (Assoc) loop
10717 if Nkind (Assoc) /= N_Others_Choice then
10718 Act := Explicit_Generic_Actual_Parameter (Assoc);
10720 -- Within a nested instantiation, a defaulted actual is an empty
10721 -- association, so nothing to analyze. If the subprogram actual
10722 -- is an attribute, analyze prefix only, because actual is not a
10723 -- complete attribute reference.
10725 -- If actual is an allocator, analyze expression only. The full
10726 -- analysis can generate code, and if instance is a compilation
10727 -- unit we have to wait until the package instance is installed
10728 -- to have a proper place to insert this code.
10730 -- String literals may be operators, but at this point we do not
10731 -- know whether the actual is a formal subprogram or a string.
10733 if No (Act) then
10734 null;
10736 elsif Nkind (Act) = N_Attribute_Reference then
10737 Analyze (Prefix (Act));
10739 elsif Nkind (Act) = N_Explicit_Dereference then
10740 Analyze (Prefix (Act));
10742 elsif Nkind (Act) = N_Allocator then
10743 declare
10744 Expr : constant Node_Id := Expression (Act);
10746 begin
10747 if Nkind (Expr) = N_Subtype_Indication then
10748 Analyze (Subtype_Mark (Expr));
10750 -- Analyze separately each discriminant constraint,
10751 -- when given with a named association.
10753 declare
10754 Constr : Node_Id;
10756 begin
10757 Constr := First (Constraints (Constraint (Expr)));
10758 while Present (Constr) loop
10759 if Nkind (Constr) = N_Discriminant_Association then
10760 Analyze (Expression (Constr));
10761 else
10762 Analyze (Constr);
10763 end if;
10765 Next (Constr);
10766 end loop;
10767 end;
10769 else
10770 Analyze (Expr);
10771 end if;
10772 end;
10774 elsif Nkind (Act) /= N_Operator_Symbol then
10775 Analyze (Act);
10776 end if;
10778 if Errs /= Serious_Errors_Detected then
10780 -- Do a minimal analysis of the generic, to prevent spurious
10781 -- warnings complaining about the generic being unreferenced,
10782 -- before abandoning the instantiation.
10784 Analyze (Name (N));
10786 if Is_Entity_Name (Name (N))
10787 and then Etype (Name (N)) /= Any_Type
10788 then
10789 Generate_Reference (Entity (Name (N)), Name (N));
10790 Set_Is_Instantiated (Entity (Name (N)));
10791 end if;
10793 Abandon_Instantiation (Act);
10794 end if;
10795 end if;
10797 Next (Assoc);
10798 end loop;
10799 end Preanalyze_Actuals;
10801 -------------------
10802 -- Remove_Parent --
10803 -------------------
10805 procedure Remove_Parent (In_Body : Boolean := False) is
10806 S : Entity_Id := Current_Scope;
10807 -- S is the scope containing the instantiation just completed. The
10808 -- scope stack contains the parent instances of the instantiation,
10809 -- followed by the original S.
10811 E : Entity_Id;
10812 P : Entity_Id;
10813 Hidden : Elmt_Id;
10815 begin
10816 -- After child instantiation is complete, remove from scope stack the
10817 -- extra copy of the current scope, and then remove parent instances.
10819 if not In_Body then
10820 Pop_Scope;
10822 while Current_Scope /= S loop
10823 P := Current_Scope;
10824 End_Package_Scope (Current_Scope);
10826 if In_Open_Scopes (P) then
10827 E := First_Entity (P);
10828 while Present (E) loop
10829 Set_Is_Immediately_Visible (E, True);
10830 Next_Entity (E);
10831 end loop;
10833 if Is_Generic_Instance (Current_Scope)
10834 and then P /= Current_Scope
10835 then
10836 -- We are within an instance of some sibling. Retain
10837 -- visibility of parent, for proper subsequent cleanup,
10838 -- and reinstall private declarations as well.
10840 Set_In_Private_Part (P);
10841 Install_Private_Declarations (P);
10842 end if;
10844 -- If the ultimate parent is a top-level unit recorded in
10845 -- Instance_Parent_Unit, then reset its visibility to what
10846 -- it was before instantiation. (It's not clear what the
10847 -- purpose is of testing whether Scope (P) is In_Open_Scopes,
10848 -- but that test was present before the ultimate parent test
10849 -- was added.???)
10851 elsif not In_Open_Scopes (Scope (P))
10852 or else (P = Instance_Parent_Unit
10853 and then not Parent_Unit_Visible)
10854 then
10855 Set_Is_Immediately_Visible (P, False);
10857 -- If the current scope is itself an instantiation of a generic
10858 -- nested within P, and we are in the private part of body of
10859 -- this instantiation, restore the full views of P, that were
10860 -- removed in End_Package_Scope above. This obscure case can
10861 -- occur when a subunit of a generic contains an instance of
10862 -- of a child unit of its generic parent unit.
10864 elsif S = Current_Scope
10865 and then Is_Generic_Instance (S)
10866 then
10867 declare
10868 Par : constant Entity_Id :=
10869 Generic_Parent
10870 (Specification (Unit_Declaration_Node (S)));
10871 begin
10872 if Present (Par)
10873 and then P = Scope (Par)
10874 and then (In_Package_Body (S) or else In_Private_Part (S))
10875 then
10876 Set_In_Private_Part (P);
10877 Install_Private_Declarations (P);
10878 end if;
10879 end;
10880 end if;
10881 end loop;
10883 -- Reset visibility of entities in the enclosing scope
10885 Set_Is_Hidden_Open_Scope (Current_Scope, False);
10887 Hidden := First_Elmt (Hidden_Entities);
10888 while Present (Hidden) loop
10889 Set_Is_Immediately_Visible (Node (Hidden), True);
10890 Next_Elmt (Hidden);
10891 end loop;
10893 else
10894 -- Each body is analyzed separately, and there is no context
10895 -- that needs preserving from one body instance to the next,
10896 -- so remove all parent scopes that have been installed.
10898 while Present (S) loop
10899 End_Package_Scope (S);
10900 Set_Is_Immediately_Visible (S, False);
10901 S := Current_Scope;
10902 exit when S = Standard_Standard;
10903 end loop;
10904 end if;
10905 end Remove_Parent;
10907 -----------------
10908 -- Restore_Env --
10909 -----------------
10911 procedure Restore_Env is
10912 Saved : Instance_Env renames Instance_Envs.Table (Instance_Envs.Last);
10914 begin
10915 if No (Current_Instantiated_Parent.Act_Id) then
10917 -- Restore environment after subprogram inlining
10919 Restore_Private_Views (Empty);
10920 end if;
10922 Current_Instantiated_Parent := Saved.Instantiated_Parent;
10923 Exchanged_Views := Saved.Exchanged_Views;
10924 Hidden_Entities := Saved.Hidden_Entities;
10925 Current_Sem_Unit := Saved.Current_Sem_Unit;
10926 Parent_Unit_Visible := Saved.Parent_Unit_Visible;
10927 Instance_Parent_Unit := Saved.Instance_Parent_Unit;
10929 Restore_Opt_Config_Switches (Saved.Switches);
10931 Instance_Envs.Decrement_Last;
10932 end Restore_Env;
10934 ---------------------------
10935 -- Restore_Private_Views --
10936 ---------------------------
10938 procedure Restore_Private_Views
10939 (Pack_Id : Entity_Id;
10940 Is_Package : Boolean := True)
10942 M : Elmt_Id;
10943 E : Entity_Id;
10944 Typ : Entity_Id;
10945 Dep_Elmt : Elmt_Id;
10946 Dep_Typ : Node_Id;
10948 procedure Restore_Nested_Formal (Formal : Entity_Id);
10949 -- Hide the generic formals of formal packages declared with box
10950 -- which were reachable in the current instantiation.
10952 ---------------------------
10953 -- Restore_Nested_Formal --
10954 ---------------------------
10956 procedure Restore_Nested_Formal (Formal : Entity_Id) is
10957 Ent : Entity_Id;
10959 begin
10960 if Present (Renamed_Object (Formal))
10961 and then Denotes_Formal_Package (Renamed_Object (Formal), True)
10962 then
10963 return;
10965 elsif Present (Associated_Formal_Package (Formal)) then
10966 Ent := First_Entity (Formal);
10967 while Present (Ent) loop
10968 exit when Ekind (Ent) = E_Package
10969 and then Renamed_Entity (Ent) = Renamed_Entity (Formal);
10971 Set_Is_Hidden (Ent);
10972 Set_Is_Potentially_Use_Visible (Ent, False);
10974 -- If package, then recurse
10976 if Ekind (Ent) = E_Package then
10977 Restore_Nested_Formal (Ent);
10978 end if;
10980 Next_Entity (Ent);
10981 end loop;
10982 end if;
10983 end Restore_Nested_Formal;
10985 -- Start of processing for Restore_Private_Views
10987 begin
10988 M := First_Elmt (Exchanged_Views);
10989 while Present (M) loop
10990 Typ := Node (M);
10992 -- Subtypes of types whose views have been exchanged, and that
10993 -- are defined within the instance, were not on the list of
10994 -- Private_Dependents on entry to the instance, so they have to
10995 -- be exchanged explicitly now, in order to remain consistent with
10996 -- the view of the parent type.
10998 if Ekind (Typ) = E_Private_Type
10999 or else Ekind (Typ) = E_Limited_Private_Type
11000 or else Ekind (Typ) = E_Record_Type_With_Private
11001 then
11002 Dep_Elmt := First_Elmt (Private_Dependents (Typ));
11003 while Present (Dep_Elmt) loop
11004 Dep_Typ := Node (Dep_Elmt);
11006 if Scope (Dep_Typ) = Pack_Id
11007 and then Present (Full_View (Dep_Typ))
11008 then
11009 Replace_Elmt (Dep_Elmt, Full_View (Dep_Typ));
11010 Exchange_Declarations (Dep_Typ);
11011 end if;
11013 Next_Elmt (Dep_Elmt);
11014 end loop;
11015 end if;
11017 Exchange_Declarations (Node (M));
11018 Next_Elmt (M);
11019 end loop;
11021 if No (Pack_Id) then
11022 return;
11023 end if;
11025 -- Make the generic formal parameters private, and make the formal
11026 -- types into subtypes of the actuals again.
11028 E := First_Entity (Pack_Id);
11029 while Present (E) loop
11030 Set_Is_Hidden (E, True);
11032 if Is_Type (E)
11033 and then Nkind (Parent (E)) = N_Subtype_Declaration
11034 then
11035 Set_Is_Generic_Actual_Type (E, False);
11037 -- An unusual case of aliasing: the actual may also be directly
11038 -- visible in the generic, and be private there, while it is fully
11039 -- visible in the context of the instance. The internal subtype
11040 -- is private in the instance, but has full visibility like its
11041 -- parent in the enclosing scope. This enforces the invariant that
11042 -- the privacy status of all private dependents of a type coincide
11043 -- with that of the parent type. This can only happen when a
11044 -- generic child unit is instantiated within sibling.
11046 if Is_Private_Type (E)
11047 and then not Is_Private_Type (Etype (E))
11048 then
11049 Exchange_Declarations (E);
11050 end if;
11052 elsif Ekind (E) = E_Package then
11054 -- The end of the renaming list is the renaming of the generic
11055 -- package itself. If the instance is a subprogram, all entities
11056 -- in the corresponding package are renamings. If this entity is
11057 -- a formal package, make its own formals private as well. The
11058 -- actual in this case is itself the renaming of an instantiation.
11059 -- If the entity is not a package renaming, it is the entity
11060 -- created to validate formal package actuals: ignore.
11062 -- If the actual is itself a formal package for the enclosing
11063 -- generic, or the actual for such a formal package, it remains
11064 -- visible on exit from the instance, and therefore nothing needs
11065 -- to be done either, except to keep it accessible.
11067 if Is_Package
11068 and then Renamed_Object (E) = Pack_Id
11069 then
11070 exit;
11072 elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
11073 null;
11075 elsif Denotes_Formal_Package (Renamed_Object (E), True) then
11076 Set_Is_Hidden (E, False);
11078 else
11079 declare
11080 Act_P : constant Entity_Id := Renamed_Object (E);
11081 Id : Entity_Id;
11083 begin
11084 Id := First_Entity (Act_P);
11085 while Present (Id)
11086 and then Id /= First_Private_Entity (Act_P)
11087 loop
11088 exit when Ekind (Id) = E_Package
11089 and then Renamed_Object (Id) = Act_P;
11091 Set_Is_Hidden (Id, True);
11092 Set_Is_Potentially_Use_Visible (Id, In_Use (Act_P));
11094 if Ekind (Id) = E_Package then
11095 Restore_Nested_Formal (Id);
11096 end if;
11098 Next_Entity (Id);
11099 end loop;
11100 end;
11101 end if;
11102 end if;
11104 Next_Entity (E);
11105 end loop;
11106 end Restore_Private_Views;
11108 --------------
11109 -- Save_Env --
11110 --------------
11112 procedure Save_Env
11113 (Gen_Unit : Entity_Id;
11114 Act_Unit : Entity_Id)
11116 begin
11117 Init_Env;
11118 Set_Instance_Env (Gen_Unit, Act_Unit);
11119 end Save_Env;
11121 ----------------------------
11122 -- Save_Global_References --
11123 ----------------------------
11125 procedure Save_Global_References (N : Node_Id) is
11126 Gen_Scope : Entity_Id;
11127 E : Entity_Id;
11128 N2 : Node_Id;
11130 function Is_Global (E : Entity_Id) return Boolean;
11131 -- Check whether entity is defined outside of generic unit. Examine the
11132 -- scope of an entity, and the scope of the scope, etc, until we find
11133 -- either Standard, in which case the entity is global, or the generic
11134 -- unit itself, which indicates that the entity is local. If the entity
11135 -- is the generic unit itself, as in the case of a recursive call, or
11136 -- the enclosing generic unit, if different from the current scope, then
11137 -- it is local as well, because it will be replaced at the point of
11138 -- instantiation. On the other hand, if it is a reference to a child
11139 -- unit of a common ancestor, which appears in an instantiation, it is
11140 -- global because it is used to denote a specific compilation unit at
11141 -- the time the instantiations will be analyzed.
11143 procedure Reset_Entity (N : Node_Id);
11144 -- Save semantic information on global entity, so that it is not
11145 -- resolved again at instantiation time.
11147 procedure Save_Entity_Descendants (N : Node_Id);
11148 -- Apply Save_Global_References to the two syntactic descendants of
11149 -- non-terminal nodes that carry an Associated_Node and are processed
11150 -- through Reset_Entity. Once the global entity (if any) has been
11151 -- captured together with its type, only two syntactic descendants need
11152 -- to be traversed to complete the processing of the tree rooted at N.
11153 -- This applies to Selected_Components, Expanded_Names, and to Operator
11154 -- nodes. N can also be a character literal, identifier, or operator
11155 -- symbol node, but the call has no effect in these cases.
11157 procedure Save_Global_Defaults (N1, N2 : Node_Id);
11158 -- Default actuals in nested instances must be handled specially
11159 -- because there is no link to them from the original tree. When an
11160 -- actual subprogram is given by a default, we add an explicit generic
11161 -- association for it in the instantiation node. When we save the
11162 -- global references on the name of the instance, we recover the list
11163 -- of generic associations, and add an explicit one to the original
11164 -- generic tree, through which a global actual can be preserved.
11165 -- Similarly, if a child unit is instantiated within a sibling, in the
11166 -- context of the parent, we must preserve the identifier of the parent
11167 -- so that it can be properly resolved in a subsequent instantiation.
11169 procedure Save_Global_Descendant (D : Union_Id);
11170 -- Apply Save_Global_References recursively to the descendents of the
11171 -- current node.
11173 procedure Save_References (N : Node_Id);
11174 -- This is the recursive procedure that does the work, once the
11175 -- enclosing generic scope has been established.
11177 ---------------
11178 -- Is_Global --
11179 ---------------
11181 function Is_Global (E : Entity_Id) return Boolean is
11182 Se : Entity_Id;
11184 function Is_Instance_Node (Decl : Node_Id) return Boolean;
11185 -- Determine whether the parent node of a reference to a child unit
11186 -- denotes an instantiation or a formal package, in which case the
11187 -- reference to the child unit is global, even if it appears within
11188 -- the current scope (e.g. when the instance appears within the body
11189 -- of an ancestor).
11191 ----------------------
11192 -- Is_Instance_Node --
11193 ----------------------
11195 function Is_Instance_Node (Decl : Node_Id) return Boolean is
11196 begin
11197 return (Nkind (Decl) in N_Generic_Instantiation
11198 or else
11199 Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration);
11200 end Is_Instance_Node;
11202 -- Start of processing for Is_Global
11204 begin
11205 if E = Gen_Scope then
11206 return False;
11208 elsif E = Standard_Standard then
11209 return True;
11211 elsif Is_Child_Unit (E)
11212 and then (Is_Instance_Node (Parent (N2))
11213 or else (Nkind (Parent (N2)) = N_Expanded_Name
11214 and then N2 = Selector_Name (Parent (N2))
11215 and then
11216 Is_Instance_Node (Parent (Parent (N2)))))
11217 then
11218 return True;
11220 else
11221 Se := Scope (E);
11222 while Se /= Gen_Scope loop
11223 if Se = Standard_Standard then
11224 return True;
11225 else
11226 Se := Scope (Se);
11227 end if;
11228 end loop;
11230 return False;
11231 end if;
11232 end Is_Global;
11234 ------------------
11235 -- Reset_Entity --
11236 ------------------
11238 procedure Reset_Entity (N : Node_Id) is
11240 procedure Set_Global_Type (N : Node_Id; N2 : Node_Id);
11241 -- If the type of N2 is global to the generic unit. Save
11242 -- the type in the generic node.
11244 function Top_Ancestor (E : Entity_Id) return Entity_Id;
11245 -- Find the ultimate ancestor of the current unit. If it is
11246 -- not a generic unit, then the name of the current unit
11247 -- in the prefix of an expanded name must be replaced with
11248 -- its generic homonym to ensure that it will be properly
11249 -- resolved in an instance.
11251 ---------------------
11252 -- Set_Global_Type --
11253 ---------------------
11255 procedure Set_Global_Type (N : Node_Id; N2 : Node_Id) is
11256 Typ : constant Entity_Id := Etype (N2);
11258 begin
11259 Set_Etype (N, Typ);
11261 if Entity (N) /= N2
11262 and then Has_Private_View (Entity (N))
11263 then
11264 -- If the entity of N is not the associated node, this is
11265 -- a nested generic and it has an associated node as well,
11266 -- whose type is already the full view (see below). Indicate
11267 -- that the original node has a private view.
11269 Set_Has_Private_View (N);
11270 end if;
11272 -- If not a private type, nothing else to do
11274 if not Is_Private_Type (Typ) then
11275 if Is_Array_Type (Typ)
11276 and then Is_Private_Type (Component_Type (Typ))
11277 then
11278 Set_Has_Private_View (N);
11279 end if;
11281 -- If it is a derivation of a private type in a context where
11282 -- no full view is needed, nothing to do either.
11284 elsif No (Full_View (Typ)) and then Typ /= Etype (Typ) then
11285 null;
11287 -- Otherwise mark the type for flipping and use the full_view
11288 -- when available.
11290 else
11291 Set_Has_Private_View (N);
11293 if Present (Full_View (Typ)) then
11294 Set_Etype (N2, Full_View (Typ));
11295 end if;
11296 end if;
11297 end Set_Global_Type;
11299 ------------------
11300 -- Top_Ancestor --
11301 ------------------
11303 function Top_Ancestor (E : Entity_Id) return Entity_Id is
11304 Par : Entity_Id;
11306 begin
11307 Par := E;
11308 while Is_Child_Unit (Par) loop
11309 Par := Scope (Par);
11310 end loop;
11312 return Par;
11313 end Top_Ancestor;
11315 -- Start of processing for Reset_Entity
11317 begin
11318 N2 := Get_Associated_Node (N);
11319 E := Entity (N2);
11321 if Present (E) then
11322 if Is_Global (E) then
11323 Set_Global_Type (N, N2);
11325 elsif Nkind (N) = N_Op_Concat
11326 and then Is_Generic_Type (Etype (N2))
11327 and then
11328 (Base_Type (Etype (Right_Opnd (N2))) = Etype (N2)
11329 or else Base_Type (Etype (Left_Opnd (N2))) = Etype (N2))
11330 and then Is_Intrinsic_Subprogram (E)
11331 then
11332 null;
11334 else
11335 -- Entity is local. Mark generic node as unresolved.
11336 -- Note that now it does not have an entity.
11338 Set_Associated_Node (N, Empty);
11339 Set_Etype (N, Empty);
11340 end if;
11342 if Nkind (Parent (N)) in N_Generic_Instantiation
11343 and then N = Name (Parent (N))
11344 then
11345 Save_Global_Defaults (Parent (N), Parent (N2));
11346 end if;
11348 elsif Nkind (Parent (N)) = N_Selected_Component
11349 and then Nkind (Parent (N2)) = N_Expanded_Name
11350 then
11351 if Is_Global (Entity (Parent (N2))) then
11352 Change_Selected_Component_To_Expanded_Name (Parent (N));
11353 Set_Associated_Node (Parent (N), Parent (N2));
11354 Set_Global_Type (Parent (N), Parent (N2));
11355 Save_Entity_Descendants (N);
11357 -- If this is a reference to the current generic entity, replace
11358 -- by the name of the generic homonym of the current package. This
11359 -- is because in an instantiation Par.P.Q will not resolve to the
11360 -- name of the instance, whose enclosing scope is not necessarily
11361 -- Par. We use the generic homonym rather that the name of the
11362 -- generic itself, because it may be hidden by a local
11363 -- declaration.
11365 elsif In_Open_Scopes (Entity (Parent (N2)))
11366 and then not
11367 Is_Generic_Unit (Top_Ancestor (Entity (Prefix (Parent (N2)))))
11368 then
11369 if Ekind (Entity (Parent (N2))) = E_Generic_Package then
11370 Rewrite (Parent (N),
11371 Make_Identifier (Sloc (N),
11372 Chars =>
11373 Chars (Generic_Homonym (Entity (Parent (N2))))));
11374 else
11375 Rewrite (Parent (N),
11376 Make_Identifier (Sloc (N),
11377 Chars => Chars (Selector_Name (Parent (N2)))));
11378 end if;
11379 end if;
11381 if Nkind (Parent (Parent (N))) in N_Generic_Instantiation
11382 and then Parent (N) = Name (Parent (Parent (N)))
11383 then
11384 Save_Global_Defaults
11385 (Parent (Parent (N)), Parent (Parent ((N2))));
11386 end if;
11388 -- A selected component may denote a static constant that has been
11389 -- folded. If the static constant is global to the generic, capture
11390 -- its value. Otherwise the folding will happen in any instantiation,
11392 elsif Nkind (Parent (N)) = N_Selected_Component
11393 and then Nkind_In (Parent (N2), N_Integer_Literal, N_Real_Literal)
11394 then
11395 if Present (Entity (Original_Node (Parent (N2))))
11396 and then Is_Global (Entity (Original_Node (Parent (N2))))
11397 then
11398 Rewrite (Parent (N), New_Copy (Parent (N2)));
11399 Set_Analyzed (Parent (N), False);
11401 else
11402 null;
11403 end if;
11405 -- A selected component may be transformed into a parameterless
11406 -- function call. If the called entity is global, rewrite the node
11407 -- appropriately, i.e. as an extended name for the global entity.
11409 elsif Nkind (Parent (N)) = N_Selected_Component
11410 and then Nkind (Parent (N2)) = N_Function_Call
11411 and then N = Selector_Name (Parent (N))
11412 then
11413 if No (Parameter_Associations (Parent (N2))) then
11414 if Is_Global (Entity (Name (Parent (N2)))) then
11415 Change_Selected_Component_To_Expanded_Name (Parent (N));
11416 Set_Associated_Node (Parent (N), Name (Parent (N2)));
11417 Set_Global_Type (Parent (N), Name (Parent (N2)));
11418 Save_Entity_Descendants (N);
11420 else
11421 Set_Associated_Node (N, Empty);
11422 Set_Etype (N, Empty);
11423 end if;
11425 -- In Ada 2005, X.F may be a call to a primitive operation,
11426 -- rewritten as F (X). This rewriting will be done again in an
11427 -- instance, so keep the original node. Global entities will be
11428 -- captured as for other constructs.
11430 else
11431 null;
11432 end if;
11434 -- Entity is local. Reset in generic unit, so that node is resolved
11435 -- anew at the point of instantiation.
11437 else
11438 Set_Associated_Node (N, Empty);
11439 Set_Etype (N, Empty);
11440 end if;
11441 end Reset_Entity;
11443 -----------------------------
11444 -- Save_Entity_Descendants --
11445 -----------------------------
11447 procedure Save_Entity_Descendants (N : Node_Id) is
11448 begin
11449 case Nkind (N) is
11450 when N_Binary_Op =>
11451 Save_Global_Descendant (Union_Id (Left_Opnd (N)));
11452 Save_Global_Descendant (Union_Id (Right_Opnd (N)));
11454 when N_Unary_Op =>
11455 Save_Global_Descendant (Union_Id (Right_Opnd (N)));
11457 when N_Expanded_Name | N_Selected_Component =>
11458 Save_Global_Descendant (Union_Id (Prefix (N)));
11459 Save_Global_Descendant (Union_Id (Selector_Name (N)));
11461 when N_Identifier | N_Character_Literal | N_Operator_Symbol =>
11462 null;
11464 when others =>
11465 raise Program_Error;
11466 end case;
11467 end Save_Entity_Descendants;
11469 --------------------------
11470 -- Save_Global_Defaults --
11471 --------------------------
11473 procedure Save_Global_Defaults (N1, N2 : Node_Id) is
11474 Loc : constant Source_Ptr := Sloc (N1);
11475 Assoc2 : constant List_Id := Generic_Associations (N2);
11476 Gen_Id : constant Entity_Id := Get_Generic_Entity (N2);
11477 Assoc1 : List_Id;
11478 Act1 : Node_Id;
11479 Act2 : Node_Id;
11480 Def : Node_Id;
11481 Ndec : Node_Id;
11482 Subp : Entity_Id;
11483 Actual : Entity_Id;
11485 begin
11486 Assoc1 := Generic_Associations (N1);
11488 if Present (Assoc1) then
11489 Act1 := First (Assoc1);
11490 else
11491 Act1 := Empty;
11492 Set_Generic_Associations (N1, New_List);
11493 Assoc1 := Generic_Associations (N1);
11494 end if;
11496 if Present (Assoc2) then
11497 Act2 := First (Assoc2);
11498 else
11499 return;
11500 end if;
11502 while Present (Act1) and then Present (Act2) loop
11503 Next (Act1);
11504 Next (Act2);
11505 end loop;
11507 -- Find the associations added for default subprograms
11509 if Present (Act2) then
11510 while Nkind (Act2) /= N_Generic_Association
11511 or else No (Entity (Selector_Name (Act2)))
11512 or else not Is_Overloadable (Entity (Selector_Name (Act2)))
11513 loop
11514 Next (Act2);
11515 end loop;
11517 -- Add a similar association if the default is global. The
11518 -- renaming declaration for the actual has been analyzed, and
11519 -- its alias is the program it renames. Link the actual in the
11520 -- original generic tree with the node in the analyzed tree.
11522 while Present (Act2) loop
11523 Subp := Entity (Selector_Name (Act2));
11524 Def := Explicit_Generic_Actual_Parameter (Act2);
11526 -- Following test is defence against rubbish errors
11528 if No (Alias (Subp)) then
11529 return;
11530 end if;
11532 -- Retrieve the resolved actual from the renaming declaration
11533 -- created for the instantiated formal.
11535 Actual := Entity (Name (Parent (Parent (Subp))));
11536 Set_Entity (Def, Actual);
11537 Set_Etype (Def, Etype (Actual));
11539 if Is_Global (Actual) then
11540 Ndec :=
11541 Make_Generic_Association (Loc,
11542 Selector_Name => New_Occurrence_Of (Subp, Loc),
11543 Explicit_Generic_Actual_Parameter =>
11544 New_Occurrence_Of (Actual, Loc));
11546 Set_Associated_Node
11547 (Explicit_Generic_Actual_Parameter (Ndec), Def);
11549 Append (Ndec, Assoc1);
11551 -- If there are other defaults, add a dummy association in case
11552 -- there are other defaulted formals with the same name.
11554 elsif Present (Next (Act2)) then
11555 Ndec :=
11556 Make_Generic_Association (Loc,
11557 Selector_Name => New_Occurrence_Of (Subp, Loc),
11558 Explicit_Generic_Actual_Parameter => Empty);
11560 Append (Ndec, Assoc1);
11561 end if;
11563 Next (Act2);
11564 end loop;
11565 end if;
11567 if Nkind (Name (N1)) = N_Identifier
11568 and then Is_Child_Unit (Gen_Id)
11569 and then Is_Global (Gen_Id)
11570 and then Is_Generic_Unit (Scope (Gen_Id))
11571 and then In_Open_Scopes (Scope (Gen_Id))
11572 then
11573 -- This is an instantiation of a child unit within a sibling,
11574 -- so that the generic parent is in scope. An eventual instance
11575 -- must occur within the scope of an instance of the parent.
11576 -- Make name in instance into an expanded name, to preserve the
11577 -- identifier of the parent, so it can be resolved subsequently.
11579 Rewrite (Name (N2),
11580 Make_Expanded_Name (Loc,
11581 Chars => Chars (Gen_Id),
11582 Prefix => New_Occurrence_Of (Scope (Gen_Id), Loc),
11583 Selector_Name => New_Occurrence_Of (Gen_Id, Loc)));
11584 Set_Entity (Name (N2), Gen_Id);
11586 Rewrite (Name (N1),
11587 Make_Expanded_Name (Loc,
11588 Chars => Chars (Gen_Id),
11589 Prefix => New_Occurrence_Of (Scope (Gen_Id), Loc),
11590 Selector_Name => New_Occurrence_Of (Gen_Id, Loc)));
11592 Set_Associated_Node (Name (N1), Name (N2));
11593 Set_Associated_Node (Prefix (Name (N1)), Empty);
11594 Set_Associated_Node
11595 (Selector_Name (Name (N1)), Selector_Name (Name (N2)));
11596 Set_Etype (Name (N1), Etype (Gen_Id));
11597 end if;
11599 end Save_Global_Defaults;
11601 ----------------------------
11602 -- Save_Global_Descendant --
11603 ----------------------------
11605 procedure Save_Global_Descendant (D : Union_Id) is
11606 N1 : Node_Id;
11608 begin
11609 if D in Node_Range then
11610 if D = Union_Id (Empty) then
11611 null;
11613 elsif Nkind (Node_Id (D)) /= N_Compilation_Unit then
11614 Save_References (Node_Id (D));
11615 end if;
11617 elsif D in List_Range then
11618 if D = Union_Id (No_List)
11619 or else Is_Empty_List (List_Id (D))
11620 then
11621 null;
11623 else
11624 N1 := First (List_Id (D));
11625 while Present (N1) loop
11626 Save_References (N1);
11627 Next (N1);
11628 end loop;
11629 end if;
11631 -- Element list or other non-node field, nothing to do
11633 else
11634 null;
11635 end if;
11636 end Save_Global_Descendant;
11638 ---------------------
11639 -- Save_References --
11640 ---------------------
11642 -- This is the recursive procedure that does the work, once the
11643 -- enclosing generic scope has been established. We have to treat
11644 -- specially a number of node rewritings that are required by semantic
11645 -- processing and which change the kind of nodes in the generic copy:
11646 -- typically constant-folding, replacing an operator node by a string
11647 -- literal, or a selected component by an expanded name. In each of
11648 -- those cases, the transformation is propagated to the generic unit.
11650 procedure Save_References (N : Node_Id) is
11651 begin
11652 if N = Empty then
11653 null;
11655 elsif Nkind_In (N, N_Character_Literal, N_Operator_Symbol) then
11656 if Nkind (N) = Nkind (Get_Associated_Node (N)) then
11657 Reset_Entity (N);
11659 elsif Nkind (N) = N_Operator_Symbol
11660 and then Nkind (Get_Associated_Node (N)) = N_String_Literal
11661 then
11662 Change_Operator_Symbol_To_String_Literal (N);
11663 end if;
11665 elsif Nkind (N) in N_Op then
11666 if Nkind (N) = Nkind (Get_Associated_Node (N)) then
11667 if Nkind (N) = N_Op_Concat then
11668 Set_Is_Component_Left_Opnd (N,
11669 Is_Component_Left_Opnd (Get_Associated_Node (N)));
11671 Set_Is_Component_Right_Opnd (N,
11672 Is_Component_Right_Opnd (Get_Associated_Node (N)));
11673 end if;
11675 Reset_Entity (N);
11677 else
11678 -- Node may be transformed into call to a user-defined operator
11680 N2 := Get_Associated_Node (N);
11682 if Nkind (N2) = N_Function_Call then
11683 E := Entity (Name (N2));
11685 if Present (E)
11686 and then Is_Global (E)
11687 then
11688 Set_Etype (N, Etype (N2));
11689 else
11690 Set_Associated_Node (N, Empty);
11691 Set_Etype (N, Empty);
11692 end if;
11694 elsif Nkind_In (N2, N_Integer_Literal,
11695 N_Real_Literal,
11696 N_String_Literal)
11697 then
11698 if Present (Original_Node (N2))
11699 and then Nkind (Original_Node (N2)) = Nkind (N)
11700 then
11702 -- Operation was constant-folded. Whenever possible,
11703 -- recover semantic information from unfolded node,
11704 -- for ASIS use.
11706 Set_Associated_Node (N, Original_Node (N2));
11708 if Nkind (N) = N_Op_Concat then
11709 Set_Is_Component_Left_Opnd (N,
11710 Is_Component_Left_Opnd (Get_Associated_Node (N)));
11711 Set_Is_Component_Right_Opnd (N,
11712 Is_Component_Right_Opnd (Get_Associated_Node (N)));
11713 end if;
11715 Reset_Entity (N);
11717 else
11718 -- If original node is already modified, propagate
11719 -- constant-folding to template.
11721 Rewrite (N, New_Copy (N2));
11722 Set_Analyzed (N, False);
11723 end if;
11725 elsif Nkind (N2) = N_Identifier
11726 and then Ekind (Entity (N2)) = E_Enumeration_Literal
11727 then
11728 -- Same if call was folded into a literal, but in this case
11729 -- retain the entity to avoid spurious ambiguities if id is
11730 -- overloaded at the point of instantiation or inlining.
11732 Rewrite (N, New_Copy (N2));
11733 Set_Analyzed (N, False);
11734 end if;
11735 end if;
11737 -- Complete operands check if node has not been constant-folded
11739 if Nkind (N) in N_Op then
11740 Save_Entity_Descendants (N);
11741 end if;
11743 elsif Nkind (N) = N_Identifier then
11744 if Nkind (N) = Nkind (Get_Associated_Node (N)) then
11746 -- If this is a discriminant reference, always save it. It is
11747 -- used in the instance to find the corresponding discriminant
11748 -- positionally rather than by name.
11750 Set_Original_Discriminant
11751 (N, Original_Discriminant (Get_Associated_Node (N)));
11752 Reset_Entity (N);
11754 else
11755 N2 := Get_Associated_Node (N);
11757 if Nkind (N2) = N_Function_Call then
11758 E := Entity (Name (N2));
11760 -- Name resolves to a call to parameterless function. If
11761 -- original entity is global, mark node as resolved.
11763 if Present (E)
11764 and then Is_Global (E)
11765 then
11766 Set_Etype (N, Etype (N2));
11767 else
11768 Set_Associated_Node (N, Empty);
11769 Set_Etype (N, Empty);
11770 end if;
11772 elsif Nkind_In (N2, N_Integer_Literal, N_Real_Literal)
11773 and then Is_Entity_Name (Original_Node (N2))
11774 then
11775 -- Name resolves to named number that is constant-folded,
11776 -- We must preserve the original name for ASIS use, and
11777 -- undo the constant-folding, which will be repeated in
11778 -- each instance.
11780 Set_Associated_Node (N, Original_Node (N2));
11781 Reset_Entity (N);
11783 elsif Nkind (N2) = N_String_Literal then
11785 -- Name resolves to string literal. Perform the same
11786 -- replacement in generic.
11788 Rewrite (N, New_Copy (N2));
11790 elsif Nkind (N2) = N_Explicit_Dereference then
11792 -- An identifier is rewritten as a dereference if it is
11793 -- the prefix in a selected component, and it denotes an
11794 -- access to a composite type, or a parameterless function
11795 -- call that returns an access type.
11797 -- Check whether corresponding entity in prefix is global
11799 if Is_Entity_Name (Prefix (N2))
11800 and then Present (Entity (Prefix (N2)))
11801 and then Is_Global (Entity (Prefix (N2)))
11802 then
11803 Rewrite (N,
11804 Make_Explicit_Dereference (Sloc (N),
11805 Prefix => Make_Identifier (Sloc (N),
11806 Chars => Chars (N))));
11807 Set_Associated_Node (Prefix (N), Prefix (N2));
11809 elsif Nkind (Prefix (N2)) = N_Function_Call
11810 and then Is_Global (Entity (Name (Prefix (N2))))
11811 then
11812 Rewrite (N,
11813 Make_Explicit_Dereference (Sloc (N),
11814 Prefix => Make_Function_Call (Sloc (N),
11815 Name =>
11816 Make_Identifier (Sloc (N),
11817 Chars => Chars (N)))));
11819 Set_Associated_Node
11820 (Name (Prefix (N)), Name (Prefix (N2)));
11822 else
11823 Set_Associated_Node (N, Empty);
11824 Set_Etype (N, Empty);
11825 end if;
11827 -- The subtype mark of a nominally unconstrained object is
11828 -- rewritten as a subtype indication using the bounds of the
11829 -- expression. Recover the original subtype mark.
11831 elsif Nkind (N2) = N_Subtype_Indication
11832 and then Is_Entity_Name (Original_Node (N2))
11833 then
11834 Set_Associated_Node (N, Original_Node (N2));
11835 Reset_Entity (N);
11837 else
11838 null;
11839 end if;
11840 end if;
11842 elsif Nkind (N) in N_Entity then
11843 null;
11845 else
11846 declare
11847 Loc : constant Source_Ptr := Sloc (N);
11848 Qual : Node_Id := Empty;
11849 Typ : Entity_Id := Empty;
11850 Nam : Node_Id;
11852 use Atree.Unchecked_Access;
11853 -- This code section is part of implementing an untyped tree
11854 -- traversal, so it needs direct access to node fields.
11856 begin
11857 if Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
11858 N2 := Get_Associated_Node (N);
11860 if No (N2) then
11861 Typ := Empty;
11862 else
11863 Typ := Etype (N2);
11865 -- In an instance within a generic, use the name of the
11866 -- actual and not the original generic parameter. If the
11867 -- actual is global in the current generic it must be
11868 -- preserved for its instantiation.
11870 if Nkind (Parent (Typ)) = N_Subtype_Declaration
11871 and then
11872 Present (Generic_Parent_Type (Parent (Typ)))
11873 then
11874 Typ := Base_Type (Typ);
11875 Set_Etype (N2, Typ);
11876 end if;
11877 end if;
11879 if No (N2)
11880 or else No (Typ)
11881 or else not Is_Global (Typ)
11882 then
11883 Set_Associated_Node (N, Empty);
11885 -- If the aggregate is an actual in a call, it has been
11886 -- resolved in the current context, to some local type.
11887 -- The enclosing call may have been disambiguated by the
11888 -- aggregate, and this disambiguation might fail at
11889 -- instantiation time because the type to which the
11890 -- aggregate did resolve is not preserved. In order to
11891 -- preserve some of this information, we wrap the
11892 -- aggregate in a qualified expression, using the id of
11893 -- its type. For further disambiguation we qualify the
11894 -- type name with its scope (if visible) because both
11895 -- id's will have corresponding entities in an instance.
11896 -- This resolves most of the problems with missing type
11897 -- information on aggregates in instances.
11899 if Nkind (N2) = Nkind (N)
11900 and then
11901 Nkind_In (Parent (N2), N_Procedure_Call_Statement,
11902 N_Function_Call)
11903 and then Comes_From_Source (Typ)
11904 then
11905 if Is_Immediately_Visible (Scope (Typ)) then
11906 Nam := Make_Selected_Component (Loc,
11907 Prefix =>
11908 Make_Identifier (Loc, Chars (Scope (Typ))),
11909 Selector_Name =>
11910 Make_Identifier (Loc, Chars (Typ)));
11911 else
11912 Nam := Make_Identifier (Loc, Chars (Typ));
11913 end if;
11915 Qual :=
11916 Make_Qualified_Expression (Loc,
11917 Subtype_Mark => Nam,
11918 Expression => Relocate_Node (N));
11919 end if;
11920 end if;
11922 Save_Global_Descendant (Field1 (N));
11923 Save_Global_Descendant (Field2 (N));
11924 Save_Global_Descendant (Field3 (N));
11925 Save_Global_Descendant (Field5 (N));
11927 if Present (Qual) then
11928 Rewrite (N, Qual);
11929 end if;
11931 -- All other cases than aggregates
11933 else
11934 Save_Global_Descendant (Field1 (N));
11935 Save_Global_Descendant (Field2 (N));
11936 Save_Global_Descendant (Field3 (N));
11937 Save_Global_Descendant (Field4 (N));
11938 Save_Global_Descendant (Field5 (N));
11939 end if;
11940 end;
11941 end if;
11942 end Save_References;
11944 -- Start of processing for Save_Global_References
11946 begin
11947 Gen_Scope := Current_Scope;
11949 -- If the generic unit is a child unit, references to entities in the
11950 -- parent are treated as local, because they will be resolved anew in
11951 -- the context of the instance of the parent.
11953 while Is_Child_Unit (Gen_Scope)
11954 and then Ekind (Scope (Gen_Scope)) = E_Generic_Package
11955 loop
11956 Gen_Scope := Scope (Gen_Scope);
11957 end loop;
11959 Save_References (N);
11960 end Save_Global_References;
11962 --------------------------------------
11963 -- Set_Copied_Sloc_For_Inlined_Body --
11964 --------------------------------------
11966 procedure Set_Copied_Sloc_For_Inlined_Body (N : Node_Id; E : Entity_Id) is
11967 begin
11968 Create_Instantiation_Source (N, E, True, S_Adjustment);
11969 end Set_Copied_Sloc_For_Inlined_Body;
11971 ---------------------
11972 -- Set_Instance_Of --
11973 ---------------------
11975 procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id) is
11976 begin
11977 Generic_Renamings.Table (Generic_Renamings.Last) := (A, B, Assoc_Null);
11978 Generic_Renamings_HTable.Set (Generic_Renamings.Last);
11979 Generic_Renamings.Increment_Last;
11980 end Set_Instance_Of;
11982 --------------------
11983 -- Set_Next_Assoc --
11984 --------------------
11986 procedure Set_Next_Assoc (E : Assoc_Ptr; Next : Assoc_Ptr) is
11987 begin
11988 Generic_Renamings.Table (E).Next_In_HTable := Next;
11989 end Set_Next_Assoc;
11991 -------------------
11992 -- Start_Generic --
11993 -------------------
11995 procedure Start_Generic is
11996 begin
11997 -- ??? More things could be factored out in this routine.
11998 -- Should probably be done at a later stage.
12000 Generic_Flags.Append (Inside_A_Generic);
12001 Inside_A_Generic := True;
12003 Expander_Mode_Save_And_Set (False);
12004 end Start_Generic;
12006 ----------------------
12007 -- Set_Instance_Env --
12008 ----------------------
12010 procedure Set_Instance_Env
12011 (Gen_Unit : Entity_Id;
12012 Act_Unit : Entity_Id)
12014 begin
12015 -- Regardless of the current mode, predefined units are analyzed in
12016 -- the most current Ada mode, and earlier version Ada checks do not
12017 -- apply to predefined units. Nothing needs to be done for non-internal
12018 -- units. These are always analyzed in the current mode.
12020 if Is_Internal_File_Name
12021 (Fname => Unit_File_Name (Get_Source_Unit (Gen_Unit)),
12022 Renamings_Included => True)
12023 then
12024 Set_Opt_Config_Switches (True, Current_Sem_Unit = Main_Unit);
12025 end if;
12027 Current_Instantiated_Parent := (Gen_Unit, Act_Unit, Assoc_Null);
12028 end Set_Instance_Env;
12030 -----------------
12031 -- Switch_View --
12032 -----------------
12034 procedure Switch_View (T : Entity_Id) is
12035 BT : constant Entity_Id := Base_Type (T);
12036 Priv_Elmt : Elmt_Id := No_Elmt;
12037 Priv_Sub : Entity_Id;
12039 begin
12040 -- T may be private but its base type may have been exchanged through
12041 -- some other occurrence, in which case there is nothing to switch
12042 -- besides T itself. Note that a private dependent subtype of a private
12043 -- type might not have been switched even if the base type has been,
12044 -- because of the last branch of Check_Private_View (see comment there).
12046 if not Is_Private_Type (BT) then
12047 Prepend_Elmt (Full_View (T), Exchanged_Views);
12048 Exchange_Declarations (T);
12049 return;
12050 end if;
12052 Priv_Elmt := First_Elmt (Private_Dependents (BT));
12054 if Present (Full_View (BT)) then
12055 Prepend_Elmt (Full_View (BT), Exchanged_Views);
12056 Exchange_Declarations (BT);
12057 end if;
12059 while Present (Priv_Elmt) loop
12060 Priv_Sub := (Node (Priv_Elmt));
12062 -- We avoid flipping the subtype if the Etype of its full view is
12063 -- private because this would result in a malformed subtype. This
12064 -- occurs when the Etype of the subtype full view is the full view of
12065 -- the base type (and since the base types were just switched, the
12066 -- subtype is pointing to the wrong view). This is currently the case
12067 -- for tagged record types, access types (maybe more?) and needs to
12068 -- be resolved. ???
12070 if Present (Full_View (Priv_Sub))
12071 and then not Is_Private_Type (Etype (Full_View (Priv_Sub)))
12072 then
12073 Prepend_Elmt (Full_View (Priv_Sub), Exchanged_Views);
12074 Exchange_Declarations (Priv_Sub);
12075 end if;
12077 Next_Elmt (Priv_Elmt);
12078 end loop;
12079 end Switch_View;
12081 -----------------------------
12082 -- Valid_Default_Attribute --
12083 -----------------------------
12085 procedure Valid_Default_Attribute (Nam : Entity_Id; Def : Node_Id) is
12086 Attr_Id : constant Attribute_Id :=
12087 Get_Attribute_Id (Attribute_Name (Def));
12088 T : constant Entity_Id := Entity (Prefix (Def));
12089 Is_Fun : constant Boolean := (Ekind (Nam) = E_Function);
12090 F : Entity_Id;
12091 Num_F : Int;
12092 OK : Boolean;
12094 begin
12095 if No (T)
12096 or else T = Any_Id
12097 then
12098 return;
12099 end if;
12101 Num_F := 0;
12102 F := First_Formal (Nam);
12103 while Present (F) loop
12104 Num_F := Num_F + 1;
12105 Next_Formal (F);
12106 end loop;
12108 case Attr_Id is
12109 when Attribute_Adjacent | Attribute_Ceiling | Attribute_Copy_Sign |
12110 Attribute_Floor | Attribute_Fraction | Attribute_Machine |
12111 Attribute_Model | Attribute_Remainder | Attribute_Rounding |
12112 Attribute_Unbiased_Rounding =>
12113 OK := Is_Fun
12114 and then Num_F = 1
12115 and then Is_Floating_Point_Type (T);
12117 when Attribute_Image | Attribute_Pred | Attribute_Succ |
12118 Attribute_Value | Attribute_Wide_Image |
12119 Attribute_Wide_Value =>
12120 OK := (Is_Fun and then Num_F = 1 and then Is_Scalar_Type (T));
12122 when Attribute_Max | Attribute_Min =>
12123 OK := (Is_Fun and then Num_F = 2 and then Is_Scalar_Type (T));
12125 when Attribute_Input =>
12126 OK := (Is_Fun and then Num_F = 1);
12128 when Attribute_Output | Attribute_Read | Attribute_Write =>
12129 OK := (not Is_Fun and then Num_F = 2);
12131 when others =>
12132 OK := False;
12133 end case;
12135 if not OK then
12136 Error_Msg_N ("attribute reference has wrong profile for subprogram",
12137 Def);
12138 end if;
12139 end Valid_Default_Attribute;
12141 end Sem_Ch12;