1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2015, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Aspects
; use Aspects
;
27 with Atree
; use Atree
;
28 with Einfo
; use Einfo
;
29 with Elists
; use Elists
;
30 with Errout
; use Errout
;
31 with Expander
; use Expander
;
32 with Exp_Disp
; use Exp_Disp
;
33 with Fname
; use Fname
;
34 with Fname
.UF
; use Fname
.UF
;
35 with Freeze
; use Freeze
;
36 with Ghost
; use Ghost
;
37 with Itypes
; use Itypes
;
39 with Lib
.Load
; use Lib
.Load
;
40 with Lib
.Xref
; use Lib
.Xref
;
41 with Nlists
; use Nlists
;
42 with Namet
; use Namet
;
43 with Nmake
; use Nmake
;
45 with Rident
; use Rident
;
46 with Restrict
; use Restrict
;
47 with Rtsfind
; use Rtsfind
;
49 with Sem_Aux
; use Sem_Aux
;
50 with Sem_Cat
; use Sem_Cat
;
51 with Sem_Ch3
; use Sem_Ch3
;
52 with Sem_Ch6
; use Sem_Ch6
;
53 with Sem_Ch7
; use Sem_Ch7
;
54 with Sem_Ch8
; use Sem_Ch8
;
55 with Sem_Ch10
; use Sem_Ch10
;
56 with Sem_Ch13
; use Sem_Ch13
;
57 with Sem_Dim
; use Sem_Dim
;
58 with Sem_Disp
; use Sem_Disp
;
59 with Sem_Elab
; use Sem_Elab
;
60 with Sem_Elim
; use Sem_Elim
;
61 with Sem_Eval
; use Sem_Eval
;
62 with Sem_Prag
; use Sem_Prag
;
63 with Sem_Res
; use Sem_Res
;
64 with Sem_Type
; use Sem_Type
;
65 with Sem_Util
; use Sem_Util
;
66 with Sem_Warn
; use Sem_Warn
;
67 with Stand
; use Stand
;
68 with Sinfo
; use Sinfo
;
69 with Sinfo
.CN
; use Sinfo
.CN
;
70 with Sinput
; use Sinput
;
71 with Sinput
.L
; use Sinput
.L
;
72 with Snames
; use Snames
;
73 with Stringt
; use Stringt
;
74 with Uname
; use Uname
;
76 with Tbuild
; use Tbuild
;
77 with Uintp
; use Uintp
;
78 with Urealp
; use Urealp
;
79 with Warnsw
; use Warnsw
;
83 package body Sem_Ch12
is
85 ----------------------------------------------------------
86 -- Implementation of Generic Analysis and Instantiation --
87 ----------------------------------------------------------
89 -- GNAT implements generics by macro expansion. No attempt is made to share
90 -- generic instantiations (for now). Analysis of a generic definition does
91 -- not perform any expansion action, but the expander must be called on the
92 -- tree for each instantiation, because the expansion may of course depend
93 -- on the generic actuals. All of this is best achieved as follows:
95 -- a) Semantic analysis of a generic unit is performed on a copy of the
96 -- tree for the generic unit. All tree modifications that follow analysis
97 -- do not affect the original tree. Links are kept between the original
98 -- tree and the copy, in order to recognize non-local references within
99 -- the generic, and propagate them to each instance (recall that name
100 -- resolution is done on the generic declaration: generics are not really
101 -- macros). This is summarized in the following diagram:
103 -- .-----------. .----------.
104 -- | semantic |<--------------| generic |
106 -- | |==============>| |
107 -- |___________| global |__________|
118 -- b) Each instantiation copies the original tree, and inserts into it a
119 -- series of declarations that describe the mapping between generic formals
120 -- and actuals. For example, a generic In OUT parameter is an object
121 -- renaming of the corresponding actual, etc. Generic IN parameters are
122 -- constant declarations.
124 -- c) In order to give the right visibility for these renamings, we use
125 -- a different scheme for package and subprogram instantiations. For
126 -- packages, the list of renamings is inserted into the package
127 -- specification, before the visible declarations of the package. The
128 -- renamings are analyzed before any of the text of the instance, and are
129 -- thus visible at the right place. Furthermore, outside of the instance,
130 -- the generic parameters are visible and denote their corresponding
133 -- For subprograms, we create a container package to hold the renamings
134 -- and the subprogram instance itself. Analysis of the package makes the
135 -- renaming declarations visible to the subprogram. After analyzing the
136 -- package, the defining entity for the subprogram is touched-up so that
137 -- it appears declared in the current scope, and not inside the container
140 -- If the instantiation is a compilation unit, the container package is
141 -- given the same name as the subprogram instance. This ensures that
142 -- the elaboration procedure called by the binder, using the compilation
143 -- unit name, calls in fact the elaboration procedure for the package.
145 -- Not surprisingly, private types complicate this approach. By saving in
146 -- the original generic object the non-local references, we guarantee that
147 -- the proper entities are referenced at the point of instantiation.
148 -- However, for private types, this by itself does not insure that the
149 -- proper VIEW of the entity is used (the full type may be visible at the
150 -- point of generic definition, but not at instantiation, or vice-versa).
151 -- In order to reference the proper view, we special-case any reference
152 -- to private types in the generic object, by saving both views, one in
153 -- the generic and one in the semantic copy. At time of instantiation, we
154 -- check whether the two views are consistent, and exchange declarations if
155 -- necessary, in order to restore the correct visibility. Similarly, if
156 -- the instance view is private when the generic view was not, we perform
157 -- the exchange. After completing the instantiation, we restore the
158 -- current visibility. The flag Has_Private_View marks identifiers in the
159 -- the generic unit that require checking.
161 -- Visibility within nested generic units requires special handling.
162 -- Consider the following scheme:
164 -- type Global is ... -- outside of generic unit.
168 -- type Semi_Global is ... -- global to inner.
171 -- procedure inner (X1 : Global; X2 : Semi_Global);
173 -- procedure in2 is new inner (...); -- 4
176 -- package New_Outer is new Outer (...); -- 2
177 -- procedure New_Inner is new New_Outer.Inner (...); -- 3
179 -- The semantic analysis of Outer captures all occurrences of Global.
180 -- The semantic analysis of Inner (at 1) captures both occurrences of
181 -- Global and Semi_Global.
183 -- At point 2 (instantiation of Outer), we also produce a generic copy
184 -- of Inner, even though Inner is, at that point, not being instantiated.
185 -- (This is just part of the semantic analysis of New_Outer).
187 -- Critically, references to Global within Inner must be preserved, while
188 -- references to Semi_Global should not preserved, because they must now
189 -- resolve to an entity within New_Outer. To distinguish between these, we
190 -- use a global variable, Current_Instantiated_Parent, which is set when
191 -- performing a generic copy during instantiation (at 2). This variable is
192 -- used when performing a generic copy that is not an instantiation, but
193 -- that is nested within one, as the occurrence of 1 within 2. The analysis
194 -- of a nested generic only preserves references that are global to the
195 -- enclosing Current_Instantiated_Parent. We use the Scope_Depth value to
196 -- determine whether a reference is external to the given parent.
198 -- The instantiation at point 3 requires no special treatment. The method
199 -- works as well for further nestings of generic units, but of course the
200 -- variable Current_Instantiated_Parent must be stacked because nested
201 -- instantiations can occur, e.g. the occurrence of 4 within 2.
203 -- The instantiation of package and subprogram bodies is handled in a
204 -- similar manner, except that it is delayed until after semantic
205 -- analysis is complete. In this fashion complex cross-dependencies
206 -- between several package declarations and bodies containing generics
207 -- can be compiled which otherwise would diagnose spurious circularities.
209 -- For example, it is possible to compile two packages A and B that
210 -- have the following structure:
212 -- package A is package B is
213 -- generic ... generic ...
214 -- package G_A is package G_B is
217 -- package body A is package body B is
218 -- package N_B is new G_B (..) package N_A is new G_A (..)
220 -- The table Pending_Instantiations in package Inline is used to keep
221 -- track of body instantiations that are delayed in this manner. Inline
222 -- handles the actual calls to do the body instantiations. This activity
223 -- is part of Inline, since the processing occurs at the same point, and
224 -- for essentially the same reason, as the handling of inlined routines.
226 ----------------------------------------------
227 -- Detection of Instantiation Circularities --
228 ----------------------------------------------
230 -- If we have a chain of instantiations that is circular, this is static
231 -- error which must be detected at compile time. The detection of these
232 -- circularities is carried out at the point that we insert a generic
233 -- instance spec or body. If there is a circularity, then the analysis of
234 -- the offending spec or body will eventually result in trying to load the
235 -- same unit again, and we detect this problem as we analyze the package
236 -- instantiation for the second time.
238 -- At least in some cases after we have detected the circularity, we get
239 -- into trouble if we try to keep going. The following flag is set if a
240 -- circularity is detected, and used to abandon compilation after the
241 -- messages have been posted.
243 -----------------------------------------
244 -- Implementation of Generic Contracts --
245 -----------------------------------------
247 -- A "contract" is a collection of aspects and pragmas that either verify a
248 -- property of a construct at runtime or classify the data flow to and from
249 -- the construct in some fashion.
251 -- Generic packages, subprograms and their respective bodies may be subject
252 -- to the following contract-related aspects or pragmas collectively known
255 -- package subprogram [body]
256 -- Abstract_State Contract_Cases
257 -- Initial_Condition Depends
258 -- Initializes Extensions_Visible
261 -- Refined_State Post_Class
271 -- Most package contract annotations utilize forward references to classify
272 -- data declared within the package [body]. Subprogram annotations then use
273 -- the classifications to further refine them. These inter dependencies are
274 -- problematic with respect to the implementation of generics because their
275 -- analysis, capture of global references and instantiation does not mesh
276 -- well with the existing mechanism.
278 -- 1) Analysis of generic contracts is carried out the same way non-generic
279 -- contracts are analyzed:
281 -- 1.1) General rule - a contract is analyzed after all related aspects
282 -- and pragmas are analyzed. This is done by routines
284 -- Analyze_Package_Body_Contract
285 -- Analyze_Package_Contract
286 -- Analyze_Subprogram_Body_Contract
287 -- Analyze_Subprogram_Contract
289 -- 1.2) Compilation unit - the contract is analyzed after Pragmas_After
292 -- 1.3) Compilation unit body - the contract is analyzed at the end of
293 -- the body declaration list.
295 -- 1.4) Package - the contract is analyzed at the end of the private or
296 -- visible declarations, prior to analyzing the contracts of any nested
297 -- packages or subprograms.
299 -- 1.5) Package body - the contract is analyzed at the end of the body
300 -- declaration list, prior to analyzing the contracts of any nested
301 -- packages or subprograms.
303 -- 1.6) Subprogram - if the subprogram is declared inside a block, a
304 -- package or a subprogram, then its contract is analyzed at the end of
305 -- the enclosing declarations, otherwise the subprogram is a compilation
308 -- 1.7) Subprogram body - if the subprogram body is declared inside a
309 -- block, a package body or a subprogram body, then its contract is
310 -- analyzed at the end of the enclosing declarations, otherwise the
311 -- subprogram is a compilation unit 1.3).
313 -- 2) Capture of global references within contracts is done after capturing
314 -- global references within the generic template. There are two reasons for
315 -- this delay - pragma annotations are not part of the generic template in
316 -- the case of a generic subprogram declaration, and analysis of contracts
319 -- Contract-related source pragmas within generic templates are prepared
320 -- for delayed capture of global references by routine
322 -- Create_Generic_Contract
324 -- The routine associates these pragmas with the contract of the template.
325 -- In the case of a generic subprogram declaration, the routine creates
326 -- generic templates for the pragmas declared after the subprogram because
327 -- they are not part of the template.
329 -- generic -- template starts
330 -- procedure Gen_Proc (Input : Integer); -- template ends
331 -- pragma Precondition (Input > 0); -- requires own template
333 -- 2.1) The capture of global references with aspect specifications and
334 -- source pragmas that apply to a generic unit must be suppressed when
335 -- the generic template is being processed because the contracts have not
336 -- been analyzed yet. Any attempts to capture global references at that
337 -- point will destroy the Associated_Node linkages and leave the template
338 -- undecorated. This delay is controlled by routine
340 -- Requires_Delayed_Save
342 -- 2.2) The real capture of global references within a contract is done
343 -- after the contract has been analyzed, by routine
345 -- Save_Global_References_In_Contract
347 -- 3) The instantiation of a generic contract occurs as part of the
348 -- instantiation of the contract owner. Generic subprogram declarations
349 -- require additional processing when the contract is specified by pragmas
350 -- because the pragmas are not part of the generic template. This is done
353 -- Instantiate_Subprogram_Contract
355 Circularity_Detected
: Boolean := False;
356 -- This should really be reset on encountering a new main unit, but in
357 -- practice we are not using multiple main units so it is not critical.
359 --------------------------------------------------
360 -- Formal packages and partial parameterization --
361 --------------------------------------------------
363 -- When compiling a generic, a formal package is a local instantiation. If
364 -- declared with a box, its generic formals are visible in the enclosing
365 -- generic. If declared with a partial list of actuals, those actuals that
366 -- are defaulted (covered by an Others clause, or given an explicit box
367 -- initialization) are also visible in the enclosing generic, while those
368 -- that have a corresponding actual are not.
370 -- In our source model of instantiation, the same visibility must be
371 -- present in the spec and body of an instance: the names of the formals
372 -- that are defaulted must be made visible within the instance, and made
373 -- invisible (hidden) after the instantiation is complete, so that they
374 -- are not accessible outside of the instance.
376 -- In a generic, a formal package is treated like a special instantiation.
377 -- Our Ada 95 compiler handled formals with and without box in different
378 -- ways. With partial parameterization, we use a single model for both.
379 -- We create a package declaration that consists of the specification of
380 -- the generic package, and a set of declarations that map the actuals
381 -- into local renamings, just as we do for bona fide instantiations. For
382 -- defaulted parameters and formals with a box, we copy directly the
383 -- declarations of the formal into this local package. The result is a
384 -- a package whose visible declarations may include generic formals. This
385 -- package is only used for type checking and visibility analysis, and
386 -- never reaches the back-end, so it can freely violate the placement
387 -- rules for generic formal declarations.
389 -- The list of declarations (renamings and copies of formals) is built
390 -- by Analyze_Associations, just as for regular instantiations.
392 -- At the point of instantiation, conformance checking must be applied only
393 -- to those parameters that were specified in the formal. We perform this
394 -- checking by creating another internal instantiation, this one including
395 -- only the renamings and the formals (the rest of the package spec is not
396 -- relevant to conformance checking). We can then traverse two lists: the
397 -- list of actuals in the instance that corresponds to the formal package,
398 -- and the list of actuals produced for this bogus instantiation. We apply
399 -- the conformance rules to those actuals that are not defaulted (i.e.
400 -- which still appear as generic formals.
402 -- When we compile an instance body we must make the right parameters
403 -- visible again. The predicate Is_Generic_Formal indicates which of the
404 -- formals should have its Is_Hidden flag reset.
406 -----------------------
407 -- Local subprograms --
408 -----------------------
410 procedure Abandon_Instantiation
(N
: Node_Id
);
411 pragma No_Return
(Abandon_Instantiation
);
412 -- Posts an error message "instantiation abandoned" at the indicated node
413 -- and then raises the exception Instantiation_Error to do it.
415 procedure Analyze_Formal_Array_Type
416 (T
: in out Entity_Id
;
418 -- A formal array type is treated like an array type declaration, and
419 -- invokes Array_Type_Declaration (sem_ch3) whose first parameter is
420 -- in-out, because in the case of an anonymous type the entity is
421 -- actually created in the procedure.
423 -- The following procedures treat other kinds of formal parameters
425 procedure Analyze_Formal_Derived_Interface_Type
430 procedure Analyze_Formal_Derived_Type
435 procedure Analyze_Formal_Interface_Type
440 -- The following subprograms create abbreviated declarations for formal
441 -- scalar types. We introduce an anonymous base of the proper class for
442 -- each of them, and define the formals as constrained first subtypes of
443 -- their bases. The bounds are expressions that are non-static in the
446 procedure Analyze_Formal_Decimal_Fixed_Point_Type
447 (T
: Entity_Id
; Def
: Node_Id
);
448 procedure Analyze_Formal_Discrete_Type
(T
: Entity_Id
; Def
: Node_Id
);
449 procedure Analyze_Formal_Floating_Type
(T
: Entity_Id
; Def
: Node_Id
);
450 procedure Analyze_Formal_Signed_Integer_Type
(T
: Entity_Id
; Def
: Node_Id
);
451 procedure Analyze_Formal_Modular_Type
(T
: Entity_Id
; Def
: Node_Id
);
452 procedure Analyze_Formal_Ordinary_Fixed_Point_Type
453 (T
: Entity_Id
; Def
: Node_Id
);
455 procedure Analyze_Formal_Private_Type
459 -- Creates a new private type, which does not require completion
461 procedure Analyze_Formal_Incomplete_Type
(T
: Entity_Id
; Def
: Node_Id
);
462 -- Ada 2012: Creates a new incomplete type whose actual does not freeze
464 procedure Analyze_Generic_Formal_Part
(N
: Node_Id
);
465 -- Analyze generic formal part
467 procedure Analyze_Generic_Access_Type
(T
: Entity_Id
; Def
: Node_Id
);
468 -- Create a new access type with the given designated type
470 function Analyze_Associations
473 F_Copy
: List_Id
) return List_Id
;
474 -- At instantiation time, build the list of associations between formals
475 -- and actuals. Each association becomes a renaming declaration for the
476 -- formal entity. F_Copy is the analyzed list of formals in the generic
477 -- copy. It is used to apply legality checks to the actuals. I_Node is the
478 -- instantiation node itself.
480 procedure Analyze_Subprogram_Instantiation
484 procedure Build_Instance_Compilation_Unit_Nodes
488 -- This procedure is used in the case where the generic instance of a
489 -- subprogram body or package body is a library unit. In this case, the
490 -- original library unit node for the generic instantiation must be
491 -- replaced by the resulting generic body, and a link made to a new
492 -- compilation unit node for the generic declaration. The argument N is
493 -- the original generic instantiation. Act_Body and Act_Decl are the body
494 -- and declaration of the instance (either package body and declaration
495 -- nodes or subprogram body and declaration nodes depending on the case).
496 -- On return, the node N has been rewritten with the actual body.
498 procedure Check_Access_Definition
(N
: Node_Id
);
499 -- Subsidiary routine to null exclusion processing. Perform an assertion
500 -- check on Ada version and the presence of an access definition in N.
502 procedure Check_Formal_Packages
(P_Id
: Entity_Id
);
503 -- Apply the following to all formal packages in generic associations
505 procedure Check_Formal_Package_Instance
506 (Formal_Pack
: Entity_Id
;
507 Actual_Pack
: Entity_Id
);
508 -- Verify that the actuals of the actual instance match the actuals of
509 -- the template for a formal package that is not declared with a box.
511 procedure Check_Forward_Instantiation
(Decl
: Node_Id
);
512 -- If the generic is a local entity and the corresponding body has not
513 -- been seen yet, flag enclosing packages to indicate that it will be
514 -- elaborated after the generic body. Subprograms declared in the same
515 -- package cannot be inlined by the front-end because front-end inlining
516 -- requires a strict linear order of elaboration.
518 function Check_Hidden_Primitives
(Assoc_List
: List_Id
) return Elist_Id
;
519 -- Check if some association between formals and actuals requires to make
520 -- visible primitives of a tagged type, and make those primitives visible.
521 -- Return the list of primitives whose visibility is modified (to restore
522 -- their visibility later through Restore_Hidden_Primitives). If no
523 -- candidate is found then return No_Elist.
525 procedure Check_Hidden_Child_Unit
527 Gen_Unit
: Entity_Id
;
528 Act_Decl_Id
: Entity_Id
);
529 -- If the generic unit is an implicit child instance within a parent
530 -- instance, we need to make an explicit test that it is not hidden by
531 -- a child instance of the same name and parent.
533 procedure Check_Generic_Actuals
534 (Instance
: Entity_Id
;
535 Is_Formal_Box
: Boolean);
536 -- Similar to previous one. Check the actuals in the instantiation,
537 -- whose views can change between the point of instantiation and the point
538 -- of instantiation of the body. In addition, mark the generic renamings
539 -- as generic actuals, so that they are not compatible with other actuals.
540 -- Recurse on an actual that is a formal package whose declaration has
543 function Contains_Instance_Of
546 N
: Node_Id
) return Boolean;
547 -- Inner is instantiated within the generic Outer. Check whether Inner
548 -- directly or indirectly contains an instance of Outer or of one of its
549 -- parents, in the case of a subunit. Each generic unit holds a list of
550 -- the entities instantiated within (at any depth). This procedure
551 -- determines whether the set of such lists contains a cycle, i.e. an
552 -- illegal circular instantiation.
554 function Denotes_Formal_Package
556 On_Exit
: Boolean := False;
557 Instance
: Entity_Id
:= Empty
) return Boolean;
558 -- Returns True if E is a formal package of an enclosing generic, or
559 -- the actual for such a formal in an enclosing instantiation. If such
560 -- a package is used as a formal in an nested generic, or as an actual
561 -- in a nested instantiation, the visibility of ITS formals should not
562 -- be modified. When called from within Restore_Private_Views, the flag
563 -- On_Exit is true, to indicate that the search for a possible enclosing
564 -- instance should ignore the current one. In that case Instance denotes
565 -- the declaration for which this is an actual. This declaration may be
566 -- an instantiation in the source, or the internal instantiation that
567 -- corresponds to the actual for a formal package.
569 function Earlier
(N1
, N2
: Node_Id
) return Boolean;
570 -- Yields True if N1 and N2 appear in the same compilation unit,
571 -- ignoring subunits, and if N1 is to the left of N2 in a left-to-right
572 -- traversal of the tree for the unit. Used to determine the placement
573 -- of freeze nodes for instance bodies that may depend on other instances.
575 function Find_Actual_Type
577 Gen_Type
: Entity_Id
) return Entity_Id
;
578 -- When validating the actual types of a child instance, check whether
579 -- the formal is a formal type of the parent unit, and retrieve the current
580 -- actual for it. Typ is the entity in the analyzed formal type declaration
581 -- (component or index type of an array type, or designated type of an
582 -- access formal) and Gen_Type is the enclosing analyzed formal array
583 -- or access type. The desired actual may be a formal of a parent, or may
584 -- be declared in a formal package of a parent. In both cases it is a
585 -- generic actual type because it appears within a visible instance.
586 -- Finally, it may be declared in a parent unit without being a formal
587 -- of that unit, in which case it must be retrieved by visibility.
588 -- Ambiguities may still arise if two homonyms are declared in two formal
589 -- packages, and the prefix of the formal type may be needed to resolve
590 -- the ambiguity in the instance ???
592 procedure Freeze_Subprogram_Body
593 (Inst_Node
: Node_Id
;
595 Pack_Id
: Entity_Id
);
596 -- The generic body may appear textually after the instance, including
597 -- in the proper body of a stub, or within a different package instance.
598 -- Given that the instance can only be elaborated after the generic, we
599 -- place freeze_nodes for the instance and/or for packages that may enclose
600 -- the instance and the generic, so that the back-end can establish the
601 -- proper order of elaboration.
603 function Get_Associated_Node
(N
: Node_Id
) return Node_Id
;
604 -- In order to propagate semantic information back from the analyzed copy
605 -- to the original generic, we maintain links between selected nodes in the
606 -- generic and their corresponding copies. At the end of generic analysis,
607 -- the routine Save_Global_References traverses the generic tree, examines
608 -- the semantic information, and preserves the links to those nodes that
609 -- contain global information. At instantiation, the information from the
610 -- associated node is placed on the new copy, so that name resolution is
613 -- Three kinds of source nodes have associated nodes:
615 -- a) those that can reference (denote) entities, that is identifiers,
616 -- character literals, expanded_names, operator symbols, operators,
617 -- and attribute reference nodes. These nodes have an Entity field
618 -- and are the set of nodes that are in N_Has_Entity.
620 -- b) aggregates (N_Aggregate and N_Extension_Aggregate)
622 -- c) selected components (N_Selected_Component)
624 -- For the first class, the associated node preserves the entity if it is
625 -- global. If the generic contains nested instantiations, the associated
626 -- node itself has been recopied, and a chain of them must be followed.
628 -- For aggregates, the associated node allows retrieval of the type, which
629 -- may otherwise not appear in the generic. The view of this type may be
630 -- different between generic and instantiation, and the full view can be
631 -- installed before the instantiation is analyzed. For aggregates of type
632 -- extensions, the same view exchange may have to be performed for some of
633 -- the ancestor types, if their view is private at the point of
636 -- Nodes that are selected components in the parse tree may be rewritten
637 -- as expanded names after resolution, and must be treated as potential
638 -- entity holders, which is why they also have an Associated_Node.
640 -- Nodes that do not come from source, such as freeze nodes, do not appear
641 -- in the generic tree, and need not have an associated node.
643 -- The associated node is stored in the Associated_Node field. Note that
644 -- this field overlaps Entity, which is fine, because the whole point is
645 -- that we don't need or want the normal Entity field in this situation.
647 function Has_Been_Exchanged
(E
: Entity_Id
) return Boolean;
648 -- Traverse the Exchanged_Views list to see if a type was private
649 -- and has already been flipped during this phase of instantiation.
651 procedure Hide_Current_Scope
;
652 -- When instantiating a generic child unit, the parent context must be
653 -- present, but the instance and all entities that may be generated
654 -- must be inserted in the current scope. We leave the current scope
655 -- on the stack, but make its entities invisible to avoid visibility
656 -- problems. This is reversed at the end of the instantiation. This is
657 -- not done for the instantiation of the bodies, which only require the
658 -- instances of the generic parents to be in scope.
660 function In_Same_Declarative_Part
662 Inst
: Node_Id
) return Boolean;
663 -- True if the instantiation Inst and the given freeze_node F_Node appear
664 -- within the same declarative part, ignoring subunits, but with no inter-
665 -- vening subprograms or concurrent units. Used to find the proper plave
666 -- for the freeze node of an instance, when the generic is declared in a
667 -- previous instance. If predicate is true, the freeze node of the instance
668 -- can be placed after the freeze node of the previous instance, Otherwise
669 -- it has to be placed at the end of the current declarative part.
671 function In_Main_Context
(E
: Entity_Id
) return Boolean;
672 -- Check whether an instantiation is in the context of the main unit.
673 -- Used to determine whether its body should be elaborated to allow
674 -- front-end inlining.
676 procedure Inherit_Context
(Gen_Decl
: Node_Id
; Inst
: Node_Id
);
677 -- Add the context clause of the unit containing a generic unit to a
678 -- compilation unit that is, or contains, an instantiation.
681 -- Establish environment for subsequent instantiation. Separated from
682 -- Save_Env because data-structures for visibility handling must be
683 -- initialized before call to Check_Generic_Child_Unit.
685 procedure Inline_Instance_Body
687 Gen_Unit
: Entity_Id
;
689 -- If front-end inlining is requested, instantiate the package body,
690 -- and preserve the visibility of its compilation unit, to insure
691 -- that successive instantiations succeed.
693 procedure Insert_Freeze_Node_For_Instance
696 -- N denotes a package or a subprogram instantiation and F_Node is the
697 -- associated freeze node. Insert the freeze node before the first source
698 -- body which follows immediately after N. If no such body is found, the
699 -- freeze node is inserted at the end of the declarative region which
702 procedure Install_Body
707 -- If the instantiation happens textually before the body of the generic,
708 -- the instantiation of the body must be analyzed after the generic body,
709 -- and not at the point of instantiation. Such early instantiations can
710 -- happen if the generic and the instance appear in a package declaration
711 -- because the generic body can only appear in the corresponding package
712 -- body. Early instantiations can also appear if generic, instance and
713 -- body are all in the declarative part of a subprogram or entry. Entities
714 -- of packages that are early instantiations are delayed, and their freeze
715 -- node appears after the generic body.
717 procedure Install_Formal_Packages
(Par
: Entity_Id
);
718 -- Install the visible part of any formal of the parent that is a formal
719 -- package. Note that for the case of a formal package with a box, this
720 -- includes the formal part of the formal package (12.7(10/2)).
722 procedure Install_Hidden_Primitives
723 (Prims_List
: in out Elist_Id
;
726 -- Remove suffix 'P' from hidden primitives of Act_T to match the
727 -- visibility of primitives of Gen_T. The list of primitives to which
728 -- the suffix is removed is added to Prims_List to restore them later.
730 procedure Install_Parent
(P
: Entity_Id
; In_Body
: Boolean := False);
731 -- When compiling an instance of a child unit the parent (which is
732 -- itself an instance) is an enclosing scope that must be made
733 -- immediately visible. This procedure is also used to install the non-
734 -- generic parent of a generic child unit when compiling its body, so
735 -- that full views of types in the parent are made visible.
737 -- The functions Instantiate_XXX perform various legality checks and build
738 -- the declarations for instantiated generic parameters. In all of these
739 -- Formal is the entity in the generic unit, Actual is the entity of
740 -- expression in the generic associations, and Analyzed_Formal is the
741 -- formal in the generic copy, which contains the semantic information to
742 -- be used to validate the actual.
744 function Instantiate_Object
747 Analyzed_Formal
: Node_Id
) return List_Id
;
749 function Instantiate_Type
752 Analyzed_Formal
: Node_Id
;
753 Actual_Decls
: List_Id
) return List_Id
;
755 function Instantiate_Formal_Subprogram
758 Analyzed_Formal
: Node_Id
) return Node_Id
;
760 function Instantiate_Formal_Package
763 Analyzed_Formal
: Node_Id
) return List_Id
;
764 -- If the formal package is declared with a box, special visibility rules
765 -- apply to its formals: they are in the visible part of the package. This
766 -- is true in the declarative region of the formal package, that is to say
767 -- in the enclosing generic or instantiation. For an instantiation, the
768 -- parameters of the formal package are made visible in an explicit step.
769 -- Furthermore, if the actual has a visible USE clause, these formals must
770 -- be made potentially use-visible as well. On exit from the enclosing
771 -- instantiation, the reverse must be done.
773 -- For a formal package declared without a box, there are conformance rules
774 -- that apply to the actuals in the generic declaration and the actuals of
775 -- the actual package in the enclosing instantiation. The simplest way to
776 -- apply these rules is to repeat the instantiation of the formal package
777 -- in the context of the enclosing instance, and compare the generic
778 -- associations of this instantiation with those of the actual package.
779 -- This internal instantiation only needs to contain the renamings of the
780 -- formals: the visible and private declarations themselves need not be
783 -- In Ada 2005, the formal package may be only partially parameterized.
784 -- In that case the visibility step must make visible those actuals whose
785 -- corresponding formals were given with a box. A final complication
786 -- involves inherited operations from formal derived types, which must
787 -- be visible if the type is.
789 function Is_In_Main_Unit
(N
: Node_Id
) return Boolean;
790 -- Test if given node is in the main unit
792 procedure Load_Parent_Of_Generic
795 Body_Optional
: Boolean := False);
796 -- If the generic appears in a separate non-generic library unit, load the
797 -- corresponding body to retrieve the body of the generic. N is the node
798 -- for the generic instantiation, Spec is the generic package declaration.
800 -- Body_Optional is a flag that indicates that the body is being loaded to
801 -- ensure that temporaries are generated consistently when there are other
802 -- instances in the current declarative part that precede the one being
803 -- loaded. In that case a missing body is acceptable.
805 procedure Map_Formal_Package_Entities
(Form
: Entity_Id
; Act
: Entity_Id
);
806 -- Within the generic part, entities in the formal package are
807 -- visible. To validate subsequent type declarations, indicate
808 -- the correspondence between the entities in the analyzed formal,
809 -- and the entities in the actual package. There are three packages
810 -- involved in the instantiation of a formal package: the parent
811 -- generic P1 which appears in the generic declaration, the fake
812 -- instantiation P2 which appears in the analyzed generic, and whose
813 -- visible entities may be used in subsequent formals, and the actual
814 -- P3 in the instance. To validate subsequent formals, me indicate
815 -- that the entities in P2 are mapped into those of P3. The mapping of
816 -- entities has to be done recursively for nested packages.
818 procedure Move_Freeze_Nodes
822 -- Freeze nodes can be generated in the analysis of a generic unit, but
823 -- will not be seen by the back-end. It is necessary to move those nodes
824 -- to the enclosing scope if they freeze an outer entity. We place them
825 -- at the end of the enclosing generic package, which is semantically
828 procedure Preanalyze_Actuals
(N
: Node_Id
; Inst
: Entity_Id
:= Empty
);
829 -- Analyze actuals to perform name resolution. Full resolution is done
830 -- later, when the expected types are known, but names have to be captured
831 -- before installing parents of generics, that are not visible for the
832 -- actuals themselves.
834 -- If Inst is present, it is the entity of the package instance. This
835 -- entity is marked as having a limited_view actual when some actual is
836 -- a limited view. This is used to place the instance body properly.
838 procedure Remove_Parent
(In_Body
: Boolean := False);
839 -- Reverse effect after instantiation of child is complete
841 procedure Restore_Hidden_Primitives
(Prims_List
: in out Elist_Id
);
842 -- Restore suffix 'P' to primitives of Prims_List and leave Prims_List
845 procedure Save_Global_References_In_Aspects
(N
: Node_Id
);
846 -- Save all global references found within the expressions of all aspects
847 -- that appear on node N.
849 procedure Set_Instance_Env
850 (Gen_Unit
: Entity_Id
;
851 Act_Unit
: Entity_Id
);
852 -- Save current instance on saved environment, to be used to determine
853 -- the global status of entities in nested instances. Part of Save_Env.
854 -- called after verifying that the generic unit is legal for the instance,
855 -- The procedure also examines whether the generic unit is a predefined
856 -- unit, in order to set configuration switches accordingly. As a result
857 -- the procedure must be called after analyzing and freezing the actuals.
859 procedure Set_Instance_Of
(A
: Entity_Id
; B
: Entity_Id
);
860 -- Associate analyzed generic parameter with corresponding instance. Used
861 -- for semantic checks at instantiation time.
863 function True_Parent
(N
: Node_Id
) return Node_Id
;
864 -- For a subunit, return parent of corresponding stub, else return
867 procedure Valid_Default_Attribute
(Nam
: Entity_Id
; Def
: Node_Id
);
868 -- Verify that an attribute that appears as the default for a formal
869 -- subprogram is a function or procedure with the correct profile.
871 -------------------------------------------
872 -- Data Structures for Generic Renamings --
873 -------------------------------------------
875 -- The map Generic_Renamings associates generic entities with their
876 -- corresponding actuals. Currently used to validate type instances. It
877 -- will eventually be used for all generic parameters to eliminate the
878 -- need for overload resolution in the instance.
880 type Assoc_Ptr
is new Int
;
882 Assoc_Null
: constant Assoc_Ptr
:= -1;
887 Next_In_HTable
: Assoc_Ptr
;
890 package Generic_Renamings
is new Table
.Table
891 (Table_Component_Type
=> Assoc
,
892 Table_Index_Type
=> Assoc_Ptr
,
893 Table_Low_Bound
=> 0,
895 Table_Increment
=> 100,
896 Table_Name
=> "Generic_Renamings");
898 -- Variable to hold enclosing instantiation. When the environment is
899 -- saved for a subprogram inlining, the corresponding Act_Id is empty.
901 Current_Instantiated_Parent
: Assoc
:= (Empty
, Empty
, Assoc_Null
);
903 -- Hash table for associations
905 HTable_Size
: constant := 37;
906 type HTable_Range
is range 0 .. HTable_Size
- 1;
908 procedure Set_Next_Assoc
(E
: Assoc_Ptr
; Next
: Assoc_Ptr
);
909 function Next_Assoc
(E
: Assoc_Ptr
) return Assoc_Ptr
;
910 function Get_Gen_Id
(E
: Assoc_Ptr
) return Entity_Id
;
911 function Hash
(F
: Entity_Id
) return HTable_Range
;
913 package Generic_Renamings_HTable
is new GNAT
.HTable
.Static_HTable
(
914 Header_Num
=> HTable_Range
,
916 Elmt_Ptr
=> Assoc_Ptr
,
917 Null_Ptr
=> Assoc_Null
,
918 Set_Next
=> Set_Next_Assoc
,
921 Get_Key
=> Get_Gen_Id
,
925 Exchanged_Views
: Elist_Id
;
926 -- This list holds the private views that have been exchanged during
927 -- instantiation to restore the visibility of the generic declaration.
928 -- (see comments above). After instantiation, the current visibility is
929 -- reestablished by means of a traversal of this list.
931 Hidden_Entities
: Elist_Id
;
932 -- This list holds the entities of the current scope that are removed
933 -- from immediate visibility when instantiating a child unit. Their
934 -- visibility is restored in Remove_Parent.
936 -- Because instantiations can be recursive, the following must be saved
937 -- on entry and restored on exit from an instantiation (spec or body).
938 -- This is done by the two procedures Save_Env and Restore_Env. For
939 -- package and subprogram instantiations (but not for the body instances)
940 -- the action of Save_Env is done in two steps: Init_Env is called before
941 -- Check_Generic_Child_Unit, because setting the parent instances requires
942 -- that the visibility data structures be properly initialized. Once the
943 -- generic is unit is validated, Set_Instance_Env completes Save_Env.
945 Parent_Unit_Visible
: Boolean := False;
946 -- Parent_Unit_Visible is used when the generic is a child unit, and
947 -- indicates whether the ultimate parent of the generic is visible in the
948 -- instantiation environment. It is used to reset the visibility of the
949 -- parent at the end of the instantiation (see Remove_Parent).
951 Instance_Parent_Unit
: Entity_Id
:= Empty
;
952 -- This records the ultimate parent unit of an instance of a generic
953 -- child unit and is used in conjunction with Parent_Unit_Visible to
954 -- indicate the unit to which the Parent_Unit_Visible flag corresponds.
956 type Instance_Env
is record
957 Instantiated_Parent
: Assoc
;
958 Exchanged_Views
: Elist_Id
;
959 Hidden_Entities
: Elist_Id
;
960 Current_Sem_Unit
: Unit_Number_Type
;
961 Parent_Unit_Visible
: Boolean := False;
962 Instance_Parent_Unit
: Entity_Id
:= Empty
;
963 Switches
: Config_Switches_Type
;
966 package Instance_Envs
is new Table
.Table
(
967 Table_Component_Type
=> Instance_Env
,
968 Table_Index_Type
=> Int
,
969 Table_Low_Bound
=> 0,
971 Table_Increment
=> 100,
972 Table_Name
=> "Instance_Envs");
974 procedure Restore_Private_Views
975 (Pack_Id
: Entity_Id
;
976 Is_Package
: Boolean := True);
977 -- Restore the private views of external types, and unmark the generic
978 -- renamings of actuals, so that they become compatible subtypes again.
979 -- For subprograms, Pack_Id is the package constructed to hold the
982 procedure Switch_View
(T
: Entity_Id
);
983 -- Switch the partial and full views of a type and its private
984 -- dependents (i.e. its subtypes and derived types).
986 ------------------------------------
987 -- Structures for Error Reporting --
988 ------------------------------------
990 Instantiation_Node
: Node_Id
;
991 -- Used by subprograms that validate instantiation of formal parameters
992 -- where there might be no actual on which to place the error message.
993 -- Also used to locate the instantiation node for generic subunits.
995 Instantiation_Error
: exception;
996 -- When there is a semantic error in the generic parameter matching,
997 -- there is no point in continuing the instantiation, because the
998 -- number of cascaded errors is unpredictable. This exception aborts
999 -- the instantiation process altogether.
1001 S_Adjustment
: Sloc_Adjustment
;
1002 -- Offset created for each node in an instantiation, in order to keep
1003 -- track of the source position of the instantiation in each of its nodes.
1004 -- A subsequent semantic error or warning on a construct of the instance
1005 -- points to both places: the original generic node, and the point of
1006 -- instantiation. See Sinput and Sinput.L for additional details.
1008 ------------------------------------------------------------
1009 -- Data structure for keeping track when inside a Generic --
1010 ------------------------------------------------------------
1012 -- The following table is used to save values of the Inside_A_Generic
1013 -- flag (see spec of Sem) when they are saved by Start_Generic.
1015 package Generic_Flags
is new Table
.Table
(
1016 Table_Component_Type
=> Boolean,
1017 Table_Index_Type
=> Int
,
1018 Table_Low_Bound
=> 0,
1019 Table_Initial
=> 32,
1020 Table_Increment
=> 200,
1021 Table_Name
=> "Generic_Flags");
1023 ---------------------------
1024 -- Abandon_Instantiation --
1025 ---------------------------
1027 procedure Abandon_Instantiation
(N
: Node_Id
) is
1029 Error_Msg_N
("\instantiation abandoned!", N
);
1030 raise Instantiation_Error
;
1031 end Abandon_Instantiation
;
1033 --------------------------
1034 -- Analyze_Associations --
1035 --------------------------
1037 function Analyze_Associations
1040 F_Copy
: List_Id
) return List_Id
1042 Actuals_To_Freeze
: constant Elist_Id
:= New_Elmt_List
;
1043 Assoc
: constant List_Id
:= New_List
;
1044 Default_Actuals
: constant List_Id
:= New_List
;
1045 Gen_Unit
: constant Entity_Id
:=
1046 Defining_Entity
(Parent
(F_Copy
));
1050 Analyzed_Formal
: Node_Id
;
1051 First_Named
: Node_Id
:= Empty
;
1055 Saved_Formal
: Node_Id
;
1057 Default_Formals
: constant List_Id
:= New_List
;
1058 -- If an Others_Choice is present, some of the formals may be defaulted.
1059 -- To simplify the treatment of visibility in an instance, we introduce
1060 -- individual defaults for each such formal. These defaults are
1061 -- appended to the list of associations and replace the Others_Choice.
1063 Found_Assoc
: Node_Id
;
1064 -- Association for the current formal being match. Empty if there are
1065 -- no remaining actuals, or if there is no named association with the
1066 -- name of the formal.
1068 Is_Named_Assoc
: Boolean;
1069 Num_Matched
: Int
:= 0;
1070 Num_Actuals
: Int
:= 0;
1072 Others_Present
: Boolean := False;
1073 Others_Choice
: Node_Id
:= Empty
;
1074 -- In Ada 2005, indicates partial parameterization of a formal
1075 -- package. As usual an other association must be last in the list.
1077 procedure Check_Overloaded_Formal_Subprogram
(Formal
: Entity_Id
);
1078 -- Apply RM 12.3 (9): if a formal subprogram is overloaded, the instance
1079 -- cannot have a named association for it. AI05-0025 extends this rule
1080 -- to formals of formal packages by AI05-0025, and it also applies to
1081 -- box-initialized formals.
1083 function Has_Fully_Defined_Profile
(Subp
: Entity_Id
) return Boolean;
1084 -- Determine whether the parameter types and the return type of Subp
1085 -- are fully defined at the point of instantiation.
1087 function Matching_Actual
1089 A_F
: Entity_Id
) return Node_Id
;
1090 -- Find actual that corresponds to a given a formal parameter. If the
1091 -- actuals are positional, return the next one, if any. If the actuals
1092 -- are named, scan the parameter associations to find the right one.
1093 -- A_F is the corresponding entity in the analyzed generic,which is
1094 -- placed on the selector name for ASIS use.
1096 -- In Ada 2005, a named association may be given with a box, in which
1097 -- case Matching_Actual sets Found_Assoc to the generic association,
1098 -- but return Empty for the actual itself. In this case the code below
1099 -- creates a corresponding declaration for the formal.
1101 function Partial_Parameterization
return Boolean;
1102 -- Ada 2005: if no match is found for a given formal, check if the
1103 -- association for it includes a box, or whether the associations
1104 -- include an Others clause.
1106 procedure Process_Default
(F
: Entity_Id
);
1107 -- Add a copy of the declaration of generic formal F to the list of
1108 -- associations, and add an explicit box association for F if there
1109 -- is none yet, and the default comes from an Others_Choice.
1111 function Renames_Standard_Subprogram
(Subp
: Entity_Id
) return Boolean;
1112 -- Determine whether Subp renames one of the subprograms defined in the
1113 -- generated package Standard.
1115 procedure Set_Analyzed_Formal
;
1116 -- Find the node in the generic copy that corresponds to a given formal.
1117 -- The semantic information on this node is used to perform legality
1118 -- checks on the actuals. Because semantic analysis can introduce some
1119 -- anonymous entities or modify the declaration node itself, the
1120 -- correspondence between the two lists is not one-one. In addition to
1121 -- anonymous types, the presence a formal equality will introduce an
1122 -- implicit declaration for the corresponding inequality.
1124 ----------------------------------------
1125 -- Check_Overloaded_Formal_Subprogram --
1126 ----------------------------------------
1128 procedure Check_Overloaded_Formal_Subprogram
(Formal
: Entity_Id
) is
1129 Temp_Formal
: Entity_Id
;
1132 Temp_Formal
:= First
(Formals
);
1133 while Present
(Temp_Formal
) loop
1134 if Nkind
(Temp_Formal
) in N_Formal_Subprogram_Declaration
1135 and then Temp_Formal
/= Formal
1137 Chars
(Defining_Unit_Name
(Specification
(Formal
))) =
1138 Chars
(Defining_Unit_Name
(Specification
(Temp_Formal
)))
1140 if Present
(Found_Assoc
) then
1142 ("named association not allowed for overloaded formal",
1147 ("named association not allowed for overloaded formal",
1151 Abandon_Instantiation
(Instantiation_Node
);
1156 end Check_Overloaded_Formal_Subprogram
;
1158 -------------------------------
1159 -- Has_Fully_Defined_Profile --
1160 -------------------------------
1162 function Has_Fully_Defined_Profile
(Subp
: Entity_Id
) return Boolean is
1163 function Is_Fully_Defined_Type
(Typ
: Entity_Id
) return Boolean;
1164 -- Determine whethet type Typ is fully defined
1166 ---------------------------
1167 -- Is_Fully_Defined_Type --
1168 ---------------------------
1170 function Is_Fully_Defined_Type
(Typ
: Entity_Id
) return Boolean is
1172 -- A private type without a full view is not fully defined
1174 if Is_Private_Type
(Typ
)
1175 and then No
(Full_View
(Typ
))
1179 -- An incomplete type is never fully defined
1181 elsif Is_Incomplete_Type
(Typ
) then
1184 -- All other types are fully defined
1189 end Is_Fully_Defined_Type
;
1191 -- Local declarations
1195 -- Start of processing for Has_Fully_Defined_Profile
1198 -- Check the parameters
1200 Param
:= First_Formal
(Subp
);
1201 while Present
(Param
) loop
1202 if not Is_Fully_Defined_Type
(Etype
(Param
)) then
1206 Next_Formal
(Param
);
1209 -- Check the return type
1211 return Is_Fully_Defined_Type
(Etype
(Subp
));
1212 end Has_Fully_Defined_Profile
;
1214 ---------------------
1215 -- Matching_Actual --
1216 ---------------------
1218 function Matching_Actual
1220 A_F
: Entity_Id
) return Node_Id
1226 Is_Named_Assoc
:= False;
1228 -- End of list of purely positional parameters
1230 if No
(Actual
) or else Nkind
(Actual
) = N_Others_Choice
then
1231 Found_Assoc
:= Empty
;
1234 -- Case of positional parameter corresponding to current formal
1236 elsif No
(Selector_Name
(Actual
)) then
1237 Found_Assoc
:= Actual
;
1238 Act
:= Explicit_Generic_Actual_Parameter
(Actual
);
1239 Num_Matched
:= Num_Matched
+ 1;
1242 -- Otherwise scan list of named actuals to find the one with the
1243 -- desired name. All remaining actuals have explicit names.
1246 Is_Named_Assoc
:= True;
1247 Found_Assoc
:= Empty
;
1251 while Present
(Actual
) loop
1252 if Chars
(Selector_Name
(Actual
)) = Chars
(F
) then
1253 Set_Entity
(Selector_Name
(Actual
), A_F
);
1254 Set_Etype
(Selector_Name
(Actual
), Etype
(A_F
));
1255 Generate_Reference
(A_F
, Selector_Name
(Actual
));
1256 Found_Assoc
:= Actual
;
1257 Act
:= Explicit_Generic_Actual_Parameter
(Actual
);
1258 Num_Matched
:= Num_Matched
+ 1;
1266 -- Reset for subsequent searches. In most cases the named
1267 -- associations are in order. If they are not, we reorder them
1268 -- to avoid scanning twice the same actual. This is not just a
1269 -- question of efficiency: there may be multiple defaults with
1270 -- boxes that have the same name. In a nested instantiation we
1271 -- insert actuals for those defaults, and cannot rely on their
1272 -- names to disambiguate them.
1274 if Actual
= First_Named
then
1277 elsif Present
(Actual
) then
1278 Insert_Before
(First_Named
, Remove_Next
(Prev
));
1281 Actual
:= First_Named
;
1284 if Is_Entity_Name
(Act
) and then Present
(Entity
(Act
)) then
1285 Set_Used_As_Generic_Actual
(Entity
(Act
));
1289 end Matching_Actual
;
1291 ------------------------------
1292 -- Partial_Parameterization --
1293 ------------------------------
1295 function Partial_Parameterization
return Boolean is
1297 return Others_Present
1298 or else (Present
(Found_Assoc
) and then Box_Present
(Found_Assoc
));
1299 end Partial_Parameterization
;
1301 ---------------------
1302 -- Process_Default --
1303 ---------------------
1305 procedure Process_Default
(F
: Entity_Id
) is
1306 Loc
: constant Source_Ptr
:= Sloc
(I_Node
);
1307 F_Id
: constant Entity_Id
:= Defining_Entity
(F
);
1313 -- Append copy of formal declaration to associations, and create new
1314 -- defining identifier for it.
1316 Decl
:= New_Copy_Tree
(F
);
1317 Id
:= Make_Defining_Identifier
(Sloc
(F_Id
), Chars
(F_Id
));
1319 if Nkind
(F
) in N_Formal_Subprogram_Declaration
then
1320 Set_Defining_Unit_Name
(Specification
(Decl
), Id
);
1323 Set_Defining_Identifier
(Decl
, Id
);
1326 Append
(Decl
, Assoc
);
1328 if No
(Found_Assoc
) then
1330 Make_Generic_Association
(Loc
,
1332 New_Occurrence_Of
(Id
, Loc
),
1333 Explicit_Generic_Actual_Parameter
=> Empty
);
1334 Set_Box_Present
(Default
);
1335 Append
(Default
, Default_Formals
);
1337 end Process_Default
;
1339 ---------------------------------
1340 -- Renames_Standard_Subprogram --
1341 ---------------------------------
1343 function Renames_Standard_Subprogram
(Subp
: Entity_Id
) return Boolean is
1348 while Present
(Id
) loop
1349 if Scope
(Id
) = Standard_Standard
then
1357 end Renames_Standard_Subprogram
;
1359 -------------------------
1360 -- Set_Analyzed_Formal --
1361 -------------------------
1363 procedure Set_Analyzed_Formal
is
1367 while Present
(Analyzed_Formal
) loop
1368 Kind
:= Nkind
(Analyzed_Formal
);
1370 case Nkind
(Formal
) is
1372 when N_Formal_Subprogram_Declaration
=>
1373 exit when Kind
in N_Formal_Subprogram_Declaration
1376 (Defining_Unit_Name
(Specification
(Formal
))) =
1378 (Defining_Unit_Name
(Specification
(Analyzed_Formal
)));
1380 when N_Formal_Package_Declaration
=>
1381 exit when Nkind_In
(Kind
, N_Formal_Package_Declaration
,
1382 N_Generic_Package_Declaration
,
1383 N_Package_Declaration
);
1385 when N_Use_Package_Clause | N_Use_Type_Clause
=> exit;
1389 -- Skip freeze nodes, and nodes inserted to replace
1390 -- unrecognized pragmas.
1393 Kind
not in N_Formal_Subprogram_Declaration
1394 and then not Nkind_In
(Kind
, N_Subprogram_Declaration
,
1398 and then Chars
(Defining_Identifier
(Formal
)) =
1399 Chars
(Defining_Identifier
(Analyzed_Formal
));
1402 Next
(Analyzed_Formal
);
1404 end Set_Analyzed_Formal
;
1406 -- Start of processing for Analyze_Associations
1409 Actuals
:= Generic_Associations
(I_Node
);
1411 if Present
(Actuals
) then
1413 -- Check for an Others choice, indicating a partial parameterization
1414 -- for a formal package.
1416 Actual
:= First
(Actuals
);
1417 while Present
(Actual
) loop
1418 if Nkind
(Actual
) = N_Others_Choice
then
1419 Others_Present
:= True;
1420 Others_Choice
:= Actual
;
1422 if Present
(Next
(Actual
)) then
1423 Error_Msg_N
("others must be last association", Actual
);
1426 -- This subprogram is used both for formal packages and for
1427 -- instantiations. For the latter, associations must all be
1430 if Nkind
(I_Node
) /= N_Formal_Package_Declaration
1431 and then Comes_From_Source
(I_Node
)
1434 ("others association not allowed in an instance",
1438 -- In any case, nothing to do after the others association
1442 elsif Box_Present
(Actual
)
1443 and then Comes_From_Source
(I_Node
)
1444 and then Nkind
(I_Node
) /= N_Formal_Package_Declaration
1447 ("box association not allowed in an instance", Actual
);
1453 -- If named associations are present, save first named association
1454 -- (it may of course be Empty) to facilitate subsequent name search.
1456 First_Named
:= First
(Actuals
);
1457 while Present
(First_Named
)
1458 and then Nkind
(First_Named
) /= N_Others_Choice
1459 and then No
(Selector_Name
(First_Named
))
1461 Num_Actuals
:= Num_Actuals
+ 1;
1466 Named
:= First_Named
;
1467 while Present
(Named
) loop
1468 if Nkind
(Named
) /= N_Others_Choice
1469 and then No
(Selector_Name
(Named
))
1471 Error_Msg_N
("invalid positional actual after named one", Named
);
1472 Abandon_Instantiation
(Named
);
1475 -- A named association may lack an actual parameter, if it was
1476 -- introduced for a default subprogram that turns out to be local
1477 -- to the outer instantiation.
1479 if Nkind
(Named
) /= N_Others_Choice
1480 and then Present
(Explicit_Generic_Actual_Parameter
(Named
))
1482 Num_Actuals
:= Num_Actuals
+ 1;
1488 if Present
(Formals
) then
1489 Formal
:= First_Non_Pragma
(Formals
);
1490 Analyzed_Formal
:= First_Non_Pragma
(F_Copy
);
1492 if Present
(Actuals
) then
1493 Actual
:= First
(Actuals
);
1495 -- All formals should have default values
1501 while Present
(Formal
) loop
1502 Set_Analyzed_Formal
;
1503 Saved_Formal
:= Next_Non_Pragma
(Formal
);
1505 case Nkind
(Formal
) is
1506 when N_Formal_Object_Declaration
=>
1509 (Defining_Identifier
(Formal
),
1510 Defining_Identifier
(Analyzed_Formal
));
1512 if No
(Match
) and then Partial_Parameterization
then
1513 Process_Default
(Formal
);
1517 (Instantiate_Object
(Formal
, Match
, Analyzed_Formal
),
1520 -- For a defaulted in_parameter, create an entry in the
1521 -- the list of defaulted actuals, for GNATProve use. Do
1522 -- not included these defaults for an instance nested
1523 -- within a generic, because the defaults are also used
1524 -- in the analysis of the enclosing generic, and only
1525 -- defaulted subprograms are relevant there.
1527 if No
(Match
) and then not Inside_A_Generic
then
1528 Append_To
(Default_Actuals
,
1529 Make_Generic_Association
(Sloc
(I_Node
),
1532 (Defining_Identifier
(Formal
), Sloc
(I_Node
)),
1533 Explicit_Generic_Actual_Parameter
=>
1534 New_Copy_Tree
(Default_Expression
(Formal
))));
1538 -- If the object is a call to an expression function, this
1539 -- is a freezing point for it.
1541 if Is_Entity_Name
(Match
)
1542 and then Present
(Entity
(Match
))
1544 (Original_Node
(Unit_Declaration_Node
(Entity
(Match
))))
1545 = N_Expression_Function
1547 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
1550 when N_Formal_Type_Declaration
=>
1553 (Defining_Identifier
(Formal
),
1554 Defining_Identifier
(Analyzed_Formal
));
1557 if Partial_Parameterization
then
1558 Process_Default
(Formal
);
1561 Error_Msg_Sloc
:= Sloc
(Gen_Unit
);
1564 Instantiation_Node
, Defining_Identifier
(Formal
));
1566 ("\in instantiation of & declared#",
1567 Instantiation_Node
, Gen_Unit
);
1568 Abandon_Instantiation
(Instantiation_Node
);
1575 (Formal
, Match
, Analyzed_Formal
, Assoc
),
1578 -- An instantiation is a freeze point for the actuals,
1579 -- unless this is a rewritten formal package, or the
1580 -- formal is an Ada 2012 formal incomplete type.
1582 if Nkind
(I_Node
) = N_Formal_Package_Declaration
1584 (Ada_Version
>= Ada_2012
1586 Ekind
(Defining_Identifier
(Analyzed_Formal
)) =
1592 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
1596 -- A remote access-to-class-wide type is not a legal actual
1597 -- for a generic formal of an access type (E.2.2(17/2)).
1598 -- In GNAT an exception to this rule is introduced when
1599 -- the formal is marked as remote using implementation
1600 -- defined aspect/pragma Remote_Access_Type. In that case
1601 -- the actual must be remote as well.
1603 -- If the current instantiation is the construction of a
1604 -- local copy for a formal package the actuals may be
1605 -- defaulted, and there is no matching actual to check.
1607 if Nkind
(Analyzed_Formal
) = N_Formal_Type_Declaration
1609 Nkind
(Formal_Type_Definition
(Analyzed_Formal
)) =
1610 N_Access_To_Object_Definition
1611 and then Present
(Match
)
1614 Formal_Ent
: constant Entity_Id
:=
1615 Defining_Identifier
(Analyzed_Formal
);
1617 if Is_Remote_Access_To_Class_Wide_Type
(Entity
(Match
))
1618 = Is_Remote_Types
(Formal_Ent
)
1620 -- Remoteness of formal and actual match
1624 elsif Is_Remote_Types
(Formal_Ent
) then
1626 -- Remote formal, non-remote actual
1629 ("actual for& must be remote", Match
, Formal_Ent
);
1632 -- Non-remote formal, remote actual
1635 ("actual for& may not be remote",
1641 when N_Formal_Subprogram_Declaration
=>
1644 (Defining_Unit_Name
(Specification
(Formal
)),
1645 Defining_Unit_Name
(Specification
(Analyzed_Formal
)));
1647 -- If the formal subprogram has the same name as another
1648 -- formal subprogram of the generic, then a named
1649 -- association is illegal (12.3(9)). Exclude named
1650 -- associations that are generated for a nested instance.
1653 and then Is_Named_Assoc
1654 and then Comes_From_Source
(Found_Assoc
)
1656 Check_Overloaded_Formal_Subprogram
(Formal
);
1659 -- If there is no corresponding actual, this may be case
1660 -- of partial parameterization, or else the formal has a
1661 -- default or a box.
1663 if No
(Match
) and then Partial_Parameterization
then
1664 Process_Default
(Formal
);
1666 if Nkind
(I_Node
) = N_Formal_Package_Declaration
then
1667 Check_Overloaded_Formal_Subprogram
(Formal
);
1672 Instantiate_Formal_Subprogram
1673 (Formal
, Match
, Analyzed_Formal
));
1675 -- An instantiation is a freeze point for the actuals,
1676 -- unless this is a rewritten formal package.
1678 if Nkind
(I_Node
) /= N_Formal_Package_Declaration
1679 and then Nkind
(Match
) = N_Identifier
1680 and then Is_Subprogram
(Entity
(Match
))
1682 -- The actual subprogram may rename a routine defined
1683 -- in Standard. Avoid freezing such renamings because
1684 -- subprograms coming from Standard cannot be frozen.
1687 not Renames_Standard_Subprogram
(Entity
(Match
))
1689 -- If the actual subprogram comes from a different
1690 -- unit, it is already frozen, either by a body in
1691 -- that unit or by the end of the declarative part
1692 -- of the unit. This check avoids the freezing of
1693 -- subprograms defined in Standard which are used
1694 -- as generic actuals.
1696 and then In_Same_Code_Unit
(Entity
(Match
), I_Node
)
1697 and then Has_Fully_Defined_Profile
(Entity
(Match
))
1699 -- Mark the subprogram as having a delayed freeze
1700 -- since this may be an out-of-order action.
1702 Set_Has_Delayed_Freeze
(Entity
(Match
));
1703 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
1707 -- If this is a nested generic, preserve default for later
1708 -- instantiations. We do this as well for GNATProve use,
1709 -- so that the list of generic associations is complete.
1711 if No
(Match
) and then Box_Present
(Formal
) then
1713 Subp
: constant Entity_Id
:=
1714 Defining_Unit_Name
(Specification
(Last
(Assoc
)));
1717 Append_To
(Default_Actuals
,
1718 Make_Generic_Association
(Sloc
(I_Node
),
1720 New_Occurrence_Of
(Subp
, Sloc
(I_Node
)),
1721 Explicit_Generic_Actual_Parameter
=>
1722 New_Occurrence_Of
(Subp
, Sloc
(I_Node
))));
1726 when N_Formal_Package_Declaration
=>
1729 (Defining_Identifier
(Formal
),
1730 Defining_Identifier
(Original_Node
(Analyzed_Formal
)));
1733 if Partial_Parameterization
then
1734 Process_Default
(Formal
);
1737 Error_Msg_Sloc
:= Sloc
(Gen_Unit
);
1740 Instantiation_Node
, Defining_Identifier
(Formal
));
1742 ("\in instantiation of & declared#",
1743 Instantiation_Node
, Gen_Unit
);
1745 Abandon_Instantiation
(Instantiation_Node
);
1751 (Instantiate_Formal_Package
1752 (Formal
, Match
, Analyzed_Formal
),
1756 -- For use type and use package appearing in the generic part,
1757 -- we have already copied them, so we can just move them where
1758 -- they belong (we mustn't recopy them since this would mess up
1759 -- the Sloc values).
1761 when N_Use_Package_Clause |
1762 N_Use_Type_Clause
=>
1763 if Nkind
(Original_Node
(I_Node
)) =
1764 N_Formal_Package_Declaration
1766 Append
(New_Copy_Tree
(Formal
), Assoc
);
1769 Append
(Formal
, Assoc
);
1773 raise Program_Error
;
1777 Formal
:= Saved_Formal
;
1778 Next_Non_Pragma
(Analyzed_Formal
);
1781 if Num_Actuals
> Num_Matched
then
1782 Error_Msg_Sloc
:= Sloc
(Gen_Unit
);
1784 if Present
(Selector_Name
(Actual
)) then
1786 ("unmatched actual &", Actual
, Selector_Name
(Actual
));
1788 ("\in instantiation of & declared#", Actual
, Gen_Unit
);
1791 ("unmatched actual in instantiation of & declared#",
1796 elsif Present
(Actuals
) then
1798 ("too many actuals in generic instantiation", Instantiation_Node
);
1801 -- An instantiation freezes all generic actuals. The only exceptions
1802 -- to this are incomplete types and subprograms which are not fully
1803 -- defined at the point of instantiation.
1806 Elmt
: Elmt_Id
:= First_Elmt
(Actuals_To_Freeze
);
1808 while Present
(Elmt
) loop
1809 Freeze_Before
(I_Node
, Node
(Elmt
));
1814 -- If there are default subprograms, normalize the tree by adding
1815 -- explicit associations for them. This is required if the instance
1816 -- appears within a generic.
1818 if not Is_Empty_List
(Default_Actuals
) then
1823 Default
:= First
(Default_Actuals
);
1824 while Present
(Default
) loop
1825 Mark_Rewrite_Insertion
(Default
);
1829 if No
(Actuals
) then
1830 Set_Generic_Associations
(I_Node
, Default_Actuals
);
1832 Append_List_To
(Actuals
, Default_Actuals
);
1837 -- If this is a formal package, normalize the parameter list by adding
1838 -- explicit box associations for the formals that are covered by an
1841 if not Is_Empty_List
(Default_Formals
) then
1842 Append_List
(Default_Formals
, Formals
);
1846 end Analyze_Associations
;
1848 -------------------------------
1849 -- Analyze_Formal_Array_Type --
1850 -------------------------------
1852 procedure Analyze_Formal_Array_Type
1853 (T
: in out Entity_Id
;
1859 -- Treated like a non-generic array declaration, with additional
1864 if Nkind
(Def
) = N_Constrained_Array_Definition
then
1865 DSS
:= First
(Discrete_Subtype_Definitions
(Def
));
1866 while Present
(DSS
) loop
1867 if Nkind_In
(DSS
, N_Subtype_Indication
,
1869 N_Attribute_Reference
)
1871 Error_Msg_N
("only a subtype mark is allowed in a formal", DSS
);
1878 Array_Type_Declaration
(T
, Def
);
1879 Set_Is_Generic_Type
(Base_Type
(T
));
1881 if Ekind
(Component_Type
(T
)) = E_Incomplete_Type
1882 and then No
(Full_View
(Component_Type
(T
)))
1884 Error_Msg_N
("premature usage of incomplete type", Def
);
1886 -- Check that range constraint is not allowed on the component type
1887 -- of a generic formal array type (AARM 12.5.3(3))
1889 elsif Is_Internal
(Component_Type
(T
))
1890 and then Present
(Subtype_Indication
(Component_Definition
(Def
)))
1891 and then Nkind
(Original_Node
1892 (Subtype_Indication
(Component_Definition
(Def
)))) =
1893 N_Subtype_Indication
1896 ("in a formal, a subtype indication can only be "
1897 & "a subtype mark (RM 12.5.3(3))",
1898 Subtype_Indication
(Component_Definition
(Def
)));
1901 end Analyze_Formal_Array_Type
;
1903 ---------------------------------------------
1904 -- Analyze_Formal_Decimal_Fixed_Point_Type --
1905 ---------------------------------------------
1907 -- As for other generic types, we create a valid type representation with
1908 -- legal but arbitrary attributes, whose values are never considered
1909 -- static. For all scalar types we introduce an anonymous base type, with
1910 -- the same attributes. We choose the corresponding integer type to be
1911 -- Standard_Integer.
1912 -- Here and in other similar routines, the Sloc of the generated internal
1913 -- type must be the same as the sloc of the defining identifier of the
1914 -- formal type declaration, to provide proper source navigation.
1916 procedure Analyze_Formal_Decimal_Fixed_Point_Type
1920 Loc
: constant Source_Ptr
:= Sloc
(Def
);
1922 Base
: constant Entity_Id
:=
1924 (E_Decimal_Fixed_Point_Type
,
1926 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
1928 Int_Base
: constant Entity_Id
:= Standard_Integer
;
1929 Delta_Val
: constant Ureal
:= Ureal_1
;
1930 Digs_Val
: constant Uint
:= Uint_6
;
1932 function Make_Dummy_Bound
return Node_Id
;
1933 -- Return a properly typed universal real literal to use as a bound
1935 ----------------------
1936 -- Make_Dummy_Bound --
1937 ----------------------
1939 function Make_Dummy_Bound
return Node_Id
is
1940 Bound
: constant Node_Id
:= Make_Real_Literal
(Loc
, Ureal_1
);
1942 Set_Etype
(Bound
, Universal_Real
);
1944 end Make_Dummy_Bound
;
1946 -- Start of processing for Analyze_Formal_Decimal_Fixed_Point_Type
1951 Set_Etype
(Base
, Base
);
1952 Set_Size_Info
(Base
, Int_Base
);
1953 Set_RM_Size
(Base
, RM_Size
(Int_Base
));
1954 Set_First_Rep_Item
(Base
, First_Rep_Item
(Int_Base
));
1955 Set_Digits_Value
(Base
, Digs_Val
);
1956 Set_Delta_Value
(Base
, Delta_Val
);
1957 Set_Small_Value
(Base
, Delta_Val
);
1958 Set_Scalar_Range
(Base
,
1960 Low_Bound
=> Make_Dummy_Bound
,
1961 High_Bound
=> Make_Dummy_Bound
));
1963 Set_Is_Generic_Type
(Base
);
1964 Set_Parent
(Base
, Parent
(Def
));
1966 Set_Ekind
(T
, E_Decimal_Fixed_Point_Subtype
);
1967 Set_Etype
(T
, Base
);
1968 Set_Size_Info
(T
, Int_Base
);
1969 Set_RM_Size
(T
, RM_Size
(Int_Base
));
1970 Set_First_Rep_Item
(T
, First_Rep_Item
(Int_Base
));
1971 Set_Digits_Value
(T
, Digs_Val
);
1972 Set_Delta_Value
(T
, Delta_Val
);
1973 Set_Small_Value
(T
, Delta_Val
);
1974 Set_Scalar_Range
(T
, Scalar_Range
(Base
));
1975 Set_Is_Constrained
(T
);
1977 Check_Restriction
(No_Fixed_Point
, Def
);
1978 end Analyze_Formal_Decimal_Fixed_Point_Type
;
1980 -------------------------------------------
1981 -- Analyze_Formal_Derived_Interface_Type --
1982 -------------------------------------------
1984 procedure Analyze_Formal_Derived_Interface_Type
1989 Loc
: constant Source_Ptr
:= Sloc
(Def
);
1992 -- Rewrite as a type declaration of a derived type. This ensures that
1993 -- the interface list and primitive operations are properly captured.
1996 Make_Full_Type_Declaration
(Loc
,
1997 Defining_Identifier
=> T
,
1998 Type_Definition
=> Def
));
2000 Set_Is_Generic_Type
(T
);
2001 end Analyze_Formal_Derived_Interface_Type
;
2003 ---------------------------------
2004 -- Analyze_Formal_Derived_Type --
2005 ---------------------------------
2007 procedure Analyze_Formal_Derived_Type
2012 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2013 Unk_Disc
: constant Boolean := Unknown_Discriminants_Present
(N
);
2017 Set_Is_Generic_Type
(T
);
2019 if Private_Present
(Def
) then
2021 Make_Private_Extension_Declaration
(Loc
,
2022 Defining_Identifier
=> T
,
2023 Discriminant_Specifications
=> Discriminant_Specifications
(N
),
2024 Unknown_Discriminants_Present
=> Unk_Disc
,
2025 Subtype_Indication
=> Subtype_Mark
(Def
),
2026 Interface_List
=> Interface_List
(Def
));
2028 Set_Abstract_Present
(New_N
, Abstract_Present
(Def
));
2029 Set_Limited_Present
(New_N
, Limited_Present
(Def
));
2030 Set_Synchronized_Present
(New_N
, Synchronized_Present
(Def
));
2034 Make_Full_Type_Declaration
(Loc
,
2035 Defining_Identifier
=> T
,
2036 Discriminant_Specifications
=>
2037 Discriminant_Specifications
(Parent
(T
)),
2039 Make_Derived_Type_Definition
(Loc
,
2040 Subtype_Indication
=> Subtype_Mark
(Def
)));
2042 Set_Abstract_Present
2043 (Type_Definition
(New_N
), Abstract_Present
(Def
));
2045 (Type_Definition
(New_N
), Limited_Present
(Def
));
2052 if not Is_Composite_Type
(T
) then
2054 ("unknown discriminants not allowed for elementary types", N
);
2056 Set_Has_Unknown_Discriminants
(T
);
2057 Set_Is_Constrained
(T
, False);
2061 -- If the parent type has a known size, so does the formal, which makes
2062 -- legal representation clauses that involve the formal.
2064 Set_Size_Known_At_Compile_Time
2065 (T
, Size_Known_At_Compile_Time
(Entity
(Subtype_Mark
(Def
))));
2066 end Analyze_Formal_Derived_Type
;
2068 ----------------------------------
2069 -- Analyze_Formal_Discrete_Type --
2070 ----------------------------------
2072 -- The operations defined for a discrete types are those of an enumeration
2073 -- type. The size is set to an arbitrary value, for use in analyzing the
2076 procedure Analyze_Formal_Discrete_Type
(T
: Entity_Id
; Def
: Node_Id
) is
2077 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2081 Base
: constant Entity_Id
:=
2083 (E_Floating_Point_Type
, Current_Scope
,
2084 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2088 Set_Ekind
(T
, E_Enumeration_Subtype
);
2089 Set_Etype
(T
, Base
);
2092 Set_Is_Generic_Type
(T
);
2093 Set_Is_Constrained
(T
);
2095 -- For semantic analysis, the bounds of the type must be set to some
2096 -- non-static value. The simplest is to create attribute nodes for those
2097 -- bounds, that refer to the type itself. These bounds are never
2098 -- analyzed but serve as place-holders.
2101 Make_Attribute_Reference
(Loc
,
2102 Attribute_Name
=> Name_First
,
2103 Prefix
=> New_Occurrence_Of
(T
, Loc
));
2107 Make_Attribute_Reference
(Loc
,
2108 Attribute_Name
=> Name_Last
,
2109 Prefix
=> New_Occurrence_Of
(T
, Loc
));
2112 Set_Scalar_Range
(T
,
2117 Set_Ekind
(Base
, E_Enumeration_Type
);
2118 Set_Etype
(Base
, Base
);
2119 Init_Size
(Base
, 8);
2120 Init_Alignment
(Base
);
2121 Set_Is_Generic_Type
(Base
);
2122 Set_Scalar_Range
(Base
, Scalar_Range
(T
));
2123 Set_Parent
(Base
, Parent
(Def
));
2124 end Analyze_Formal_Discrete_Type
;
2126 ----------------------------------
2127 -- Analyze_Formal_Floating_Type --
2128 ---------------------------------
2130 procedure Analyze_Formal_Floating_Type
(T
: Entity_Id
; Def
: Node_Id
) is
2131 Base
: constant Entity_Id
:=
2133 (E_Floating_Point_Type
, Current_Scope
,
2134 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2137 -- The various semantic attributes are taken from the predefined type
2138 -- Float, just so that all of them are initialized. Their values are
2139 -- never used because no constant folding or expansion takes place in
2140 -- the generic itself.
2143 Set_Ekind
(T
, E_Floating_Point_Subtype
);
2144 Set_Etype
(T
, Base
);
2145 Set_Size_Info
(T
, (Standard_Float
));
2146 Set_RM_Size
(T
, RM_Size
(Standard_Float
));
2147 Set_Digits_Value
(T
, Digits_Value
(Standard_Float
));
2148 Set_Scalar_Range
(T
, Scalar_Range
(Standard_Float
));
2149 Set_Is_Constrained
(T
);
2151 Set_Is_Generic_Type
(Base
);
2152 Set_Etype
(Base
, Base
);
2153 Set_Size_Info
(Base
, (Standard_Float
));
2154 Set_RM_Size
(Base
, RM_Size
(Standard_Float
));
2155 Set_Digits_Value
(Base
, Digits_Value
(Standard_Float
));
2156 Set_Scalar_Range
(Base
, Scalar_Range
(Standard_Float
));
2157 Set_Parent
(Base
, Parent
(Def
));
2159 Check_Restriction
(No_Floating_Point
, Def
);
2160 end Analyze_Formal_Floating_Type
;
2162 -----------------------------------
2163 -- Analyze_Formal_Interface_Type;--
2164 -----------------------------------
2166 procedure Analyze_Formal_Interface_Type
2171 Loc
: constant Source_Ptr
:= Sloc
(N
);
2176 Make_Full_Type_Declaration
(Loc
,
2177 Defining_Identifier
=> T
,
2178 Type_Definition
=> Def
);
2182 Set_Is_Generic_Type
(T
);
2183 end Analyze_Formal_Interface_Type
;
2185 ---------------------------------
2186 -- Analyze_Formal_Modular_Type --
2187 ---------------------------------
2189 procedure Analyze_Formal_Modular_Type
(T
: Entity_Id
; Def
: Node_Id
) is
2191 -- Apart from their entity kind, generic modular types are treated like
2192 -- signed integer types, and have the same attributes.
2194 Analyze_Formal_Signed_Integer_Type
(T
, Def
);
2195 Set_Ekind
(T
, E_Modular_Integer_Subtype
);
2196 Set_Ekind
(Etype
(T
), E_Modular_Integer_Type
);
2198 end Analyze_Formal_Modular_Type
;
2200 ---------------------------------------
2201 -- Analyze_Formal_Object_Declaration --
2202 ---------------------------------------
2204 procedure Analyze_Formal_Object_Declaration
(N
: Node_Id
) is
2205 E
: constant Node_Id
:= Default_Expression
(N
);
2206 Id
: constant Node_Id
:= Defining_Identifier
(N
);
2213 -- Determine the mode of the formal object
2215 if Out_Present
(N
) then
2216 K
:= E_Generic_In_Out_Parameter
;
2218 if not In_Present
(N
) then
2219 Error_Msg_N
("formal generic objects cannot have mode OUT", N
);
2223 K
:= E_Generic_In_Parameter
;
2226 if Present
(Subtype_Mark
(N
)) then
2227 Find_Type
(Subtype_Mark
(N
));
2228 T
:= Entity
(Subtype_Mark
(N
));
2230 -- Verify that there is no redundant null exclusion
2232 if Null_Exclusion_Present
(N
) then
2233 if not Is_Access_Type
(T
) then
2235 ("null exclusion can only apply to an access type", N
);
2237 elsif Can_Never_Be_Null
(T
) then
2239 ("`NOT NULL` not allowed (& already excludes null)", N
, T
);
2243 -- Ada 2005 (AI-423): Formal object with an access definition
2246 Check_Access_Definition
(N
);
2247 T
:= Access_Definition
2249 N
=> Access_Definition
(N
));
2252 if Ekind
(T
) = E_Incomplete_Type
then
2254 Error_Node
: Node_Id
;
2257 if Present
(Subtype_Mark
(N
)) then
2258 Error_Node
:= Subtype_Mark
(N
);
2260 Check_Access_Definition
(N
);
2261 Error_Node
:= Access_Definition
(N
);
2264 Error_Msg_N
("premature usage of incomplete type", Error_Node
);
2268 if K
= E_Generic_In_Parameter
then
2270 -- Ada 2005 (AI-287): Limited aggregates allowed in generic formals
2272 if Ada_Version
< Ada_2005
and then Is_Limited_Type
(T
) then
2274 ("generic formal of mode IN must not be of limited type", N
);
2275 Explain_Limited_Type
(T
, N
);
2278 if Is_Abstract_Type
(T
) then
2280 ("generic formal of mode IN must not be of abstract type", N
);
2284 Preanalyze_Spec_Expression
(E
, T
);
2286 if Is_Limited_Type
(T
) and then not OK_For_Limited_Init
(T
, E
) then
2288 ("initialization not allowed for limited types", E
);
2289 Explain_Limited_Type
(T
, E
);
2296 -- Case of generic IN OUT parameter
2299 -- If the formal has an unconstrained type, construct its actual
2300 -- subtype, as is done for subprogram formals. In this fashion, all
2301 -- its uses can refer to specific bounds.
2306 if (Is_Array_Type
(T
) and then not Is_Constrained
(T
))
2307 or else (Ekind
(T
) = E_Record_Type
and then Has_Discriminants
(T
))
2310 Non_Freezing_Ref
: constant Node_Id
:=
2311 New_Occurrence_Of
(Id
, Sloc
(Id
));
2315 -- Make sure the actual subtype doesn't generate bogus freezing
2317 Set_Must_Not_Freeze
(Non_Freezing_Ref
);
2318 Decl
:= Build_Actual_Subtype
(T
, Non_Freezing_Ref
);
2319 Insert_Before_And_Analyze
(N
, Decl
);
2320 Set_Actual_Subtype
(Id
, Defining_Identifier
(Decl
));
2323 Set_Actual_Subtype
(Id
, T
);
2328 ("initialization not allowed for `IN OUT` formals", N
);
2332 if Has_Aspects
(N
) then
2333 Analyze_Aspect_Specifications
(N
, Id
);
2335 end Analyze_Formal_Object_Declaration
;
2337 ----------------------------------------------
2338 -- Analyze_Formal_Ordinary_Fixed_Point_Type --
2339 ----------------------------------------------
2341 procedure Analyze_Formal_Ordinary_Fixed_Point_Type
2345 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2346 Base
: constant Entity_Id
:=
2348 (E_Ordinary_Fixed_Point_Type
, Current_Scope
,
2349 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2352 -- The semantic attributes are set for completeness only, their values
2353 -- will never be used, since all properties of the type are non-static.
2356 Set_Ekind
(T
, E_Ordinary_Fixed_Point_Subtype
);
2357 Set_Etype
(T
, Base
);
2358 Set_Size_Info
(T
, Standard_Integer
);
2359 Set_RM_Size
(T
, RM_Size
(Standard_Integer
));
2360 Set_Small_Value
(T
, Ureal_1
);
2361 Set_Delta_Value
(T
, Ureal_1
);
2362 Set_Scalar_Range
(T
,
2364 Low_Bound
=> Make_Real_Literal
(Loc
, Ureal_1
),
2365 High_Bound
=> Make_Real_Literal
(Loc
, Ureal_1
)));
2366 Set_Is_Constrained
(T
);
2368 Set_Is_Generic_Type
(Base
);
2369 Set_Etype
(Base
, Base
);
2370 Set_Size_Info
(Base
, Standard_Integer
);
2371 Set_RM_Size
(Base
, RM_Size
(Standard_Integer
));
2372 Set_Small_Value
(Base
, Ureal_1
);
2373 Set_Delta_Value
(Base
, Ureal_1
);
2374 Set_Scalar_Range
(Base
, Scalar_Range
(T
));
2375 Set_Parent
(Base
, Parent
(Def
));
2377 Check_Restriction
(No_Fixed_Point
, Def
);
2378 end Analyze_Formal_Ordinary_Fixed_Point_Type
;
2380 ----------------------------------------
2381 -- Analyze_Formal_Package_Declaration --
2382 ----------------------------------------
2384 procedure Analyze_Formal_Package_Declaration
(N
: Node_Id
) is
2385 Loc
: constant Source_Ptr
:= Sloc
(N
);
2386 Pack_Id
: constant Entity_Id
:= Defining_Identifier
(N
);
2388 Gen_Id
: constant Node_Id
:= Name
(N
);
2390 Gen_Unit
: Entity_Id
;
2392 Parent_Installed
: Boolean := False;
2394 Parent_Instance
: Entity_Id
;
2395 Renaming_In_Par
: Entity_Id
;
2396 Associations
: Boolean := True;
2398 Vis_Prims_List
: Elist_Id
:= No_Elist
;
2399 -- List of primitives made temporarily visible in the instantiation
2400 -- to match the visibility of the formal type
2402 function Build_Local_Package
return Node_Id
;
2403 -- The formal package is rewritten so that its parameters are replaced
2404 -- with corresponding declarations. For parameters with bona fide
2405 -- associations these declarations are created by Analyze_Associations
2406 -- as for a regular instantiation. For boxed parameters, we preserve
2407 -- the formal declarations and analyze them, in order to introduce
2408 -- entities of the right kind in the environment of the formal.
2410 -------------------------
2411 -- Build_Local_Package --
2412 -------------------------
2414 function Build_Local_Package
return Node_Id
is
2416 Pack_Decl
: Node_Id
;
2419 -- Within the formal, the name of the generic package is a renaming
2420 -- of the formal (as for a regular instantiation).
2423 Make_Package_Declaration
(Loc
,
2426 (Specification
(Original_Node
(Gen_Decl
)),
2427 Empty
, Instantiating
=> True));
2430 Make_Package_Renaming_Declaration
(Loc
,
2431 Defining_Unit_Name
=>
2432 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
)),
2433 Name
=> New_Occurrence_Of
(Formal
, Loc
));
2435 if Nkind
(Gen_Id
) = N_Identifier
2436 and then Chars
(Gen_Id
) = Chars
(Pack_Id
)
2439 ("& is hidden within declaration of instance", Gen_Id
, Gen_Unit
);
2442 -- If the formal is declared with a box, or with an others choice,
2443 -- create corresponding declarations for all entities in the formal
2444 -- part, so that names with the proper types are available in the
2445 -- specification of the formal package.
2447 -- On the other hand, if there are no associations, then all the
2448 -- formals must have defaults, and this will be checked by the
2449 -- call to Analyze_Associations.
2452 or else Nkind
(First
(Generic_Associations
(N
))) = N_Others_Choice
2455 Formal_Decl
: Node_Id
;
2458 -- TBA : for a formal package, need to recurse ???
2463 (Generic_Formal_Declarations
(Original_Node
(Gen_Decl
)));
2464 while Present
(Formal_Decl
) loop
2466 (Decls
, Copy_Generic_Node
(Formal_Decl
, Empty
, True));
2471 -- If generic associations are present, use Analyze_Associations to
2472 -- create the proper renaming declarations.
2476 Act_Tree
: constant Node_Id
:=
2478 (Original_Node
(Gen_Decl
), Empty
,
2479 Instantiating
=> True);
2482 Generic_Renamings
.Set_Last
(0);
2483 Generic_Renamings_HTable
.Reset
;
2484 Instantiation_Node
:= N
;
2487 Analyze_Associations
2488 (I_Node
=> Original_Node
(N
),
2489 Formals
=> Generic_Formal_Declarations
(Act_Tree
),
2490 F_Copy
=> Generic_Formal_Declarations
(Gen_Decl
));
2492 Vis_Prims_List
:= Check_Hidden_Primitives
(Decls
);
2496 Append
(Renaming
, To
=> Decls
);
2498 -- Add generated declarations ahead of local declarations in
2501 if No
(Visible_Declarations
(Specification
(Pack_Decl
))) then
2502 Set_Visible_Declarations
(Specification
(Pack_Decl
), Decls
);
2505 (First
(Visible_Declarations
(Specification
(Pack_Decl
))),
2510 end Build_Local_Package
;
2512 -- Start of processing for Analyze_Formal_Package_Declaration
2515 Check_Text_IO_Special_Unit
(Gen_Id
);
2518 Check_Generic_Child_Unit
(Gen_Id
, Parent_Installed
);
2519 Gen_Unit
:= Entity
(Gen_Id
);
2521 -- Check for a formal package that is a package renaming
2523 if Present
(Renamed_Object
(Gen_Unit
)) then
2525 -- Indicate that unit is used, before replacing it with renamed
2526 -- entity for use below.
2528 if In_Extended_Main_Source_Unit
(N
) then
2529 Set_Is_Instantiated
(Gen_Unit
);
2530 Generate_Reference
(Gen_Unit
, N
);
2533 Gen_Unit
:= Renamed_Object
(Gen_Unit
);
2536 if Ekind
(Gen_Unit
) /= E_Generic_Package
then
2537 Error_Msg_N
("expect generic package name", Gen_Id
);
2541 elsif Gen_Unit
= Current_Scope
then
2543 ("generic package cannot be used as a formal package of itself",
2548 elsif In_Open_Scopes
(Gen_Unit
) then
2549 if Is_Compilation_Unit
(Gen_Unit
)
2550 and then Is_Child_Unit
(Current_Scope
)
2552 -- Special-case the error when the formal is a parent, and
2553 -- continue analysis to minimize cascaded errors.
2556 ("generic parent cannot be used as formal package "
2557 & "of a child unit", Gen_Id
);
2561 ("generic package cannot be used as a formal package "
2562 & "within itself", Gen_Id
);
2568 -- Check that name of formal package does not hide name of generic,
2569 -- or its leading prefix. This check must be done separately because
2570 -- the name of the generic has already been analyzed.
2573 Gen_Name
: Entity_Id
;
2577 while Nkind
(Gen_Name
) = N_Expanded_Name
loop
2578 Gen_Name
:= Prefix
(Gen_Name
);
2581 if Chars
(Gen_Name
) = Chars
(Pack_Id
) then
2583 ("& is hidden within declaration of formal package",
2589 or else No
(Generic_Associations
(N
))
2590 or else Nkind
(First
(Generic_Associations
(N
))) = N_Others_Choice
2592 Associations
:= False;
2595 -- If there are no generic associations, the generic parameters appear
2596 -- as local entities and are instantiated like them. We copy the generic
2597 -- package declaration as if it were an instantiation, and analyze it
2598 -- like a regular package, except that we treat the formals as
2599 -- additional visible components.
2601 Gen_Decl
:= Unit_Declaration_Node
(Gen_Unit
);
2603 if In_Extended_Main_Source_Unit
(N
) then
2604 Set_Is_Instantiated
(Gen_Unit
);
2605 Generate_Reference
(Gen_Unit
, N
);
2608 Formal
:= New_Copy
(Pack_Id
);
2609 Create_Instantiation_Source
(N
, Gen_Unit
, False, S_Adjustment
);
2612 -- Make local generic without formals. The formals will be replaced
2613 -- with internal declarations.
2615 New_N
:= Build_Local_Package
;
2617 -- If there are errors in the parameter list, Analyze_Associations
2618 -- raises Instantiation_Error. Patch the declaration to prevent
2619 -- further exception propagation.
2622 when Instantiation_Error
=>
2624 Enter_Name
(Formal
);
2625 Set_Ekind
(Formal
, E_Variable
);
2626 Set_Etype
(Formal
, Any_Type
);
2627 Restore_Hidden_Primitives
(Vis_Prims_List
);
2629 if Parent_Installed
then
2637 Set_Defining_Unit_Name
(Specification
(New_N
), Formal
);
2638 Set_Generic_Parent
(Specification
(N
), Gen_Unit
);
2639 Set_Instance_Env
(Gen_Unit
, Formal
);
2640 Set_Is_Generic_Instance
(Formal
);
2642 Enter_Name
(Formal
);
2643 Set_Ekind
(Formal
, E_Package
);
2644 Set_Etype
(Formal
, Standard_Void_Type
);
2645 Set_Inner_Instances
(Formal
, New_Elmt_List
);
2646 Push_Scope
(Formal
);
2648 if Is_Child_Unit
(Gen_Unit
) and then Parent_Installed
then
2650 -- Similarly, we have to make the name of the formal visible in the
2651 -- parent instance, to resolve properly fully qualified names that
2652 -- may appear in the generic unit. The parent instance has been
2653 -- placed on the scope stack ahead of the current scope.
2655 Parent_Instance
:= Scope_Stack
.Table
(Scope_Stack
.Last
- 1).Entity
;
2658 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
));
2659 Set_Ekind
(Renaming_In_Par
, E_Package
);
2660 Set_Etype
(Renaming_In_Par
, Standard_Void_Type
);
2661 Set_Scope
(Renaming_In_Par
, Parent_Instance
);
2662 Set_Parent
(Renaming_In_Par
, Parent
(Formal
));
2663 Set_Renamed_Object
(Renaming_In_Par
, Formal
);
2664 Append_Entity
(Renaming_In_Par
, Parent_Instance
);
2667 Analyze
(Specification
(N
));
2669 -- The formals for which associations are provided are not visible
2670 -- outside of the formal package. The others are still declared by a
2671 -- formal parameter declaration.
2673 -- If there are no associations, the only local entity to hide is the
2674 -- generated package renaming itself.
2680 E
:= First_Entity
(Formal
);
2681 while Present
(E
) loop
2682 if Associations
and then not Is_Generic_Formal
(E
) then
2686 if Ekind
(E
) = E_Package
and then Renamed_Entity
(E
) = Formal
then
2695 End_Package_Scope
(Formal
);
2696 Restore_Hidden_Primitives
(Vis_Prims_List
);
2698 if Parent_Installed
then
2704 -- Inside the generic unit, the formal package is a regular package, but
2705 -- no body is needed for it. Note that after instantiation, the defining
2706 -- unit name we need is in the new tree and not in the original (see
2707 -- Package_Instantiation). A generic formal package is an instance, and
2708 -- can be used as an actual for an inner instance.
2710 Set_Has_Completion
(Formal
, True);
2712 -- Add semantic information to the original defining identifier.
2715 Set_Ekind
(Pack_Id
, E_Package
);
2716 Set_Etype
(Pack_Id
, Standard_Void_Type
);
2717 Set_Scope
(Pack_Id
, Scope
(Formal
));
2718 Set_Has_Completion
(Pack_Id
, True);
2721 if Has_Aspects
(N
) then
2722 Analyze_Aspect_Specifications
(N
, Pack_Id
);
2724 end Analyze_Formal_Package_Declaration
;
2726 ---------------------------------
2727 -- Analyze_Formal_Private_Type --
2728 ---------------------------------
2730 procedure Analyze_Formal_Private_Type
2736 New_Private_Type
(N
, T
, Def
);
2738 -- Set the size to an arbitrary but legal value
2740 Set_Size_Info
(T
, Standard_Integer
);
2741 Set_RM_Size
(T
, RM_Size
(Standard_Integer
));
2742 end Analyze_Formal_Private_Type
;
2744 ------------------------------------
2745 -- Analyze_Formal_Incomplete_Type --
2746 ------------------------------------
2748 procedure Analyze_Formal_Incomplete_Type
2754 Set_Ekind
(T
, E_Incomplete_Type
);
2756 Set_Private_Dependents
(T
, New_Elmt_List
);
2758 if Tagged_Present
(Def
) then
2759 Set_Is_Tagged_Type
(T
);
2760 Make_Class_Wide_Type
(T
);
2761 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
2763 end Analyze_Formal_Incomplete_Type
;
2765 ----------------------------------------
2766 -- Analyze_Formal_Signed_Integer_Type --
2767 ----------------------------------------
2769 procedure Analyze_Formal_Signed_Integer_Type
2773 Base
: constant Entity_Id
:=
2775 (E_Signed_Integer_Type
,
2777 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2782 Set_Ekind
(T
, E_Signed_Integer_Subtype
);
2783 Set_Etype
(T
, Base
);
2784 Set_Size_Info
(T
, Standard_Integer
);
2785 Set_RM_Size
(T
, RM_Size
(Standard_Integer
));
2786 Set_Scalar_Range
(T
, Scalar_Range
(Standard_Integer
));
2787 Set_Is_Constrained
(T
);
2789 Set_Is_Generic_Type
(Base
);
2790 Set_Size_Info
(Base
, Standard_Integer
);
2791 Set_RM_Size
(Base
, RM_Size
(Standard_Integer
));
2792 Set_Etype
(Base
, Base
);
2793 Set_Scalar_Range
(Base
, Scalar_Range
(Standard_Integer
));
2794 Set_Parent
(Base
, Parent
(Def
));
2795 end Analyze_Formal_Signed_Integer_Type
;
2797 -------------------------------------------
2798 -- Analyze_Formal_Subprogram_Declaration --
2799 -------------------------------------------
2801 procedure Analyze_Formal_Subprogram_Declaration
(N
: Node_Id
) is
2802 Spec
: constant Node_Id
:= Specification
(N
);
2803 Def
: constant Node_Id
:= Default_Name
(N
);
2804 Nam
: constant Entity_Id
:= Defining_Unit_Name
(Spec
);
2812 if Nkind
(Nam
) = N_Defining_Program_Unit_Name
then
2813 Error_Msg_N
("name of formal subprogram must be a direct name", Nam
);
2817 Analyze_Subprogram_Declaration
(N
);
2818 Set_Is_Formal_Subprogram
(Nam
);
2819 Set_Has_Completion
(Nam
);
2821 if Nkind
(N
) = N_Formal_Abstract_Subprogram_Declaration
then
2822 Set_Is_Abstract_Subprogram
(Nam
);
2823 Set_Is_Dispatching_Operation
(Nam
);
2826 Ctrl_Type
: constant Entity_Id
:= Find_Dispatching_Type
(Nam
);
2828 if No
(Ctrl_Type
) then
2830 ("abstract formal subprogram must have a controlling type",
2833 elsif Ada_Version
>= Ada_2012
2834 and then Is_Incomplete_Type
(Ctrl_Type
)
2837 ("controlling type of abstract formal subprogram cannot "
2838 & "be incomplete type", N
, Ctrl_Type
);
2841 Check_Controlling_Formals
(Ctrl_Type
, Nam
);
2846 -- Default name is resolved at the point of instantiation
2848 if Box_Present
(N
) then
2851 -- Else default is bound at the point of generic declaration
2853 elsif Present
(Def
) then
2854 if Nkind
(Def
) = N_Operator_Symbol
then
2855 Find_Direct_Name
(Def
);
2857 elsif Nkind
(Def
) /= N_Attribute_Reference
then
2861 -- For an attribute reference, analyze the prefix and verify
2862 -- that it has the proper profile for the subprogram.
2864 Analyze
(Prefix
(Def
));
2865 Valid_Default_Attribute
(Nam
, Def
);
2869 -- Default name may be overloaded, in which case the interpretation
2870 -- with the correct profile must be selected, as for a renaming.
2871 -- If the definition is an indexed component, it must denote a
2872 -- member of an entry family. If it is a selected component, it
2873 -- can be a protected operation.
2875 if Etype
(Def
) = Any_Type
then
2878 elsif Nkind
(Def
) = N_Selected_Component
then
2879 if not Is_Overloadable
(Entity
(Selector_Name
(Def
))) then
2880 Error_Msg_N
("expect valid subprogram name as default", Def
);
2883 elsif Nkind
(Def
) = N_Indexed_Component
then
2884 if Is_Entity_Name
(Prefix
(Def
)) then
2885 if Ekind
(Entity
(Prefix
(Def
))) /= E_Entry_Family
then
2886 Error_Msg_N
("expect valid subprogram name as default", Def
);
2889 elsif Nkind
(Prefix
(Def
)) = N_Selected_Component
then
2890 if Ekind
(Entity
(Selector_Name
(Prefix
(Def
)))) /=
2893 Error_Msg_N
("expect valid subprogram name as default", Def
);
2897 Error_Msg_N
("expect valid subprogram name as default", Def
);
2901 elsif Nkind
(Def
) = N_Character_Literal
then
2903 -- Needs some type checks: subprogram should be parameterless???
2905 Resolve
(Def
, (Etype
(Nam
)));
2907 elsif not Is_Entity_Name
(Def
)
2908 or else not Is_Overloadable
(Entity
(Def
))
2910 Error_Msg_N
("expect valid subprogram name as default", Def
);
2913 elsif not Is_Overloaded
(Def
) then
2914 Subp
:= Entity
(Def
);
2917 Error_Msg_N
("premature usage of formal subprogram", Def
);
2919 elsif not Entity_Matches_Spec
(Subp
, Nam
) then
2920 Error_Msg_N
("no visible entity matches specification", Def
);
2923 -- More than one interpretation, so disambiguate as for a renaming
2928 I1
: Interp_Index
:= 0;
2934 Get_First_Interp
(Def
, I
, It
);
2935 while Present
(It
.Nam
) loop
2936 if Entity_Matches_Spec
(It
.Nam
, Nam
) then
2937 if Subp
/= Any_Id
then
2938 It1
:= Disambiguate
(Def
, I1
, I
, Etype
(Subp
));
2940 if It1
= No_Interp
then
2941 Error_Msg_N
("ambiguous default subprogram", Def
);
2954 Get_Next_Interp
(I
, It
);
2958 if Subp
/= Any_Id
then
2960 -- Subprogram found, generate reference to it
2962 Set_Entity
(Def
, Subp
);
2963 Generate_Reference
(Subp
, Def
);
2966 Error_Msg_N
("premature usage of formal subprogram", Def
);
2968 elsif Ekind
(Subp
) /= E_Operator
then
2969 Check_Mode_Conformant
(Subp
, Nam
);
2973 Error_Msg_N
("no visible subprogram matches specification", N
);
2979 if Has_Aspects
(N
) then
2980 Analyze_Aspect_Specifications
(N
, Nam
);
2983 end Analyze_Formal_Subprogram_Declaration
;
2985 -------------------------------------
2986 -- Analyze_Formal_Type_Declaration --
2987 -------------------------------------
2989 procedure Analyze_Formal_Type_Declaration
(N
: Node_Id
) is
2990 Def
: constant Node_Id
:= Formal_Type_Definition
(N
);
2994 T
:= Defining_Identifier
(N
);
2996 if Present
(Discriminant_Specifications
(N
))
2997 and then Nkind
(Def
) /= N_Formal_Private_Type_Definition
3000 ("discriminants not allowed for this formal type", T
);
3003 -- Enter the new name, and branch to specific routine
3006 when N_Formal_Private_Type_Definition
=>
3007 Analyze_Formal_Private_Type
(N
, T
, Def
);
3009 when N_Formal_Derived_Type_Definition
=>
3010 Analyze_Formal_Derived_Type
(N
, T
, Def
);
3012 when N_Formal_Incomplete_Type_Definition
=>
3013 Analyze_Formal_Incomplete_Type
(T
, Def
);
3015 when N_Formal_Discrete_Type_Definition
=>
3016 Analyze_Formal_Discrete_Type
(T
, Def
);
3018 when N_Formal_Signed_Integer_Type_Definition
=>
3019 Analyze_Formal_Signed_Integer_Type
(T
, Def
);
3021 when N_Formal_Modular_Type_Definition
=>
3022 Analyze_Formal_Modular_Type
(T
, Def
);
3024 when N_Formal_Floating_Point_Definition
=>
3025 Analyze_Formal_Floating_Type
(T
, Def
);
3027 when N_Formal_Ordinary_Fixed_Point_Definition
=>
3028 Analyze_Formal_Ordinary_Fixed_Point_Type
(T
, Def
);
3030 when N_Formal_Decimal_Fixed_Point_Definition
=>
3031 Analyze_Formal_Decimal_Fixed_Point_Type
(T
, Def
);
3033 when N_Array_Type_Definition
=>
3034 Analyze_Formal_Array_Type
(T
, Def
);
3036 when N_Access_To_Object_Definition |
3037 N_Access_Function_Definition |
3038 N_Access_Procedure_Definition
=>
3039 Analyze_Generic_Access_Type
(T
, Def
);
3041 -- Ada 2005: a interface declaration is encoded as an abstract
3042 -- record declaration or a abstract type derivation.
3044 when N_Record_Definition
=>
3045 Analyze_Formal_Interface_Type
(N
, T
, Def
);
3047 when N_Derived_Type_Definition
=>
3048 Analyze_Formal_Derived_Interface_Type
(N
, T
, Def
);
3054 raise Program_Error
;
3058 Set_Is_Generic_Type
(T
);
3060 if Has_Aspects
(N
) then
3061 Analyze_Aspect_Specifications
(N
, T
);
3063 end Analyze_Formal_Type_Declaration
;
3065 ------------------------------------
3066 -- Analyze_Function_Instantiation --
3067 ------------------------------------
3069 procedure Analyze_Function_Instantiation
(N
: Node_Id
) is
3071 Analyze_Subprogram_Instantiation
(N
, E_Function
);
3072 end Analyze_Function_Instantiation
;
3074 ---------------------------------
3075 -- Analyze_Generic_Access_Type --
3076 ---------------------------------
3078 procedure Analyze_Generic_Access_Type
(T
: Entity_Id
; Def
: Node_Id
) is
3082 if Nkind
(Def
) = N_Access_To_Object_Definition
then
3083 Access_Type_Declaration
(T
, Def
);
3085 if Is_Incomplete_Or_Private_Type
(Designated_Type
(T
))
3086 and then No
(Full_View
(Designated_Type
(T
)))
3087 and then not Is_Generic_Type
(Designated_Type
(T
))
3089 Error_Msg_N
("premature usage of incomplete type", Def
);
3091 elsif not Is_Entity_Name
(Subtype_Indication
(Def
)) then
3093 ("only a subtype mark is allowed in a formal", Def
);
3097 Access_Subprogram_Declaration
(T
, Def
);
3099 end Analyze_Generic_Access_Type
;
3101 ---------------------------------
3102 -- Analyze_Generic_Formal_Part --
3103 ---------------------------------
3105 procedure Analyze_Generic_Formal_Part
(N
: Node_Id
) is
3106 Gen_Parm_Decl
: Node_Id
;
3109 -- The generic formals are processed in the scope of the generic unit,
3110 -- where they are immediately visible. The scope is installed by the
3113 Gen_Parm_Decl
:= First
(Generic_Formal_Declarations
(N
));
3114 while Present
(Gen_Parm_Decl
) loop
3115 Analyze
(Gen_Parm_Decl
);
3116 Next
(Gen_Parm_Decl
);
3119 Generate_Reference_To_Generic_Formals
(Current_Scope
);
3120 end Analyze_Generic_Formal_Part
;
3122 ------------------------------------------
3123 -- Analyze_Generic_Package_Declaration --
3124 ------------------------------------------
3126 procedure Analyze_Generic_Package_Declaration
(N
: Node_Id
) is
3127 GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
3128 Loc
: constant Source_Ptr
:= Sloc
(N
);
3129 Decls
: constant List_Id
:=
3130 Visible_Declarations
(Specification
(N
));
3135 Save_Parent
: Node_Id
;
3138 -- The generic package declaration may be subject to pragma Ghost with
3139 -- policy Ignore. Set the mode now to ensure that any nodes generated
3140 -- during analysis and expansion are properly flagged as ignored Ghost.
3143 Check_SPARK_05_Restriction
("generic is not allowed", N
);
3145 -- We introduce a renaming of the enclosing package, to have a usable
3146 -- entity as the prefix of an expanded name for a local entity of the
3147 -- form Par.P.Q, where P is the generic package. This is because a local
3148 -- entity named P may hide it, so that the usual visibility rules in
3149 -- the instance will not resolve properly.
3152 Make_Package_Renaming_Declaration
(Loc
,
3153 Defining_Unit_Name
=>
3154 Make_Defining_Identifier
(Loc
,
3155 Chars
=> New_External_Name
(Chars
(Defining_Entity
(N
)), "GH")),
3157 Make_Identifier
(Loc
, Chars
(Defining_Entity
(N
))));
3159 if Present
(Decls
) then
3160 Decl
:= First
(Decls
);
3161 while Present
(Decl
) and then Nkind
(Decl
) = N_Pragma
loop
3165 if Present
(Decl
) then
3166 Insert_Before
(Decl
, Renaming
);
3168 Append
(Renaming
, Visible_Declarations
(Specification
(N
)));
3172 Set_Visible_Declarations
(Specification
(N
), New_List
(Renaming
));
3175 -- Create copy of generic unit, and save for instantiation. If the unit
3176 -- is a child unit, do not copy the specifications for the parent, which
3177 -- are not part of the generic tree.
3179 Save_Parent
:= Parent_Spec
(N
);
3180 Set_Parent_Spec
(N
, Empty
);
3182 New_N
:= Copy_Generic_Node
(N
, Empty
, Instantiating
=> False);
3183 Set_Parent_Spec
(New_N
, Save_Parent
);
3186 -- Once the contents of the generic copy and the template are swapped,
3187 -- do the same for their respective aspect specifications.
3189 Exchange_Aspects
(N
, New_N
);
3191 -- Collect all contract-related source pragmas found within the template
3192 -- and attach them to the contract of the package spec. This contract is
3193 -- used in the capture of global references within annotations.
3195 Create_Generic_Contract
(N
);
3197 Id
:= Defining_Entity
(N
);
3198 Generate_Definition
(Id
);
3200 -- Expansion is not applied to generic units
3205 Set_Ekind
(Id
, E_Generic_Package
);
3206 Set_Etype
(Id
, Standard_Void_Type
);
3208 -- A generic package declared within a Ghost region is rendered Ghost
3209 -- (SPARK RM 6.9(2)).
3211 if Ghost_Mode
> None
then
3212 Set_Is_Ghost_Entity
(Id
);
3215 -- Analyze aspects now, so that generated pragmas appear in the
3216 -- declarations before building and analyzing the generic copy.
3218 if Has_Aspects
(N
) then
3219 Analyze_Aspect_Specifications
(N
, Id
);
3223 Enter_Generic_Scope
(Id
);
3224 Set_Inner_Instances
(Id
, New_Elmt_List
);
3226 Set_Categorization_From_Pragmas
(N
);
3227 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
3229 -- Link the declaration of the generic homonym in the generic copy to
3230 -- the package it renames, so that it is always resolved properly.
3232 Set_Generic_Homonym
(Id
, Defining_Unit_Name
(Renaming
));
3233 Set_Entity
(Associated_Node
(Name
(Renaming
)), Id
);
3235 -- For a library unit, we have reconstructed the entity for the unit,
3236 -- and must reset it in the library tables.
3238 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
3239 Set_Cunit_Entity
(Current_Sem_Unit
, Id
);
3242 Analyze_Generic_Formal_Part
(N
);
3244 -- After processing the generic formals, analysis proceeds as for a
3245 -- non-generic package.
3247 Analyze
(Specification
(N
));
3249 Validate_Categorization_Dependency
(N
, Id
);
3253 End_Package_Scope
(Id
);
3254 Exit_Generic_Scope
(Id
);
3256 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
3257 Move_Freeze_Nodes
(Id
, N
, Visible_Declarations
(Specification
(N
)));
3258 Move_Freeze_Nodes
(Id
, N
, Private_Declarations
(Specification
(N
)));
3259 Move_Freeze_Nodes
(Id
, N
, Generic_Formal_Declarations
(N
));
3262 Set_Body_Required
(Parent
(N
), Unit_Requires_Body
(Id
));
3263 Validate_RT_RAT_Component
(N
);
3265 -- If this is a spec without a body, check that generic parameters
3268 if not Body_Required
(Parent
(N
)) then
3269 Check_References
(Id
);
3273 -- If there is a specified storage pool in the context, create an
3274 -- aspect on the package declaration, so that it is used in any
3275 -- instance that does not override it.
3277 if Present
(Default_Pool
) then
3283 Make_Aspect_Specification
(Loc
,
3284 Identifier
=> Make_Identifier
(Loc
, Name_Default_Storage_Pool
),
3285 Expression
=> New_Copy
(Default_Pool
));
3287 if No
(Aspect_Specifications
(Specification
(N
))) then
3288 Set_Aspect_Specifications
(Specification
(N
), New_List
(ASN
));
3290 Append
(ASN
, Aspect_Specifications
(Specification
(N
)));
3295 -- Restore the original Ghost mode once analysis and expansion have
3299 end Analyze_Generic_Package_Declaration
;
3301 --------------------------------------------
3302 -- Analyze_Generic_Subprogram_Declaration --
3303 --------------------------------------------
3305 procedure Analyze_Generic_Subprogram_Declaration
(N
: Node_Id
) is
3306 GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
3310 Result_Type
: Entity_Id
;
3311 Save_Parent
: Node_Id
;
3316 -- The generic subprogram declaration may be subject to pragma Ghost
3317 -- with policy Ignore. Set the mode now to ensure that any nodes
3318 -- generated during analysis and expansion are properly flagged as
3322 Check_SPARK_05_Restriction
("generic is not allowed", N
);
3324 -- Create copy of generic unit, and save for instantiation. If the unit
3325 -- is a child unit, do not copy the specifications for the parent, which
3326 -- are not part of the generic tree.
3328 Save_Parent
:= Parent_Spec
(N
);
3329 Set_Parent_Spec
(N
, Empty
);
3331 New_N
:= Copy_Generic_Node
(N
, Empty
, Instantiating
=> False);
3332 Set_Parent_Spec
(New_N
, Save_Parent
);
3335 -- Once the contents of the generic copy and the template are swapped,
3336 -- do the same for their respective aspect specifications.
3338 Exchange_Aspects
(N
, New_N
);
3340 -- Collect all contract-related source pragmas found within the template
3341 -- and attach them to the contract of the subprogram spec. This contract
3342 -- is used in the capture of global references within annotations.
3344 Create_Generic_Contract
(N
);
3346 Spec
:= Specification
(N
);
3347 Id
:= Defining_Entity
(Spec
);
3348 Generate_Definition
(Id
);
3350 if Nkind
(Id
) = N_Defining_Operator_Symbol
then
3352 ("operator symbol not allowed for generic subprogram", Id
);
3358 Set_Scope_Depth_Value
(Id
, Scope_Depth
(Current_Scope
) + 1);
3360 -- Analyze the aspects of the generic copy to ensure that all generated
3361 -- pragmas (if any) perform their semantic effects.
3363 if Has_Aspects
(N
) then
3364 Analyze_Aspect_Specifications
(N
, Id
);
3368 Enter_Generic_Scope
(Id
);
3369 Set_Inner_Instances
(Id
, New_Elmt_List
);
3370 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
3372 Analyze_Generic_Formal_Part
(N
);
3374 Formals
:= Parameter_Specifications
(Spec
);
3376 if Nkind
(Spec
) = N_Function_Specification
then
3377 Set_Ekind
(Id
, E_Generic_Function
);
3379 Set_Ekind
(Id
, E_Generic_Procedure
);
3382 if Present
(Formals
) then
3383 Process_Formals
(Formals
, Spec
);
3386 if Nkind
(Spec
) = N_Function_Specification
then
3387 if Nkind
(Result_Definition
(Spec
)) = N_Access_Definition
then
3388 Result_Type
:= Access_Definition
(Spec
, Result_Definition
(Spec
));
3389 Set_Etype
(Id
, Result_Type
);
3391 -- Check restriction imposed by AI05-073: a generic function
3392 -- cannot return an abstract type or an access to such.
3394 -- This is a binding interpretation should it apply to earlier
3395 -- versions of Ada as well as Ada 2012???
3397 if Is_Abstract_Type
(Designated_Type
(Result_Type
))
3398 and then Ada_Version
>= Ada_2012
3401 ("generic function cannot have an access result "
3402 & "that designates an abstract type", Spec
);
3406 Find_Type
(Result_Definition
(Spec
));
3407 Typ
:= Entity
(Result_Definition
(Spec
));
3409 if Is_Abstract_Type
(Typ
)
3410 and then Ada_Version
>= Ada_2012
3413 ("generic function cannot have abstract result type", Spec
);
3416 -- If a null exclusion is imposed on the result type, then create
3417 -- a null-excluding itype (an access subtype) and use it as the
3418 -- function's Etype.
3420 if Is_Access_Type
(Typ
)
3421 and then Null_Exclusion_Present
(Spec
)
3424 Create_Null_Excluding_Itype
3426 Related_Nod
=> Spec
,
3427 Scope_Id
=> Defining_Unit_Name
(Spec
)));
3429 Set_Etype
(Id
, Typ
);
3434 Set_Etype
(Id
, Standard_Void_Type
);
3437 -- A generic subprogram declared within a Ghost region is rendered Ghost
3438 -- (SPARK RM 6.9(2)).
3440 if Ghost_Mode
> None
then
3441 Set_Is_Ghost_Entity
(Id
);
3444 -- For a library unit, we have reconstructed the entity for the unit,
3445 -- and must reset it in the library tables. We also make sure that
3446 -- Body_Required is set properly in the original compilation unit node.
3448 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
3449 Set_Cunit_Entity
(Current_Sem_Unit
, Id
);
3450 Set_Body_Required
(Parent
(N
), Unit_Requires_Body
(Id
));
3453 Set_Categorization_From_Pragmas
(N
);
3454 Validate_Categorization_Dependency
(N
, Id
);
3456 -- Capture all global references that occur within the profile of the
3457 -- generic subprogram. Aspects are not part of this processing because
3458 -- they must be delayed. If processed now, Save_Global_References will
3459 -- destroy the Associated_Node links and prevent the capture of global
3460 -- references when the contract of the generic subprogram is analyzed.
3462 Save_Global_References
(Original_Node
(N
));
3466 Exit_Generic_Scope
(Id
);
3467 Generate_Reference_To_Formals
(Id
);
3469 List_Inherited_Pre_Post_Aspects
(Id
);
3471 -- Restore the original Ghost mode once analysis and expansion have
3475 end Analyze_Generic_Subprogram_Declaration
;
3477 -----------------------------------
3478 -- Analyze_Package_Instantiation --
3479 -----------------------------------
3481 procedure Analyze_Package_Instantiation
(N
: Node_Id
) is
3482 Loc
: constant Source_Ptr
:= Sloc
(N
);
3483 Gen_Id
: constant Node_Id
:= Name
(N
);
3486 Act_Decl_Name
: Node_Id
;
3487 Act_Decl_Id
: Entity_Id
;
3493 Gen_Unit
: Entity_Id
;
3495 Is_Actual_Pack
: constant Boolean :=
3496 Is_Internal
(Defining_Entity
(N
));
3498 Env_Installed
: Boolean := False;
3499 Parent_Installed
: Boolean := False;
3500 Renaming_List
: List_Id
;
3501 Unit_Renaming
: Node_Id
;
3502 Needs_Body
: Boolean;
3503 Inline_Now
: Boolean := False;
3504 Has_Inline_Always
: Boolean := False;
3506 Save_IPSM
: constant Boolean := Ignore_Pragma_SPARK_Mode
;
3507 -- Save flag Ignore_Pragma_SPARK_Mode for restore on exit
3509 Save_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
3510 Save_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
3511 -- Save the SPARK_Mode-related data for restore on exit
3513 Save_Style_Check
: constant Boolean := Style_Check
;
3514 -- Save style check mode for restore on exit
3516 procedure Delay_Descriptors
(E
: Entity_Id
);
3517 -- Delay generation of subprogram descriptors for given entity
3519 function Might_Inline_Subp
return Boolean;
3520 -- If inlining is active and the generic contains inlined subprograms,
3521 -- we instantiate the body. This may cause superfluous instantiations,
3522 -- but it is simpler than detecting the need for the body at the point
3523 -- of inlining, when the context of the instance is not available.
3525 -----------------------
3526 -- Delay_Descriptors --
3527 -----------------------
3529 procedure Delay_Descriptors
(E
: Entity_Id
) is
3531 if not Delay_Subprogram_Descriptors
(E
) then
3532 Set_Delay_Subprogram_Descriptors
(E
);
3533 Pending_Descriptor
.Append
(E
);
3535 end Delay_Descriptors
;
3537 -----------------------
3538 -- Might_Inline_Subp --
3539 -----------------------
3541 function Might_Inline_Subp
return Boolean is
3545 if not Inline_Processing_Required
then
3549 E
:= First_Entity
(Gen_Unit
);
3550 while Present
(E
) loop
3551 if Is_Subprogram
(E
) and then Is_Inlined
(E
) then
3552 -- Remember if there are any subprograms with Inline_Always
3554 if Has_Pragma_Inline_Always
(E
) then
3555 Has_Inline_Always
:= True;
3566 end Might_Inline_Subp
;
3568 -- Local declarations
3570 Vis_Prims_List
: Elist_Id
:= No_Elist
;
3571 -- List of primitives made temporarily visible in the instantiation
3572 -- to match the visibility of the formal type
3574 -- Start of processing for Analyze_Package_Instantiation
3577 Check_SPARK_05_Restriction
("generic is not allowed", N
);
3579 -- Very first thing: check for Text_IO sp[ecial unit in case we are
3580 -- instantiating one of the children of [[Wide_]Wide_]Text_IO.
3582 Check_Text_IO_Special_Unit
(Name
(N
));
3584 -- Make node global for error reporting
3586 Instantiation_Node
:= N
;
3588 -- Turn off style checking in instances. If the check is enabled on the
3589 -- generic unit, a warning in an instance would just be noise. If not
3590 -- enabled on the generic, then a warning in an instance is just wrong.
3592 Style_Check
:= False;
3594 -- Case of instantiation of a generic package
3596 if Nkind
(N
) = N_Package_Instantiation
then
3597 Act_Decl_Id
:= New_Copy
(Defining_Entity
(N
));
3598 Set_Comes_From_Source
(Act_Decl_Id
, True);
3600 if Nkind
(Defining_Unit_Name
(N
)) = N_Defining_Program_Unit_Name
then
3602 Make_Defining_Program_Unit_Name
(Loc
,
3604 New_Copy_Tree
(Name
(Defining_Unit_Name
(N
))),
3605 Defining_Identifier
=> Act_Decl_Id
);
3607 Act_Decl_Name
:= Act_Decl_Id
;
3610 -- Case of instantiation of a formal package
3613 Act_Decl_Id
:= Defining_Identifier
(N
);
3614 Act_Decl_Name
:= Act_Decl_Id
;
3617 Generate_Definition
(Act_Decl_Id
);
3618 Set_Ekind
(Act_Decl_Id
, E_Package
);
3620 -- Initialize list of incomplete actuals before analysis
3622 Set_Incomplete_Actuals
(Act_Decl_Id
, New_Elmt_List
);
3624 Preanalyze_Actuals
(N
, Act_Decl_Id
);
3627 Env_Installed
:= True;
3629 -- Reset renaming map for formal types. The mapping is established
3630 -- when analyzing the generic associations, but some mappings are
3631 -- inherited from formal packages of parent units, and these are
3632 -- constructed when the parents are installed.
3634 Generic_Renamings
.Set_Last
(0);
3635 Generic_Renamings_HTable
.Reset
;
3637 Check_Generic_Child_Unit
(Gen_Id
, Parent_Installed
);
3638 Gen_Unit
:= Entity
(Gen_Id
);
3640 -- Verify that it is the name of a generic package
3642 -- A visibility glitch: if the instance is a child unit and the generic
3643 -- is the generic unit of a parent instance (i.e. both the parent and
3644 -- the child units are instances of the same package) the name now
3645 -- denotes the renaming within the parent, not the intended generic
3646 -- unit. See if there is a homonym that is the desired generic. The
3647 -- renaming declaration must be visible inside the instance of the
3648 -- child, but not when analyzing the name in the instantiation itself.
3650 if Ekind
(Gen_Unit
) = E_Package
3651 and then Present
(Renamed_Entity
(Gen_Unit
))
3652 and then In_Open_Scopes
(Renamed_Entity
(Gen_Unit
))
3653 and then Is_Generic_Instance
(Renamed_Entity
(Gen_Unit
))
3654 and then Present
(Homonym
(Gen_Unit
))
3656 Gen_Unit
:= Homonym
(Gen_Unit
);
3659 if Etype
(Gen_Unit
) = Any_Type
then
3663 elsif Ekind
(Gen_Unit
) /= E_Generic_Package
then
3665 -- Ada 2005 (AI-50217): Cannot use instance in limited with_clause
3667 if From_Limited_With
(Gen_Unit
) then
3669 ("cannot instantiate a limited withed package", Gen_Id
);
3672 ("& is not the name of a generic package", Gen_Id
, Gen_Unit
);
3679 if In_Extended_Main_Source_Unit
(N
) then
3680 Set_Is_Instantiated
(Gen_Unit
);
3681 Generate_Reference
(Gen_Unit
, N
);
3683 if Present
(Renamed_Object
(Gen_Unit
)) then
3684 Set_Is_Instantiated
(Renamed_Object
(Gen_Unit
));
3685 Generate_Reference
(Renamed_Object
(Gen_Unit
), N
);
3689 if Nkind
(Gen_Id
) = N_Identifier
3690 and then Chars
(Gen_Unit
) = Chars
(Defining_Entity
(N
))
3693 ("& is hidden within declaration of instance", Gen_Id
, Gen_Unit
);
3695 elsif Nkind
(Gen_Id
) = N_Expanded_Name
3696 and then Is_Child_Unit
(Gen_Unit
)
3697 and then Nkind
(Prefix
(Gen_Id
)) = N_Identifier
3698 and then Chars
(Act_Decl_Id
) = Chars
(Prefix
(Gen_Id
))
3701 ("& is hidden within declaration of instance ", Prefix
(Gen_Id
));
3704 Set_Entity
(Gen_Id
, Gen_Unit
);
3706 -- If generic is a renaming, get original generic unit
3708 if Present
(Renamed_Object
(Gen_Unit
))
3709 and then Ekind
(Renamed_Object
(Gen_Unit
)) = E_Generic_Package
3711 Gen_Unit
:= Renamed_Object
(Gen_Unit
);
3714 -- Verify that there are no circular instantiations
3716 if In_Open_Scopes
(Gen_Unit
) then
3717 Error_Msg_NE
("instantiation of & within itself", N
, Gen_Unit
);
3721 elsif Contains_Instance_Of
(Gen_Unit
, Current_Scope
, Gen_Id
) then
3722 Error_Msg_Node_2
:= Current_Scope
;
3724 ("circular Instantiation: & instantiated in &!", N
, Gen_Unit
);
3725 Circularity_Detected
:= True;
3730 -- If the context of the instance is subject to SPARK_Mode "off",
3731 -- set the global flag which signals Analyze_Pragma to ignore all
3732 -- SPARK_Mode pragmas within the instance.
3734 if SPARK_Mode
= Off
then
3735 Ignore_Pragma_SPARK_Mode
:= True;
3738 Gen_Decl
:= Unit_Declaration_Node
(Gen_Unit
);
3739 Gen_Spec
:= Specification
(Gen_Decl
);
3741 -- Initialize renamings map, for error checking, and the list that
3742 -- holds private entities whose views have changed between generic
3743 -- definition and instantiation. If this is the instance created to
3744 -- validate an actual package, the instantiation environment is that
3745 -- of the enclosing instance.
3747 Create_Instantiation_Source
(N
, Gen_Unit
, False, S_Adjustment
);
3749 -- Copy original generic tree, to produce text for instantiation
3753 (Original_Node
(Gen_Decl
), Empty
, Instantiating
=> True);
3755 Act_Spec
:= Specification
(Act_Tree
);
3757 -- If this is the instance created to validate an actual package,
3758 -- only the formals matter, do not examine the package spec itself.
3760 if Is_Actual_Pack
then
3761 Set_Visible_Declarations
(Act_Spec
, New_List
);
3762 Set_Private_Declarations
(Act_Spec
, New_List
);
3766 Analyze_Associations
3768 Formals
=> Generic_Formal_Declarations
(Act_Tree
),
3769 F_Copy
=> Generic_Formal_Declarations
(Gen_Decl
));
3771 Vis_Prims_List
:= Check_Hidden_Primitives
(Renaming_List
);
3773 Set_Instance_Env
(Gen_Unit
, Act_Decl_Id
);
3774 Set_Defining_Unit_Name
(Act_Spec
, Act_Decl_Name
);
3775 Set_Is_Generic_Instance
(Act_Decl_Id
);
3776 Set_Generic_Parent
(Act_Spec
, Gen_Unit
);
3778 -- References to the generic in its own declaration or its body are
3779 -- references to the instance. Add a renaming declaration for the
3780 -- generic unit itself. This declaration, as well as the renaming
3781 -- declarations for the generic formals, must remain private to the
3782 -- unit: the formals, because this is the language semantics, and
3783 -- the unit because its use is an artifact of the implementation.
3786 Make_Package_Renaming_Declaration
(Loc
,
3787 Defining_Unit_Name
=>
3788 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
)),
3789 Name
=> New_Occurrence_Of
(Act_Decl_Id
, Loc
));
3791 Append
(Unit_Renaming
, Renaming_List
);
3793 -- The renaming declarations are the first local declarations of the
3796 if Is_Non_Empty_List
(Visible_Declarations
(Act_Spec
)) then
3798 (First
(Visible_Declarations
(Act_Spec
)), Renaming_List
);
3800 Set_Visible_Declarations
(Act_Spec
, Renaming_List
);
3803 Act_Decl
:= Make_Package_Declaration
(Loc
, Specification
=> Act_Spec
);
3805 -- Propagate the aspect specifications from the package declaration
3806 -- template to the instantiated version of the package declaration.
3808 if Has_Aspects
(Act_Tree
) then
3809 Set_Aspect_Specifications
(Act_Decl
,
3810 New_Copy_List_Tree
(Aspect_Specifications
(Act_Tree
)));
3813 -- The generic may have a generated Default_Storage_Pool aspect,
3814 -- set at the point of generic declaration. If the instance has
3815 -- that aspect, it overrides the one inherited from the generic.
3817 if Has_Aspects
(Gen_Spec
) then
3818 if No
(Aspect_Specifications
(N
)) then
3819 Set_Aspect_Specifications
(N
,
3821 (Aspect_Specifications
(Gen_Spec
))));
3825 ASN1
, ASN2
: Node_Id
;
3828 ASN1
:= First
(Aspect_Specifications
(N
));
3829 while Present
(ASN1
) loop
3830 if Chars
(Identifier
(ASN1
)) = Name_Default_Storage_Pool
3832 -- If generic carries a default storage pool, remove
3833 -- it in favor of the instance one.
3835 ASN2
:= First
(Aspect_Specifications
(Gen_Spec
));
3836 while Present
(ASN2
) loop
3837 if Chars
(Identifier
(ASN2
)) =
3838 Name_Default_Storage_Pool
3851 Prepend_List_To
(Aspect_Specifications
(N
),
3853 (Aspect_Specifications
(Gen_Spec
))));
3858 -- Save the instantiation node, for subsequent instantiation of the
3859 -- body, if there is one and we are generating code for the current
3860 -- unit. Mark unit as having a body (avoids premature error message).
3862 -- We instantiate the body if we are generating code, if we are
3863 -- generating cross-reference information, or if we are building
3864 -- trees for ASIS use or GNATprove use.
3867 Enclosing_Body_Present
: Boolean := False;
3868 -- If the generic unit is not a compilation unit, then a body may
3869 -- be present in its parent even if none is required. We create a
3870 -- tentative pending instantiation for the body, which will be
3871 -- discarded if none is actually present.
3876 if Scope
(Gen_Unit
) /= Standard_Standard
3877 and then not Is_Child_Unit
(Gen_Unit
)
3879 Scop
:= Scope
(Gen_Unit
);
3880 while Present
(Scop
) and then Scop
/= Standard_Standard
loop
3881 if Unit_Requires_Body
(Scop
) then
3882 Enclosing_Body_Present
:= True;
3885 elsif In_Open_Scopes
(Scop
)
3886 and then In_Package_Body
(Scop
)
3888 Enclosing_Body_Present
:= True;
3892 exit when Is_Compilation_Unit
(Scop
);
3893 Scop
:= Scope
(Scop
);
3897 -- If front-end inlining is enabled or there are any subprograms
3898 -- marked with Inline_Always, and this is a unit for which code
3899 -- will be generated, we instantiate the body at once.
3901 -- This is done if the instance is not the main unit, and if the
3902 -- generic is not a child unit of another generic, to avoid scope
3903 -- problems and the reinstallation of parent instances.
3906 and then (not Is_Child_Unit
(Gen_Unit
)
3907 or else not Is_Generic_Unit
(Scope
(Gen_Unit
)))
3908 and then Might_Inline_Subp
3909 and then not Is_Actual_Pack
3911 if not Back_End_Inlining
3912 and then (Front_End_Inlining
or else Has_Inline_Always
)
3913 and then (Is_In_Main_Unit
(N
)
3914 or else In_Main_Context
(Current_Scope
))
3915 and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
3919 -- In configurable_run_time mode we force the inlining of
3920 -- predefined subprograms marked Inline_Always, to minimize
3921 -- the use of the run-time library.
3923 elsif Is_Predefined_File_Name
3924 (Unit_File_Name
(Get_Source_Unit
(Gen_Decl
)))
3925 and then Configurable_Run_Time_Mode
3926 and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
3931 -- If the current scope is itself an instance within a child
3932 -- unit, there will be duplications in the scope stack, and the
3933 -- unstacking mechanism in Inline_Instance_Body will fail.
3934 -- This loses some rare cases of optimization, and might be
3935 -- improved some day, if we can find a proper abstraction for
3936 -- "the complete compilation context" that can be saved and
3939 if Is_Generic_Instance
(Current_Scope
) then
3941 Curr_Unit
: constant Entity_Id
:=
3942 Cunit_Entity
(Current_Sem_Unit
);
3944 if Curr_Unit
/= Current_Scope
3945 and then Is_Child_Unit
(Curr_Unit
)
3947 Inline_Now
:= False;
3954 (Unit_Requires_Body
(Gen_Unit
)
3955 or else Enclosing_Body_Present
3956 or else Present
(Corresponding_Body
(Gen_Decl
)))
3957 and then (Is_In_Main_Unit
(N
) or else Might_Inline_Subp
)
3958 and then not Is_Actual_Pack
3959 and then not Inline_Now
3960 and then (Operating_Mode
= Generate_Code
3962 -- Need comment for this check ???
3964 or else (Operating_Mode
= Check_Semantics
3965 and then (ASIS_Mode
or GNATprove_Mode
)));
3967 -- If front-end inlining is enabled or there are any subprograms
3968 -- marked with Inline_Always, do not instantiate body when within
3969 -- a generic context.
3971 if ((Front_End_Inlining
or else Has_Inline_Always
)
3972 and then not Expander_Active
)
3973 or else Is_Generic_Unit
(Cunit_Entity
(Main_Unit
))
3975 Needs_Body
:= False;
3978 -- If the current context is generic, and the package being
3979 -- instantiated is declared within a formal package, there is no
3980 -- body to instantiate until the enclosing generic is instantiated
3981 -- and there is an actual for the formal package. If the formal
3982 -- package has parameters, we build a regular package instance for
3983 -- it, that precedes the original formal package declaration.
3985 if In_Open_Scopes
(Scope
(Scope
(Gen_Unit
))) then
3987 Decl
: constant Node_Id
:=
3989 (Unit_Declaration_Node
(Scope
(Gen_Unit
)));
3991 if Nkind
(Decl
) = N_Formal_Package_Declaration
3992 or else (Nkind
(Decl
) = N_Package_Declaration
3993 and then Is_List_Member
(Decl
)
3994 and then Present
(Next
(Decl
))
3996 Nkind
(Next
(Decl
)) =
3997 N_Formal_Package_Declaration
)
3999 Needs_Body
:= False;
4005 -- For RCI unit calling stubs, we omit the instance body if the
4006 -- instance is the RCI library unit itself.
4008 -- However there is a special case for nested instances: in this case
4009 -- we do generate the instance body, as it might be required, e.g.
4010 -- because it provides stream attributes for some type used in the
4011 -- profile of a remote subprogram. This is consistent with 12.3(12),
4012 -- which indicates that the instance body occurs at the place of the
4013 -- instantiation, and thus is part of the RCI declaration, which is
4014 -- present on all client partitions (this is E.2.3(18)).
4016 -- Note that AI12-0002 may make it illegal at some point to have
4017 -- stream attributes defined in an RCI unit, in which case this
4018 -- special case will become unnecessary. In the meantime, there
4019 -- is known application code in production that depends on this
4020 -- being possible, so we definitely cannot eliminate the body in
4021 -- the case of nested instances for the time being.
4023 -- When we generate a nested instance body, calling stubs for any
4024 -- relevant subprogram will be be inserted immediately after the
4025 -- subprogram declarations, and will take precedence over the
4026 -- subsequent (original) body. (The stub and original body will be
4027 -- complete homographs, but this is permitted in an instance).
4028 -- (Could we do better and remove the original body???)
4030 if Distribution_Stub_Mode
= Generate_Caller_Stub_Body
4031 and then Comes_From_Source
(N
)
4032 and then Nkind
(Parent
(N
)) = N_Compilation_Unit
4034 Needs_Body
:= False;
4039 -- Here is a defence against a ludicrous number of instantiations
4040 -- caused by a circular set of instantiation attempts.
4042 if Pending_Instantiations
.Last
> Maximum_Instantiations
then
4043 Error_Msg_Uint_1
:= UI_From_Int
(Maximum_Instantiations
);
4044 Error_Msg_N
("too many instantiations, exceeds max of^", N
);
4045 Error_Msg_N
("\limit can be changed using -gnateinn switch", N
);
4046 raise Unrecoverable_Error
;
4049 -- Indicate that the enclosing scopes contain an instantiation,
4050 -- and that cleanup actions should be delayed until after the
4051 -- instance body is expanded.
4053 Check_Forward_Instantiation
(Gen_Decl
);
4054 if Nkind
(N
) = N_Package_Instantiation
then
4056 Enclosing_Master
: Entity_Id
;
4059 -- Loop to search enclosing masters
4061 Enclosing_Master
:= Current_Scope
;
4062 Scope_Loop
: while Enclosing_Master
/= Standard_Standard
loop
4063 if Ekind
(Enclosing_Master
) = E_Package
then
4064 if Is_Compilation_Unit
(Enclosing_Master
) then
4065 if In_Package_Body
(Enclosing_Master
) then
4067 (Body_Entity
(Enclosing_Master
));
4076 Enclosing_Master
:= Scope
(Enclosing_Master
);
4079 elsif Is_Generic_Unit
(Enclosing_Master
)
4080 or else Ekind
(Enclosing_Master
) = E_Void
4082 -- Cleanup actions will eventually be performed on the
4083 -- enclosing subprogram or package instance, if any.
4084 -- Enclosing scope is void in the formal part of a
4085 -- generic subprogram.
4090 if Ekind
(Enclosing_Master
) = E_Entry
4092 Ekind
(Scope
(Enclosing_Master
)) = E_Protected_Type
4094 if not Expander_Active
then
4098 Protected_Body_Subprogram
(Enclosing_Master
);
4102 Set_Delay_Cleanups
(Enclosing_Master
);
4104 while Ekind
(Enclosing_Master
) = E_Block
loop
4105 Enclosing_Master
:= Scope
(Enclosing_Master
);
4108 if Is_Subprogram
(Enclosing_Master
) then
4109 Delay_Descriptors
(Enclosing_Master
);
4111 elsif Is_Task_Type
(Enclosing_Master
) then
4113 TBP
: constant Node_Id
:=
4114 Get_Task_Body_Procedure
4117 if Present
(TBP
) then
4118 Delay_Descriptors
(TBP
);
4119 Set_Delay_Cleanups
(TBP
);
4126 end loop Scope_Loop
;
4129 -- Make entry in table
4131 Pending_Instantiations
.Append
4133 Act_Decl
=> Act_Decl
,
4134 Expander_Status
=> Expander_Active
,
4135 Current_Sem_Unit
=> Current_Sem_Unit
,
4136 Scope_Suppress
=> Scope_Suppress
,
4137 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
4138 Version
=> Ada_Version
,
4139 Version_Pragma
=> Ada_Version_Pragma
,
4140 Warnings
=> Save_Warnings
,
4141 SPARK_Mode
=> SPARK_Mode
,
4142 SPARK_Mode_Pragma
=> SPARK_Mode_Pragma
));
4146 Set_Categorization_From_Pragmas
(Act_Decl
);
4148 if Parent_Installed
then
4152 Set_Instance_Spec
(N
, Act_Decl
);
4154 -- If not a compilation unit, insert the package declaration before
4155 -- the original instantiation node.
4157 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
4158 Mark_Rewrite_Insertion
(Act_Decl
);
4159 Insert_Before
(N
, Act_Decl
);
4161 if Has_Aspects
(N
) then
4162 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
4164 -- The pragma created for a Default_Storage_Pool aspect must
4165 -- appear ahead of the declarations in the instance spec.
4166 -- Analysis has placed it after the instance node, so remove
4167 -- it and reinsert it properly now.
4170 ASN
: constant Node_Id
:= First
(Aspect_Specifications
(N
));
4171 A_Name
: constant Name_Id
:= Chars
(Identifier
(ASN
));
4175 if A_Name
= Name_Default_Storage_Pool
then
4176 if No
(Visible_Declarations
(Act_Spec
)) then
4177 Set_Visible_Declarations
(Act_Spec
, New_List
);
4181 while Present
(Decl
) loop
4182 if Nkind
(Decl
) = N_Pragma
then
4184 Prepend
(Decl
, Visible_Declarations
(Act_Spec
));
4196 -- For an instantiation that is a compilation unit, place
4197 -- declaration on current node so context is complete for analysis
4198 -- (including nested instantiations). If this is the main unit,
4199 -- the declaration eventually replaces the instantiation node.
4200 -- If the instance body is created later, it replaces the
4201 -- instance node, and the declaration is attached to it
4202 -- (see Build_Instance_Compilation_Unit_Nodes).
4205 if Cunit_Entity
(Current_Sem_Unit
) = Defining_Entity
(N
) then
4207 -- The entity for the current unit is the newly created one,
4208 -- and all semantic information is attached to it.
4210 Set_Cunit_Entity
(Current_Sem_Unit
, Act_Decl_Id
);
4212 -- If this is the main unit, replace the main entity as well
4214 if Current_Sem_Unit
= Main_Unit
then
4215 Main_Unit_Entity
:= Act_Decl_Id
;
4219 Set_Unit
(Parent
(N
), Act_Decl
);
4220 Set_Parent_Spec
(Act_Decl
, Parent_Spec
(N
));
4221 Set_Package_Instantiation
(Act_Decl_Id
, N
);
4223 -- Process aspect specifications of the instance node, if any, to
4224 -- take into account categorization pragmas before analyzing the
4227 if Has_Aspects
(N
) then
4228 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
4232 Set_Unit
(Parent
(N
), N
);
4233 Set_Body_Required
(Parent
(N
), False);
4235 -- We never need elaboration checks on instantiations, since by
4236 -- definition, the body instantiation is elaborated at the same
4237 -- time as the spec instantiation.
4239 Set_Suppress_Elaboration_Warnings
(Act_Decl_Id
);
4240 Set_Kill_Elaboration_Checks
(Act_Decl_Id
);
4243 Check_Elab_Instantiation
(N
);
4245 if ABE_Is_Certain
(N
) and then Needs_Body
then
4246 Pending_Instantiations
.Decrement_Last
;
4249 Check_Hidden_Child_Unit
(N
, Gen_Unit
, Act_Decl_Id
);
4251 Set_First_Private_Entity
(Defining_Unit_Name
(Unit_Renaming
),
4252 First_Private_Entity
(Act_Decl_Id
));
4254 -- If the instantiation will receive a body, the unit will be
4255 -- transformed into a package body, and receive its own elaboration
4256 -- entity. Otherwise, the nature of the unit is now a package
4259 if Nkind
(Parent
(N
)) = N_Compilation_Unit
4260 and then not Needs_Body
4262 Rewrite
(N
, Act_Decl
);
4265 if Present
(Corresponding_Body
(Gen_Decl
))
4266 or else Unit_Requires_Body
(Gen_Unit
)
4268 Set_Has_Completion
(Act_Decl_Id
);
4271 Check_Formal_Packages
(Act_Decl_Id
);
4273 Restore_Hidden_Primitives
(Vis_Prims_List
);
4274 Restore_Private_Views
(Act_Decl_Id
);
4276 Inherit_Context
(Gen_Decl
, N
);
4278 if Parent_Installed
then
4283 Env_Installed
:= False;
4286 Validate_Categorization_Dependency
(N
, Act_Decl_Id
);
4288 -- There used to be a check here to prevent instantiations in local
4289 -- contexts if the No_Local_Allocators restriction was active. This
4290 -- check was removed by a binding interpretation in AI-95-00130/07,
4291 -- but we retain the code for documentation purposes.
4293 -- if Ekind (Act_Decl_Id) /= E_Void
4294 -- and then not Is_Library_Level_Entity (Act_Decl_Id)
4296 -- Check_Restriction (No_Local_Allocators, N);
4300 Inline_Instance_Body
(N
, Gen_Unit
, Act_Decl
);
4303 -- The following is a tree patch for ASIS: ASIS needs separate nodes to
4304 -- be used as defining identifiers for a formal package and for the
4305 -- corresponding expanded package.
4307 if Nkind
(N
) = N_Formal_Package_Declaration
then
4308 Act_Decl_Id
:= New_Copy
(Defining_Entity
(N
));
4309 Set_Comes_From_Source
(Act_Decl_Id
, True);
4310 Set_Is_Generic_Instance
(Act_Decl_Id
, False);
4311 Set_Defining_Identifier
(N
, Act_Decl_Id
);
4314 Ignore_Pragma_SPARK_Mode
:= Save_IPSM
;
4315 SPARK_Mode
:= Save_SM
;
4316 SPARK_Mode_Pragma
:= Save_SMP
;
4317 Style_Check
:= Save_Style_Check
;
4319 if SPARK_Mode
= On
then
4320 Dynamic_Elaboration_Checks
:= False;
4323 -- Check that if N is an instantiation of System.Dim_Float_IO or
4324 -- System.Dim_Integer_IO, the formal type has a dimension system.
4326 if Nkind
(N
) = N_Package_Instantiation
4327 and then Is_Dim_IO_Package_Instantiation
(N
)
4330 Assoc
: constant Node_Id
:= First
(Generic_Associations
(N
));
4332 if not Has_Dimension_System
4333 (Etype
(Explicit_Generic_Actual_Parameter
(Assoc
)))
4335 Error_Msg_N
("type with a dimension system expected", Assoc
);
4341 if Has_Aspects
(N
) and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
4342 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
4346 when Instantiation_Error
=>
4347 if Parent_Installed
then
4351 if Env_Installed
then
4355 Ignore_Pragma_SPARK_Mode
:= Save_IPSM
;
4356 SPARK_Mode
:= Save_SM
;
4357 SPARK_Mode_Pragma
:= Save_SMP
;
4358 Style_Check
:= Save_Style_Check
;
4360 if SPARK_Mode
= On
then
4361 Dynamic_Elaboration_Checks
:= False;
4363 end Analyze_Package_Instantiation
;
4365 --------------------------
4366 -- Inline_Instance_Body --
4367 --------------------------
4369 procedure Inline_Instance_Body
4371 Gen_Unit
: Entity_Id
;
4374 Curr_Comp
: constant Node_Id
:= Cunit
(Current_Sem_Unit
);
4375 Curr_Unit
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
4376 Gen_Comp
: constant Entity_Id
:=
4377 Cunit_Entity
(Get_Source_Unit
(Gen_Unit
));
4379 Save_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
4380 Save_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
4381 -- Save all SPARK_Mode-related attributes as removing enclosing scopes
4382 -- to provide a clean environment for analysis of the inlined body will
4383 -- eliminate any previously set SPARK_Mode.
4385 Scope_Stack_Depth
: constant Int
:=
4386 Scope_Stack
.Last
- Scope_Stack
.First
+ 1;
4388 Use_Clauses
: array (1 .. Scope_Stack_Depth
) of Node_Id
;
4389 Instances
: array (1 .. Scope_Stack_Depth
) of Entity_Id
;
4390 Inner_Scopes
: array (1 .. Scope_Stack_Depth
) of Entity_Id
;
4391 Curr_Scope
: Entity_Id
:= Empty
;
4393 Num_Inner
: Int
:= 0;
4394 Num_Scopes
: Int
:= 0;
4395 N_Instances
: Int
:= 0;
4396 Removed
: Boolean := False;
4401 -- Case of generic unit defined in another unit. We must remove the
4402 -- complete context of the current unit to install that of the generic.
4404 if Gen_Comp
/= Cunit_Entity
(Current_Sem_Unit
) then
4406 -- Add some comments for the following two loops ???
4409 while Present
(S
) and then S
/= Standard_Standard
loop
4411 Num_Scopes
:= Num_Scopes
+ 1;
4413 Use_Clauses
(Num_Scopes
) :=
4415 (Scope_Stack
.Last
- Num_Scopes
+ 1).
4417 End_Use_Clauses
(Use_Clauses
(Num_Scopes
));
4419 exit when Scope_Stack
.Last
- Num_Scopes
+ 1 = Scope_Stack
.First
4420 or else Scope_Stack
.Table
4421 (Scope_Stack
.Last
- Num_Scopes
).Entity
= Scope
(S
);
4424 exit when Is_Generic_Instance
(S
)
4425 and then (In_Package_Body
(S
)
4426 or else Ekind
(S
) = E_Procedure
4427 or else Ekind
(S
) = E_Function
);
4431 Vis
:= Is_Immediately_Visible
(Gen_Comp
);
4433 -- Find and save all enclosing instances
4438 and then S
/= Standard_Standard
4440 if Is_Generic_Instance
(S
) then
4441 N_Instances
:= N_Instances
+ 1;
4442 Instances
(N_Instances
) := S
;
4444 exit when In_Package_Body
(S
);
4450 -- Remove context of current compilation unit, unless we are within a
4451 -- nested package instantiation, in which case the context has been
4452 -- removed previously.
4454 -- If current scope is the body of a child unit, remove context of
4455 -- spec as well. If an enclosing scope is an instance body, the
4456 -- context has already been removed, but the entities in the body
4457 -- must be made invisible as well.
4460 while Present
(S
) and then S
/= Standard_Standard
loop
4461 if Is_Generic_Instance
(S
)
4462 and then (In_Package_Body
(S
)
4463 or else Ekind_In
(S
, E_Procedure
, E_Function
))
4465 -- We still have to remove the entities of the enclosing
4466 -- instance from direct visibility.
4471 E
:= First_Entity
(S
);
4472 while Present
(E
) loop
4473 Set_Is_Immediately_Visible
(E
, False);
4482 or else (Ekind
(Curr_Unit
) = E_Package_Body
4483 and then S
= Spec_Entity
(Curr_Unit
))
4484 or else (Ekind
(Curr_Unit
) = E_Subprogram_Body
4485 and then S
= Corresponding_Spec
4486 (Unit_Declaration_Node
(Curr_Unit
)))
4490 -- Remove entities in current scopes from visibility, so that
4491 -- instance body is compiled in a clean environment.
4493 List
:= Save_Scope_Stack
(Handle_Use
=> False);
4495 if Is_Child_Unit
(S
) then
4497 -- Remove child unit from stack, as well as inner scopes.
4498 -- Removing the context of a child unit removes parent units
4501 while Current_Scope
/= S
loop
4502 Num_Inner
:= Num_Inner
+ 1;
4503 Inner_Scopes
(Num_Inner
) := Current_Scope
;
4508 Remove_Context
(Curr_Comp
);
4512 Remove_Context
(Curr_Comp
);
4515 if Ekind
(Curr_Unit
) = E_Package_Body
then
4516 Remove_Context
(Library_Unit
(Curr_Comp
));
4523 pragma Assert
(Num_Inner
< Num_Scopes
);
4525 -- The inlined package body must be analyzed with the SPARK_Mode of
4526 -- the enclosing context, otherwise the body may cause bogus errors
4527 -- if a configuration SPARK_Mode pragma in in effect.
4529 Push_Scope
(Standard_Standard
);
4530 Scope_Stack
.Table
(Scope_Stack
.Last
).Is_Active_Stack_Base
:= True;
4531 Instantiate_Package_Body
4534 Act_Decl
=> Act_Decl
,
4535 Expander_Status
=> Expander_Active
,
4536 Current_Sem_Unit
=> Current_Sem_Unit
,
4537 Scope_Suppress
=> Scope_Suppress
,
4538 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
4539 Version
=> Ada_Version
,
4540 Version_Pragma
=> Ada_Version_Pragma
,
4541 Warnings
=> Save_Warnings
,
4542 SPARK_Mode
=> Save_SM
,
4543 SPARK_Mode_Pragma
=> Save_SMP
)),
4544 Inlined_Body
=> True);
4550 Set_Is_Immediately_Visible
(Gen_Comp
, Vis
);
4552 -- Reset Generic_Instance flag so that use clauses can be installed
4553 -- in the proper order. (See Use_One_Package for effect of enclosing
4554 -- instances on processing of use clauses).
4556 for J
in 1 .. N_Instances
loop
4557 Set_Is_Generic_Instance
(Instances
(J
), False);
4561 Install_Context
(Curr_Comp
);
4563 if Present
(Curr_Scope
)
4564 and then Is_Child_Unit
(Curr_Scope
)
4566 Push_Scope
(Curr_Scope
);
4567 Set_Is_Immediately_Visible
(Curr_Scope
);
4569 -- Finally, restore inner scopes as well
4571 for J
in reverse 1 .. Num_Inner
loop
4572 Push_Scope
(Inner_Scopes
(J
));
4576 Restore_Scope_Stack
(List
, Handle_Use
=> False);
4578 if Present
(Curr_Scope
)
4580 (In_Private_Part
(Curr_Scope
)
4581 or else In_Package_Body
(Curr_Scope
))
4583 -- Install private declaration of ancestor units, which are
4584 -- currently available. Restore_Scope_Stack and Install_Context
4585 -- only install the visible part of parents.
4590 Par
:= Scope
(Curr_Scope
);
4591 while (Present
(Par
)) and then Par
/= Standard_Standard
loop
4592 Install_Private_Declarations
(Par
);
4599 -- Restore use clauses. For a child unit, use clauses in the parents
4600 -- are restored when installing the context, so only those in inner
4601 -- scopes (and those local to the child unit itself) need to be
4602 -- installed explicitly.
4604 if Is_Child_Unit
(Curr_Unit
) and then Removed
then
4605 for J
in reverse 1 .. Num_Inner
+ 1 loop
4606 Scope_Stack
.Table
(Scope_Stack
.Last
- J
+ 1).First_Use_Clause
:=
4608 Install_Use_Clauses
(Use_Clauses
(J
));
4612 for J
in reverse 1 .. Num_Scopes
loop
4613 Scope_Stack
.Table
(Scope_Stack
.Last
- J
+ 1).First_Use_Clause
:=
4615 Install_Use_Clauses
(Use_Clauses
(J
));
4619 -- Restore status of instances. If one of them is a body, make its
4620 -- local entities visible again.
4627 for J
in 1 .. N_Instances
loop
4628 Inst
:= Instances
(J
);
4629 Set_Is_Generic_Instance
(Inst
, True);
4631 if In_Package_Body
(Inst
)
4632 or else Ekind_In
(S
, E_Procedure
, E_Function
)
4634 E
:= First_Entity
(Instances
(J
));
4635 while Present
(E
) loop
4636 Set_Is_Immediately_Visible
(E
);
4643 -- If generic unit is in current unit, current context is correct. Note
4644 -- that the context is guaranteed to carry the correct SPARK_Mode as no
4645 -- enclosing scopes were removed.
4648 Instantiate_Package_Body
4651 Act_Decl
=> Act_Decl
,
4652 Expander_Status
=> Expander_Active
,
4653 Current_Sem_Unit
=> Current_Sem_Unit
,
4654 Scope_Suppress
=> Scope_Suppress
,
4655 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
4656 Version
=> Ada_Version
,
4657 Version_Pragma
=> Ada_Version_Pragma
,
4658 Warnings
=> Save_Warnings
,
4659 SPARK_Mode
=> SPARK_Mode
,
4660 SPARK_Mode_Pragma
=> SPARK_Mode_Pragma
)),
4661 Inlined_Body
=> True);
4663 end Inline_Instance_Body
;
4665 -------------------------------------
4666 -- Analyze_Procedure_Instantiation --
4667 -------------------------------------
4669 procedure Analyze_Procedure_Instantiation
(N
: Node_Id
) is
4671 Analyze_Subprogram_Instantiation
(N
, E_Procedure
);
4672 end Analyze_Procedure_Instantiation
;
4674 -----------------------------------
4675 -- Need_Subprogram_Instance_Body --
4676 -----------------------------------
4678 function Need_Subprogram_Instance_Body
4680 Subp
: Entity_Id
) return Boolean
4683 -- Must be inlined (or inlined renaming)
4685 if (Is_In_Main_Unit
(N
)
4686 or else Is_Inlined
(Subp
)
4687 or else Is_Inlined
(Alias
(Subp
)))
4689 -- Must be generating code or analyzing code in ASIS/GNATprove mode
4691 and then (Operating_Mode
= Generate_Code
4692 or else (Operating_Mode
= Check_Semantics
4693 and then (ASIS_Mode
or GNATprove_Mode
)))
4695 -- The body is needed when generating code (full expansion), in ASIS
4696 -- mode for other tools, and in GNATprove mode (special expansion) for
4697 -- formal verification of the body itself.
4699 and then (Expander_Active
or ASIS_Mode
or GNATprove_Mode
)
4701 -- No point in inlining if ABE is inevitable
4703 and then not ABE_Is_Certain
(N
)
4705 -- Or if subprogram is eliminated
4707 and then not Is_Eliminated
(Subp
)
4709 Pending_Instantiations
.Append
4711 Act_Decl
=> Unit_Declaration_Node
(Subp
),
4712 Expander_Status
=> Expander_Active
,
4713 Current_Sem_Unit
=> Current_Sem_Unit
,
4714 Scope_Suppress
=> Scope_Suppress
,
4715 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
4716 Version
=> Ada_Version
,
4717 Version_Pragma
=> Ada_Version_Pragma
,
4718 Warnings
=> Save_Warnings
,
4719 SPARK_Mode
=> SPARK_Mode
,
4720 SPARK_Mode_Pragma
=> SPARK_Mode_Pragma
));
4723 -- Here if not inlined, or we ignore the inlining
4728 end Need_Subprogram_Instance_Body
;
4730 --------------------------------------
4731 -- Analyze_Subprogram_Instantiation --
4732 --------------------------------------
4734 procedure Analyze_Subprogram_Instantiation
4738 Loc
: constant Source_Ptr
:= Sloc
(N
);
4739 Gen_Id
: constant Node_Id
:= Name
(N
);
4741 Anon_Id
: constant Entity_Id
:=
4742 Make_Defining_Identifier
(Sloc
(Defining_Entity
(N
)),
4743 Chars
=> New_External_Name
4744 (Chars
(Defining_Entity
(N
)), 'R'));
4746 Act_Decl_Id
: Entity_Id
;
4751 Env_Installed
: Boolean := False;
4752 Gen_Unit
: Entity_Id
;
4754 Pack_Id
: Entity_Id
;
4755 Parent_Installed
: Boolean := False;
4757 Renaming_List
: List_Id
;
4758 -- The list of declarations that link formals and actuals of the
4759 -- instance. These are subtype declarations for formal types, and
4760 -- renaming declarations for other formals. The subprogram declaration
4761 -- for the instance is then appended to the list, and the last item on
4762 -- the list is the renaming declaration for the instance.
4764 procedure Analyze_Instance_And_Renamings
;
4765 -- The instance must be analyzed in a context that includes the mappings
4766 -- of generic parameters into actuals. We create a package declaration
4767 -- for this purpose, and a subprogram with an internal name within the
4768 -- package. The subprogram instance is simply an alias for the internal
4769 -- subprogram, declared in the current scope.
4771 procedure Build_Subprogram_Renaming
;
4772 -- If the subprogram is recursive, there are occurrences of the name of
4773 -- the generic within the body, which must resolve to the current
4774 -- instance. We add a renaming declaration after the declaration, which
4775 -- is available in the instance body, as well as in the analysis of
4776 -- aspects that appear in the generic. This renaming declaration is
4777 -- inserted after the instance declaration which it renames.
4779 procedure Instantiate_Subprogram_Contract
(Templ
: Node_Id
);
4780 -- Instantiate all source pragmas found in the contract of the generic
4781 -- subprogram declaration template denoted by Templ. The instantiated
4782 -- pragmas are added to list Renaming_List.
4784 ------------------------------------
4785 -- Analyze_Instance_And_Renamings --
4786 ------------------------------------
4788 procedure Analyze_Instance_And_Renamings
is
4789 Def_Ent
: constant Entity_Id
:= Defining_Entity
(N
);
4790 Pack_Decl
: Node_Id
;
4793 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4795 -- For the case of a compilation unit, the container package has
4796 -- the same name as the instantiation, to insure that the binder
4797 -- calls the elaboration procedure with the right name. Copy the
4798 -- entity of the instance, which may have compilation level flags
4799 -- (e.g. Is_Child_Unit) set.
4801 Pack_Id
:= New_Copy
(Def_Ent
);
4804 -- Otherwise we use the name of the instantiation concatenated
4805 -- with its source position to ensure uniqueness if there are
4806 -- several instantiations with the same name.
4809 Make_Defining_Identifier
(Loc
,
4810 Chars
=> New_External_Name
4811 (Related_Id
=> Chars
(Def_Ent
),
4813 Suffix_Index
=> Source_Offset
(Sloc
(Def_Ent
))));
4817 Make_Package_Declaration
(Loc
,
4818 Specification
=> Make_Package_Specification
(Loc
,
4819 Defining_Unit_Name
=> Pack_Id
,
4820 Visible_Declarations
=> Renaming_List
,
4821 End_Label
=> Empty
));
4823 Set_Instance_Spec
(N
, Pack_Decl
);
4824 Set_Is_Generic_Instance
(Pack_Id
);
4825 Set_Debug_Info_Needed
(Pack_Id
);
4827 -- Case of not a compilation unit
4829 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
4830 Mark_Rewrite_Insertion
(Pack_Decl
);
4831 Insert_Before
(N
, Pack_Decl
);
4832 Set_Has_Completion
(Pack_Id
);
4834 -- Case of an instantiation that is a compilation unit
4836 -- Place declaration on current node so context is complete for
4837 -- analysis (including nested instantiations), and for use in a
4838 -- context_clause (see Analyze_With_Clause).
4841 Set_Unit
(Parent
(N
), Pack_Decl
);
4842 Set_Parent_Spec
(Pack_Decl
, Parent_Spec
(N
));
4845 Analyze
(Pack_Decl
);
4846 Check_Formal_Packages
(Pack_Id
);
4847 Set_Is_Generic_Instance
(Pack_Id
, False);
4849 -- Why do we clear Is_Generic_Instance??? We set it 20 lines
4852 -- Body of the enclosing package is supplied when instantiating the
4853 -- subprogram body, after semantic analysis is completed.
4855 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4857 -- Remove package itself from visibility, so it does not
4858 -- conflict with subprogram.
4860 Set_Name_Entity_Id
(Chars
(Pack_Id
), Homonym
(Pack_Id
));
4862 -- Set name and scope of internal subprogram so that the proper
4863 -- external name will be generated. The proper scope is the scope
4864 -- of the wrapper package. We need to generate debugging info for
4865 -- the internal subprogram, so set flag accordingly.
4867 Set_Chars
(Anon_Id
, Chars
(Defining_Entity
(N
)));
4868 Set_Scope
(Anon_Id
, Scope
(Pack_Id
));
4870 -- Mark wrapper package as referenced, to avoid spurious warnings
4871 -- if the instantiation appears in various with_ clauses of
4872 -- subunits of the main unit.
4874 Set_Referenced
(Pack_Id
);
4877 Set_Is_Generic_Instance
(Anon_Id
);
4878 Set_Debug_Info_Needed
(Anon_Id
);
4879 Act_Decl_Id
:= New_Copy
(Anon_Id
);
4881 Set_Parent
(Act_Decl_Id
, Parent
(Anon_Id
));
4882 Set_Chars
(Act_Decl_Id
, Chars
(Defining_Entity
(N
)));
4883 Set_Sloc
(Act_Decl_Id
, Sloc
(Defining_Entity
(N
)));
4885 -- Subprogram instance comes from source only if generic does
4887 Set_Comes_From_Source
(Act_Decl_Id
, Comes_From_Source
(Gen_Unit
));
4889 -- The signature may involve types that are not frozen yet, but the
4890 -- subprogram will be frozen at the point the wrapper package is
4891 -- frozen, so it does not need its own freeze node. In fact, if one
4892 -- is created, it might conflict with the freezing actions from the
4895 Set_Has_Delayed_Freeze
(Anon_Id
, False);
4897 -- If the instance is a child unit, mark the Id accordingly. Mark
4898 -- the anonymous entity as well, which is the real subprogram and
4899 -- which is used when the instance appears in a context clause.
4900 -- Similarly, propagate the Is_Eliminated flag to handle properly
4901 -- nested eliminated subprograms.
4903 Set_Is_Child_Unit
(Act_Decl_Id
, Is_Child_Unit
(Defining_Entity
(N
)));
4904 Set_Is_Child_Unit
(Anon_Id
, Is_Child_Unit
(Defining_Entity
(N
)));
4905 New_Overloaded_Entity
(Act_Decl_Id
);
4906 Check_Eliminated
(Act_Decl_Id
);
4907 Set_Is_Eliminated
(Anon_Id
, Is_Eliminated
(Act_Decl_Id
));
4909 -- In compilation unit case, kill elaboration checks on the
4910 -- instantiation, since they are never needed -- the body is
4911 -- instantiated at the same point as the spec.
4913 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4914 Set_Suppress_Elaboration_Warnings
(Act_Decl_Id
);
4915 Set_Kill_Elaboration_Checks
(Act_Decl_Id
);
4916 Set_Is_Compilation_Unit
(Anon_Id
);
4918 Set_Cunit_Entity
(Current_Sem_Unit
, Pack_Id
);
4921 -- The instance is not a freezing point for the new subprogram
4923 Set_Is_Frozen
(Act_Decl_Id
, False);
4925 if Nkind
(Defining_Entity
(N
)) = N_Defining_Operator_Symbol
then
4926 Valid_Operator_Definition
(Act_Decl_Id
);
4929 Set_Alias
(Act_Decl_Id
, Anon_Id
);
4930 Set_Parent
(Act_Decl_Id
, Parent
(Anon_Id
));
4931 Set_Has_Completion
(Act_Decl_Id
);
4932 Set_Related_Instance
(Pack_Id
, Act_Decl_Id
);
4934 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4935 Set_Body_Required
(Parent
(N
), False);
4937 end Analyze_Instance_And_Renamings
;
4939 -------------------------------
4940 -- Build_Subprogram_Renaming --
4941 -------------------------------
4943 procedure Build_Subprogram_Renaming
is
4944 Renaming_Decl
: Node_Id
;
4945 Unit_Renaming
: Node_Id
;
4949 Make_Subprogram_Renaming_Declaration
(Loc
,
4952 (Specification
(Original_Node
(Gen_Decl
)),
4954 Instantiating
=> True),
4955 Name
=> New_Occurrence_Of
(Anon_Id
, Loc
));
4957 -- The generic may be a a child unit. The renaming needs an
4958 -- identifier with the proper name.
4960 Set_Defining_Unit_Name
(Specification
(Unit_Renaming
),
4961 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
)));
4963 -- If there is a formal subprogram with the same name as the unit
4964 -- itself, do not add this renaming declaration, to prevent
4965 -- ambiguities when there is a call with that name in the body.
4966 -- This is a partial and ugly fix for one ACATS test. ???
4968 Renaming_Decl
:= First
(Renaming_List
);
4969 while Present
(Renaming_Decl
) loop
4970 if Nkind
(Renaming_Decl
) = N_Subprogram_Renaming_Declaration
4972 Chars
(Defining_Entity
(Renaming_Decl
)) = Chars
(Gen_Unit
)
4977 Next
(Renaming_Decl
);
4980 if No
(Renaming_Decl
) then
4981 Append
(Unit_Renaming
, Renaming_List
);
4983 end Build_Subprogram_Renaming
;
4985 -------------------------------------
4986 -- Instantiate_Subprogram_Contract --
4987 -------------------------------------
4989 procedure Instantiate_Subprogram_Contract
(Templ
: Node_Id
) is
4990 procedure Instantiate_Pragmas
(First_Prag
: Node_Id
);
4991 -- Instantiate all contract-related source pragmas found in the list
4992 -- starting with pragma First_Prag. Each instantiated pragma is added
4993 -- to list Renaming_List.
4995 -------------------------
4996 -- Instantiate_Pragmas --
4997 -------------------------
4999 procedure Instantiate_Pragmas
(First_Prag
: Node_Id
) is
5000 Inst_Prag
: Node_Id
;
5005 while Present
(Prag
) loop
5006 if Is_Generic_Contract_Pragma
(Prag
) then
5008 Copy_Generic_Node
(Prag
, Empty
, Instantiating
=> True);
5010 Set_Analyzed
(Inst_Prag
, False);
5011 Append_To
(Renaming_List
, Inst_Prag
);
5014 Prag
:= Next_Pragma
(Prag
);
5016 end Instantiate_Pragmas
;
5020 Items
: constant Node_Id
:= Contract
(Defining_Entity
(Templ
));
5022 -- Start of processing for Instantiate_Subprogram_Contract
5025 if Present
(Items
) then
5026 Instantiate_Pragmas
(Pre_Post_Conditions
(Items
));
5027 Instantiate_Pragmas
(Contract_Test_Cases
(Items
));
5028 Instantiate_Pragmas
(Classifications
(Items
));
5030 end Instantiate_Subprogram_Contract
;
5034 Save_IPSM
: constant Boolean := Ignore_Pragma_SPARK_Mode
;
5035 -- Save flag Ignore_Pragma_SPARK_Mode for restore on exit
5037 Save_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
5038 Save_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
5039 -- Save the SPARK_Mode-related data for restore on exit
5041 Vis_Prims_List
: Elist_Id
:= No_Elist
;
5042 -- List of primitives made temporarily visible in the instantiation
5043 -- to match the visibility of the formal type
5045 -- Start of processing for Analyze_Subprogram_Instantiation
5048 Check_SPARK_05_Restriction
("generic is not allowed", N
);
5050 -- Very first thing: check for special Text_IO unit in case we are
5051 -- instantiating one of the children of [[Wide_]Wide_]Text_IO. Of course
5052 -- such an instantiation is bogus (these are packages, not subprograms),
5053 -- but we get a better error message if we do this.
5055 Check_Text_IO_Special_Unit
(Gen_Id
);
5057 -- Make node global for error reporting
5059 Instantiation_Node
:= N
;
5061 -- For package instantiations we turn off style checks, because they
5062 -- will have been emitted in the generic. For subprogram instantiations
5063 -- we want to apply at least the check on overriding indicators so we
5064 -- do not modify the style check status.
5066 -- The renaming declarations for the actuals do not come from source and
5067 -- will not generate spurious warnings.
5069 Preanalyze_Actuals
(N
);
5072 Env_Installed
:= True;
5073 Check_Generic_Child_Unit
(Gen_Id
, Parent_Installed
);
5074 Gen_Unit
:= Entity
(Gen_Id
);
5076 Generate_Reference
(Gen_Unit
, Gen_Id
);
5078 if Nkind
(Gen_Id
) = N_Identifier
5079 and then Chars
(Gen_Unit
) = Chars
(Defining_Entity
(N
))
5082 ("& is hidden within declaration of instance", Gen_Id
, Gen_Unit
);
5085 if Etype
(Gen_Unit
) = Any_Type
then
5090 -- Verify that it is a generic subprogram of the right kind, and that
5091 -- it does not lead to a circular instantiation.
5093 if K
= E_Procedure
and then Ekind
(Gen_Unit
) /= E_Generic_Procedure
then
5095 ("& is not the name of a generic procedure", Gen_Id
, Gen_Unit
);
5097 elsif K
= E_Function
and then Ekind
(Gen_Unit
) /= E_Generic_Function
then
5099 ("& is not the name of a generic function", Gen_Id
, Gen_Unit
);
5101 elsif In_Open_Scopes
(Gen_Unit
) then
5102 Error_Msg_NE
("instantiation of & within itself", N
, Gen_Unit
);
5105 -- If the context of the instance is subject to SPARK_Mode "off",
5106 -- set the global flag which signals Analyze_Pragma to ignore all
5107 -- SPARK_Mode pragmas within the instance.
5109 if SPARK_Mode
= Off
then
5110 Ignore_Pragma_SPARK_Mode
:= True;
5113 Set_Entity
(Gen_Id
, Gen_Unit
);
5114 Set_Is_Instantiated
(Gen_Unit
);
5116 if In_Extended_Main_Source_Unit
(N
) then
5117 Generate_Reference
(Gen_Unit
, N
);
5120 -- If renaming, get original unit
5122 if Present
(Renamed_Object
(Gen_Unit
))
5123 and then Ekind_In
(Renamed_Object
(Gen_Unit
), E_Generic_Procedure
,
5126 Gen_Unit
:= Renamed_Object
(Gen_Unit
);
5127 Set_Is_Instantiated
(Gen_Unit
);
5128 Generate_Reference
(Gen_Unit
, N
);
5131 if Contains_Instance_Of
(Gen_Unit
, Current_Scope
, Gen_Id
) then
5132 Error_Msg_Node_2
:= Current_Scope
;
5134 ("circular Instantiation: & instantiated in &!", N
, Gen_Unit
);
5135 Circularity_Detected
:= True;
5136 Restore_Hidden_Primitives
(Vis_Prims_List
);
5140 Gen_Decl
:= Unit_Declaration_Node
(Gen_Unit
);
5142 -- Initialize renamings map, for error checking
5144 Generic_Renamings
.Set_Last
(0);
5145 Generic_Renamings_HTable
.Reset
;
5147 Create_Instantiation_Source
(N
, Gen_Unit
, False, S_Adjustment
);
5149 -- Copy original generic tree, to produce text for instantiation
5153 (Original_Node
(Gen_Decl
), Empty
, Instantiating
=> True);
5155 -- Inherit overriding indicator from instance node
5157 Act_Spec
:= Specification
(Act_Tree
);
5158 Set_Must_Override
(Act_Spec
, Must_Override
(N
));
5159 Set_Must_Not_Override
(Act_Spec
, Must_Not_Override
(N
));
5162 Analyze_Associations
5164 Formals
=> Generic_Formal_Declarations
(Act_Tree
),
5165 F_Copy
=> Generic_Formal_Declarations
(Gen_Decl
));
5167 Vis_Prims_List
:= Check_Hidden_Primitives
(Renaming_List
);
5169 -- The subprogram itself cannot contain a nested instance, so the
5170 -- current parent is left empty.
5172 Set_Instance_Env
(Gen_Unit
, Empty
);
5174 -- Build the subprogram declaration, which does not appear in the
5175 -- generic template, and give it a sloc consistent with that of the
5178 Set_Defining_Unit_Name
(Act_Spec
, Anon_Id
);
5179 Set_Generic_Parent
(Act_Spec
, Gen_Unit
);
5181 Make_Subprogram_Declaration
(Sloc
(Act_Spec
),
5182 Specification
=> Act_Spec
);
5184 -- The aspects have been copied previously, but they have to be
5185 -- linked explicitly to the new subprogram declaration. Explicit
5186 -- pre/postconditions on the instance are analyzed below, in a
5189 Move_Aspects
(Act_Tree
, To
=> Act_Decl
);
5190 Set_Categorization_From_Pragmas
(Act_Decl
);
5192 if Parent_Installed
then
5196 Append
(Act_Decl
, Renaming_List
);
5198 -- Contract-related source pragmas that follow a generic subprogram
5199 -- must be instantiated explicitly because they are not part of the
5200 -- subprogram template.
5202 Instantiate_Subprogram_Contract
(Original_Node
(Gen_Decl
));
5203 Build_Subprogram_Renaming
;
5205 Analyze_Instance_And_Renamings
;
5207 -- If the generic is marked Import (Intrinsic), then so is the
5208 -- instance. This indicates that there is no body to instantiate. If
5209 -- generic is marked inline, so it the instance, and the anonymous
5210 -- subprogram it renames. If inlined, or else if inlining is enabled
5211 -- for the compilation, we generate the instance body even if it is
5212 -- not within the main unit.
5214 if Is_Intrinsic_Subprogram
(Gen_Unit
) then
5215 Set_Is_Intrinsic_Subprogram
(Anon_Id
);
5216 Set_Is_Intrinsic_Subprogram
(Act_Decl_Id
);
5218 if Chars
(Gen_Unit
) = Name_Unchecked_Conversion
then
5219 Validate_Unchecked_Conversion
(N
, Act_Decl_Id
);
5223 -- Inherit convention from generic unit. Intrinsic convention, as for
5224 -- an instance of unchecked conversion, is not inherited because an
5225 -- explicit Ada instance has been created.
5227 if Has_Convention_Pragma
(Gen_Unit
)
5228 and then Convention
(Gen_Unit
) /= Convention_Intrinsic
5230 Set_Convention
(Act_Decl_Id
, Convention
(Gen_Unit
));
5231 Set_Is_Exported
(Act_Decl_Id
, Is_Exported
(Gen_Unit
));
5234 Generate_Definition
(Act_Decl_Id
);
5236 -- Inherit all inlining-related flags which apply to the generic in
5237 -- the subprogram and its declaration.
5239 Set_Is_Inlined
(Act_Decl_Id
, Is_Inlined
(Gen_Unit
));
5240 Set_Is_Inlined
(Anon_Id
, Is_Inlined
(Gen_Unit
));
5242 Set_Has_Pragma_Inline
(Act_Decl_Id
, Has_Pragma_Inline
(Gen_Unit
));
5243 Set_Has_Pragma_Inline
(Anon_Id
, Has_Pragma_Inline
(Gen_Unit
));
5245 Set_Has_Pragma_Inline_Always
5246 (Act_Decl_Id
, Has_Pragma_Inline_Always
(Gen_Unit
));
5247 Set_Has_Pragma_Inline_Always
5248 (Anon_Id
, Has_Pragma_Inline_Always
(Gen_Unit
));
5250 if not Is_Intrinsic_Subprogram
(Gen_Unit
) then
5251 Check_Elab_Instantiation
(N
);
5254 if Is_Dispatching_Operation
(Act_Decl_Id
)
5255 and then Ada_Version
>= Ada_2005
5261 Formal
:= First_Formal
(Act_Decl_Id
);
5262 while Present
(Formal
) loop
5263 if Ekind
(Etype
(Formal
)) = E_Anonymous_Access_Type
5264 and then Is_Controlling_Formal
(Formal
)
5265 and then not Can_Never_Be_Null
(Formal
)
5268 ("access parameter& is controlling,", N
, Formal
);
5270 ("\corresponding parameter of & must be "
5271 & "explicitly null-excluding", N
, Gen_Id
);
5274 Next_Formal
(Formal
);
5279 Check_Hidden_Child_Unit
(N
, Gen_Unit
, Act_Decl_Id
);
5281 Validate_Categorization_Dependency
(N
, Act_Decl_Id
);
5283 if not Is_Intrinsic_Subprogram
(Act_Decl_Id
) then
5284 Inherit_Context
(Gen_Decl
, N
);
5286 Restore_Private_Views
(Pack_Id
, False);
5288 -- If the context requires a full instantiation, mark node for
5289 -- subsequent construction of the body.
5291 if Need_Subprogram_Instance_Body
(N
, Act_Decl_Id
) then
5292 Check_Forward_Instantiation
(Gen_Decl
);
5294 -- The wrapper package is always delayed, because it does not
5295 -- constitute a freeze point, but to insure that the freeze
5296 -- node is placed properly, it is created directly when
5297 -- instantiating the body (otherwise the freeze node might
5298 -- appear to early for nested instantiations).
5300 elsif Nkind
(Parent
(N
)) = N_Compilation_Unit
then
5302 -- For ASIS purposes, indicate that the wrapper package has
5303 -- replaced the instantiation node.
5305 Rewrite
(N
, Unit
(Parent
(N
)));
5306 Set_Unit
(Parent
(N
), N
);
5309 elsif Nkind
(Parent
(N
)) = N_Compilation_Unit
then
5311 -- Replace instance node for library-level instantiations of
5312 -- intrinsic subprograms, for ASIS use.
5314 Rewrite
(N
, Unit
(Parent
(N
)));
5315 Set_Unit
(Parent
(N
), N
);
5318 if Parent_Installed
then
5322 Restore_Hidden_Primitives
(Vis_Prims_List
);
5324 Env_Installed
:= False;
5325 Generic_Renamings
.Set_Last
(0);
5326 Generic_Renamings_HTable
.Reset
;
5328 Ignore_Pragma_SPARK_Mode
:= Save_IPSM
;
5329 SPARK_Mode
:= Save_SM
;
5330 SPARK_Mode_Pragma
:= Save_SMP
;
5332 if SPARK_Mode
= On
then
5333 Dynamic_Elaboration_Checks
:= False;
5339 if Has_Aspects
(N
) then
5340 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
5344 when Instantiation_Error
=>
5345 if Parent_Installed
then
5349 if Env_Installed
then
5353 Ignore_Pragma_SPARK_Mode
:= Save_IPSM
;
5354 SPARK_Mode
:= Save_SM
;
5355 SPARK_Mode_Pragma
:= Save_SMP
;
5357 if SPARK_Mode
= On
then
5358 Dynamic_Elaboration_Checks
:= False;
5360 end Analyze_Subprogram_Instantiation
;
5362 -------------------------
5363 -- Get_Associated_Node --
5364 -------------------------
5366 function Get_Associated_Node
(N
: Node_Id
) return Node_Id
is
5370 Assoc
:= Associated_Node
(N
);
5372 if Nkind
(Assoc
) /= Nkind
(N
) then
5375 elsif Nkind_In
(Assoc
, N_Aggregate
, N_Extension_Aggregate
) then
5379 -- If the node is part of an inner generic, it may itself have been
5380 -- remapped into a further generic copy. Associated_Node is otherwise
5381 -- used for the entity of the node, and will be of a different node
5382 -- kind, or else N has been rewritten as a literal or function call.
5384 while Present
(Associated_Node
(Assoc
))
5385 and then Nkind
(Associated_Node
(Assoc
)) = Nkind
(Assoc
)
5387 Assoc
:= Associated_Node
(Assoc
);
5390 -- Follow and additional link in case the final node was rewritten.
5391 -- This can only happen with nested generic units.
5393 if (Nkind
(Assoc
) = N_Identifier
or else Nkind
(Assoc
) in N_Op
)
5394 and then Present
(Associated_Node
(Assoc
))
5395 and then (Nkind_In
(Associated_Node
(Assoc
), N_Function_Call
,
5396 N_Explicit_Dereference
,
5401 Assoc
:= Associated_Node
(Assoc
);
5404 -- An additional special case: an unconstrained type in an object
5405 -- declaration may have been rewritten as a local subtype constrained
5406 -- by the expression in the declaration. We need to recover the
5407 -- original entity which may be global.
5409 if Present
(Original_Node
(Assoc
))
5410 and then Nkind
(Parent
(N
)) = N_Object_Declaration
5412 Assoc
:= Original_Node
(Assoc
);
5417 end Get_Associated_Node
;
5419 ----------------------------
5420 -- Build_Function_Wrapper --
5421 ----------------------------
5423 function Build_Function_Wrapper
5424 (Formal_Subp
: Entity_Id
;
5425 Actual_Subp
: Entity_Id
) return Node_Id
5427 Loc
: constant Source_Ptr
:= Sloc
(Current_Scope
);
5428 Ret_Type
: constant Entity_Id
:= Get_Instance_Of
(Etype
(Formal_Subp
));
5431 Func_Name
: Node_Id
;
5433 Parm_Type
: Node_Id
;
5434 Profile
: List_Id
:= New_List
;
5441 Func_Name
:= New_Occurrence_Of
(Actual_Subp
, Loc
);
5443 Func
:= Make_Defining_Identifier
(Loc
, Chars
(Formal_Subp
));
5444 Set_Ekind
(Func
, E_Function
);
5445 Set_Is_Generic_Actual_Subprogram
(Func
);
5447 Actuals
:= New_List
;
5448 Profile
:= New_List
;
5450 Act_F
:= First_Formal
(Actual_Subp
);
5451 Form_F
:= First_Formal
(Formal_Subp
);
5452 while Present
(Form_F
) loop
5454 -- Create new formal for profile of wrapper, and add a reference
5455 -- to it in the list of actuals for the enclosing call. The name
5456 -- must be that of the formal in the formal subprogram, because
5457 -- calls to it in the generic body may use named associations.
5459 New_F
:= Make_Defining_Identifier
(Loc
, Chars
(Form_F
));
5462 New_Occurrence_Of
(Get_Instance_Of
(Etype
(Form_F
)), Loc
);
5465 Make_Parameter_Specification
(Loc
,
5466 Defining_Identifier
=> New_F
,
5467 Parameter_Type
=> Parm_Type
));
5469 Append_To
(Actuals
, New_Occurrence_Of
(New_F
, Loc
));
5470 Next_Formal
(Form_F
);
5472 if Present
(Act_F
) then
5473 Next_Formal
(Act_F
);
5478 Make_Function_Specification
(Loc
,
5479 Defining_Unit_Name
=> Func
,
5480 Parameter_Specifications
=> Profile
,
5481 Result_Definition
=> New_Occurrence_Of
(Ret_Type
, Loc
));
5484 Make_Expression_Function
(Loc
,
5485 Specification
=> Spec
,
5487 Make_Function_Call
(Loc
,
5489 Parameter_Associations
=> Actuals
));
5492 end Build_Function_Wrapper
;
5494 ----------------------------
5495 -- Build_Operator_Wrapper --
5496 ----------------------------
5498 function Build_Operator_Wrapper
5499 (Formal_Subp
: Entity_Id
;
5500 Actual_Subp
: Entity_Id
) return Node_Id
5502 Loc
: constant Source_Ptr
:= Sloc
(Current_Scope
);
5503 Ret_Type
: constant Entity_Id
:=
5504 Get_Instance_Of
(Etype
(Formal_Subp
));
5505 Op_Type
: constant Entity_Id
:=
5506 Get_Instance_Of
(Etype
(First_Formal
(Formal_Subp
)));
5507 Is_Binary
: constant Boolean :=
5508 Present
(Next_Formal
(First_Formal
(Formal_Subp
)));
5519 Op_Name
:= Chars
(Actual_Subp
);
5521 -- Create entities for wrapper function and its formals
5523 F1
:= Make_Temporary
(Loc
, 'A');
5524 F2
:= Make_Temporary
(Loc
, 'B');
5525 L
:= New_Occurrence_Of
(F1
, Loc
);
5526 R
:= New_Occurrence_Of
(F2
, Loc
);
5528 Func
:= Make_Defining_Identifier
(Loc
, Chars
(Formal_Subp
));
5529 Set_Ekind
(Func
, E_Function
);
5530 Set_Is_Generic_Actual_Subprogram
(Func
);
5533 Make_Function_Specification
(Loc
,
5534 Defining_Unit_Name
=> Func
,
5535 Parameter_Specifications
=> New_List
(
5536 Make_Parameter_Specification
(Loc
,
5537 Defining_Identifier
=> F1
,
5538 Parameter_Type
=> New_Occurrence_Of
(Op_Type
, Loc
))),
5539 Result_Definition
=> New_Occurrence_Of
(Ret_Type
, Loc
));
5542 Append_To
(Parameter_Specifications
(Spec
),
5543 Make_Parameter_Specification
(Loc
,
5544 Defining_Identifier
=> F2
,
5545 Parameter_Type
=> New_Occurrence_Of
(Op_Type
, Loc
)));
5548 -- Build expression as a function call, or as an operator node
5549 -- that corresponds to the name of the actual, starting with
5550 -- binary operators.
5552 if Op_Name
not in Any_Operator_Name
then
5554 Make_Function_Call
(Loc
,
5556 New_Occurrence_Of
(Actual_Subp
, Loc
),
5557 Parameter_Associations
=> New_List
(L
));
5560 Append_To
(Parameter_Associations
(Expr
), R
);
5565 elsif Is_Binary
then
5566 if Op_Name
= Name_Op_And
then
5567 Expr
:= Make_Op_And
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5568 elsif Op_Name
= Name_Op_Or
then
5569 Expr
:= Make_Op_Or
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5570 elsif Op_Name
= Name_Op_Xor
then
5571 Expr
:= Make_Op_Xor
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5572 elsif Op_Name
= Name_Op_Eq
then
5573 Expr
:= Make_Op_Eq
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5574 elsif Op_Name
= Name_Op_Ne
then
5575 Expr
:= Make_Op_Ne
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5576 elsif Op_Name
= Name_Op_Le
then
5577 Expr
:= Make_Op_Le
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5578 elsif Op_Name
= Name_Op_Gt
then
5579 Expr
:= Make_Op_Gt
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5580 elsif Op_Name
= Name_Op_Ge
then
5581 Expr
:= Make_Op_Ge
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5582 elsif Op_Name
= Name_Op_Lt
then
5583 Expr
:= Make_Op_Lt
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5584 elsif Op_Name
= Name_Op_Add
then
5585 Expr
:= Make_Op_Add
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5586 elsif Op_Name
= Name_Op_Subtract
then
5587 Expr
:= Make_Op_Subtract
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5588 elsif Op_Name
= Name_Op_Concat
then
5589 Expr
:= Make_Op_Concat
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5590 elsif Op_Name
= Name_Op_Multiply
then
5591 Expr
:= Make_Op_Multiply
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5592 elsif Op_Name
= Name_Op_Divide
then
5593 Expr
:= Make_Op_Divide
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5594 elsif Op_Name
= Name_Op_Mod
then
5595 Expr
:= Make_Op_Mod
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5596 elsif Op_Name
= Name_Op_Rem
then
5597 Expr
:= Make_Op_Rem
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5598 elsif Op_Name
= Name_Op_Expon
then
5599 Expr
:= Make_Op_Expon
(Loc
, Left_Opnd
=> L
, Right_Opnd
=> R
);
5605 if Op_Name
= Name_Op_Add
then
5606 Expr
:= Make_Op_Plus
(Loc
, Right_Opnd
=> L
);
5607 elsif Op_Name
= Name_Op_Subtract
then
5608 Expr
:= Make_Op_Minus
(Loc
, Right_Opnd
=> L
);
5609 elsif Op_Name
= Name_Op_Abs
then
5610 Expr
:= Make_Op_Abs
(Loc
, Right_Opnd
=> L
);
5611 elsif Op_Name
= Name_Op_Not
then
5612 Expr
:= Make_Op_Not
(Loc
, Right_Opnd
=> L
);
5617 Make_Expression_Function
(Loc
,
5618 Specification
=> Spec
,
5619 Expression
=> Expr
);
5622 end Build_Operator_Wrapper
;
5624 -------------------------------------------
5625 -- Build_Instance_Compilation_Unit_Nodes --
5626 -------------------------------------------
5628 procedure Build_Instance_Compilation_Unit_Nodes
5633 Decl_Cunit
: Node_Id
;
5634 Body_Cunit
: Node_Id
;
5636 New_Main
: constant Entity_Id
:= Defining_Entity
(Act_Decl
);
5637 Old_Main
: constant Entity_Id
:= Cunit_Entity
(Main_Unit
);
5640 -- A new compilation unit node is built for the instance declaration
5643 Make_Compilation_Unit
(Sloc
(N
),
5644 Context_Items
=> Empty_List
,
5646 Aux_Decls_Node
=> Make_Compilation_Unit_Aux
(Sloc
(N
)));
5648 Set_Parent_Spec
(Act_Decl
, Parent_Spec
(N
));
5650 -- The new compilation unit is linked to its body, but both share the
5651 -- same file, so we do not set Body_Required on the new unit so as not
5652 -- to create a spurious dependency on a non-existent body in the ali.
5653 -- This simplifies CodePeer unit traversal.
5655 -- We use the original instantiation compilation unit as the resulting
5656 -- compilation unit of the instance, since this is the main unit.
5658 Rewrite
(N
, Act_Body
);
5660 -- Propagate the aspect specifications from the package body template to
5661 -- the instantiated version of the package body.
5663 if Has_Aspects
(Act_Body
) then
5664 Set_Aspect_Specifications
5665 (N
, New_Copy_List_Tree
(Aspect_Specifications
(Act_Body
)));
5668 Body_Cunit
:= Parent
(N
);
5670 -- The two compilation unit nodes are linked by the Library_Unit field
5672 Set_Library_Unit
(Decl_Cunit
, Body_Cunit
);
5673 Set_Library_Unit
(Body_Cunit
, Decl_Cunit
);
5675 -- Preserve the private nature of the package if needed
5677 Set_Private_Present
(Decl_Cunit
, Private_Present
(Body_Cunit
));
5679 -- If the instance is not the main unit, its context, categorization
5680 -- and elaboration entity are not relevant to the compilation.
5682 if Body_Cunit
/= Cunit
(Main_Unit
) then
5683 Make_Instance_Unit
(Body_Cunit
, In_Main
=> False);
5687 -- The context clause items on the instantiation, which are now attached
5688 -- to the body compilation unit (since the body overwrote the original
5689 -- instantiation node), semantically belong on the spec, so copy them
5690 -- there. It's harmless to leave them on the body as well. In fact one
5691 -- could argue that they belong in both places.
5693 Citem
:= First
(Context_Items
(Body_Cunit
));
5694 while Present
(Citem
) loop
5695 Append
(New_Copy
(Citem
), Context_Items
(Decl_Cunit
));
5699 -- Propagate categorization flags on packages, so that they appear in
5700 -- the ali file for the spec of the unit.
5702 if Ekind
(New_Main
) = E_Package
then
5703 Set_Is_Pure
(Old_Main
, Is_Pure
(New_Main
));
5704 Set_Is_Preelaborated
(Old_Main
, Is_Preelaborated
(New_Main
));
5705 Set_Is_Remote_Types
(Old_Main
, Is_Remote_Types
(New_Main
));
5706 Set_Is_Shared_Passive
(Old_Main
, Is_Shared_Passive
(New_Main
));
5707 Set_Is_Remote_Call_Interface
5708 (Old_Main
, Is_Remote_Call_Interface
(New_Main
));
5711 -- Make entry in Units table, so that binder can generate call to
5712 -- elaboration procedure for body, if any.
5714 Make_Instance_Unit
(Body_Cunit
, In_Main
=> True);
5715 Main_Unit_Entity
:= New_Main
;
5716 Set_Cunit_Entity
(Main_Unit
, Main_Unit_Entity
);
5718 -- Build elaboration entity, since the instance may certainly generate
5719 -- elaboration code requiring a flag for protection.
5721 Build_Elaboration_Entity
(Decl_Cunit
, New_Main
);
5722 end Build_Instance_Compilation_Unit_Nodes
;
5724 -----------------------------
5725 -- Check_Access_Definition --
5726 -----------------------------
5728 procedure Check_Access_Definition
(N
: Node_Id
) is
5731 (Ada_Version
>= Ada_2005
and then Present
(Access_Definition
(N
)));
5733 end Check_Access_Definition
;
5735 -----------------------------------
5736 -- Check_Formal_Package_Instance --
5737 -----------------------------------
5739 -- If the formal has specific parameters, they must match those of the
5740 -- actual. Both of them are instances, and the renaming declarations for
5741 -- their formal parameters appear in the same order in both. The analyzed
5742 -- formal has been analyzed in the context of the current instance.
5744 procedure Check_Formal_Package_Instance
5745 (Formal_Pack
: Entity_Id
;
5746 Actual_Pack
: Entity_Id
)
5748 E1
: Entity_Id
:= First_Entity
(Actual_Pack
);
5749 E2
: Entity_Id
:= First_Entity
(Formal_Pack
);
5754 procedure Check_Mismatch
(B
: Boolean);
5755 -- Common error routine for mismatch between the parameters of the
5756 -- actual instance and those of the formal package.
5758 function Same_Instantiated_Constant
(E1
, E2
: Entity_Id
) return Boolean;
5759 -- The formal may come from a nested formal package, and the actual may
5760 -- have been constant-folded. To determine whether the two denote the
5761 -- same entity we may have to traverse several definitions to recover
5762 -- the ultimate entity that they refer to.
5764 function Same_Instantiated_Variable
(E1
, E2
: Entity_Id
) return Boolean;
5765 -- Similarly, if the formal comes from a nested formal package, the
5766 -- actual may designate the formal through multiple renamings, which
5767 -- have to be followed to determine the original variable in question.
5769 --------------------
5770 -- Check_Mismatch --
5771 --------------------
5773 procedure Check_Mismatch
(B
: Boolean) is
5774 Kind
: constant Node_Kind
:= Nkind
(Parent
(E2
));
5777 if Kind
= N_Formal_Type_Declaration
then
5780 elsif Nkind_In
(Kind
, N_Formal_Object_Declaration
,
5781 N_Formal_Package_Declaration
)
5782 or else Kind
in N_Formal_Subprogram_Declaration
5786 -- Ada 2012: If both formal and actual are incomplete types they
5789 elsif Is_Incomplete_Type
(E1
) and then Is_Incomplete_Type
(E2
) then
5794 ("actual for & in actual instance does not match formal",
5795 Parent
(Actual_Pack
), E1
);
5799 --------------------------------
5800 -- Same_Instantiated_Constant --
5801 --------------------------------
5803 function Same_Instantiated_Constant
5804 (E1
, E2
: Entity_Id
) return Boolean
5810 while Present
(Ent
) loop
5814 elsif Ekind
(Ent
) /= E_Constant
then
5817 elsif Is_Entity_Name
(Constant_Value
(Ent
)) then
5818 if Entity
(Constant_Value
(Ent
)) = E1
then
5821 Ent
:= Entity
(Constant_Value
(Ent
));
5824 -- The actual may be a constant that has been folded. Recover
5827 elsif Is_Entity_Name
(Original_Node
(Constant_Value
(Ent
))) then
5828 Ent
:= Entity
(Original_Node
(Constant_Value
(Ent
)));
5836 end Same_Instantiated_Constant
;
5838 --------------------------------
5839 -- Same_Instantiated_Variable --
5840 --------------------------------
5842 function Same_Instantiated_Variable
5843 (E1
, E2
: Entity_Id
) return Boolean
5845 function Original_Entity
(E
: Entity_Id
) return Entity_Id
;
5846 -- Follow chain of renamings to the ultimate ancestor
5848 ---------------------
5849 -- Original_Entity --
5850 ---------------------
5852 function Original_Entity
(E
: Entity_Id
) return Entity_Id
is
5857 while Nkind
(Parent
(Orig
)) = N_Object_Renaming_Declaration
5858 and then Present
(Renamed_Object
(Orig
))
5859 and then Is_Entity_Name
(Renamed_Object
(Orig
))
5861 Orig
:= Entity
(Renamed_Object
(Orig
));
5865 end Original_Entity
;
5867 -- Start of processing for Same_Instantiated_Variable
5870 return Ekind
(E1
) = Ekind
(E2
)
5871 and then Original_Entity
(E1
) = Original_Entity
(E2
);
5872 end Same_Instantiated_Variable
;
5874 -- Start of processing for Check_Formal_Package_Instance
5877 while Present
(E1
) and then Present
(E2
) loop
5878 exit when Ekind
(E1
) = E_Package
5879 and then Renamed_Entity
(E1
) = Renamed_Entity
(Actual_Pack
);
5881 -- If the formal is the renaming of the formal package, this
5882 -- is the end of its formal part, which may occur before the
5883 -- end of the formal part in the actual in the presence of
5884 -- defaulted parameters in the formal package.
5886 exit when Nkind
(Parent
(E2
)) = N_Package_Renaming_Declaration
5887 and then Renamed_Entity
(E2
) = Scope
(E2
);
5889 -- The analysis of the actual may generate additional internal
5890 -- entities. If the formal is defaulted, there is no corresponding
5891 -- analysis and the internal entities must be skipped, until we
5892 -- find corresponding entities again.
5894 if Comes_From_Source
(E2
)
5895 and then not Comes_From_Source
(E1
)
5896 and then Chars
(E1
) /= Chars
(E2
)
5898 while Present
(E1
) and then Chars
(E1
) /= Chars
(E2
) loop
5906 -- If the formal entity comes from a formal declaration, it was
5907 -- defaulted in the formal package, and no check is needed on it.
5909 elsif Nkind
(Parent
(E2
)) = N_Formal_Object_Declaration
then
5912 -- Ditto for defaulted formal subprograms.
5914 elsif Is_Overloadable
(E1
)
5915 and then Nkind
(Unit_Declaration_Node
(E2
)) in
5916 N_Formal_Subprogram_Declaration
5920 elsif Is_Type
(E1
) then
5922 -- Subtypes must statically match. E1, E2 are the local entities
5923 -- that are subtypes of the actuals. Itypes generated for other
5924 -- parameters need not be checked, the check will be performed
5925 -- on the parameters themselves.
5927 -- If E2 is a formal type declaration, it is a defaulted parameter
5928 -- and needs no checking.
5930 if not Is_Itype
(E1
) and then not Is_Itype
(E2
) then
5933 or else Etype
(E1
) /= Etype
(E2
)
5934 or else not Subtypes_Statically_Match
(E1
, E2
));
5937 elsif Ekind
(E1
) = E_Constant
then
5939 -- IN parameters must denote the same static value, or the same
5940 -- constant, or the literal null.
5942 Expr1
:= Expression
(Parent
(E1
));
5944 if Ekind
(E2
) /= E_Constant
then
5945 Check_Mismatch
(True);
5948 Expr2
:= Expression
(Parent
(E2
));
5951 if Is_OK_Static_Expression
(Expr1
) then
5952 if not Is_OK_Static_Expression
(Expr2
) then
5953 Check_Mismatch
(True);
5955 elsif Is_Discrete_Type
(Etype
(E1
)) then
5957 V1
: constant Uint
:= Expr_Value
(Expr1
);
5958 V2
: constant Uint
:= Expr_Value
(Expr2
);
5960 Check_Mismatch
(V1
/= V2
);
5963 elsif Is_Real_Type
(Etype
(E1
)) then
5965 V1
: constant Ureal
:= Expr_Value_R
(Expr1
);
5966 V2
: constant Ureal
:= Expr_Value_R
(Expr2
);
5968 Check_Mismatch
(V1
/= V2
);
5971 elsif Is_String_Type
(Etype
(E1
))
5972 and then Nkind
(Expr1
) = N_String_Literal
5974 if Nkind
(Expr2
) /= N_String_Literal
then
5975 Check_Mismatch
(True);
5978 (not String_Equal
(Strval
(Expr1
), Strval
(Expr2
)));
5982 elsif Is_Entity_Name
(Expr1
) then
5983 if Is_Entity_Name
(Expr2
) then
5984 if Entity
(Expr1
) = Entity
(Expr2
) then
5988 (not Same_Instantiated_Constant
5989 (Entity
(Expr1
), Entity
(Expr2
)));
5993 Check_Mismatch
(True);
5996 elsif Is_Entity_Name
(Original_Node
(Expr1
))
5997 and then Is_Entity_Name
(Expr2
)
5998 and then Same_Instantiated_Constant
5999 (Entity
(Original_Node
(Expr1
)), Entity
(Expr2
))
6003 elsif Nkind
(Expr1
) = N_Null
then
6004 Check_Mismatch
(Nkind
(Expr1
) /= N_Null
);
6007 Check_Mismatch
(True);
6010 elsif Ekind
(E1
) = E_Variable
then
6011 Check_Mismatch
(not Same_Instantiated_Variable
(E1
, E2
));
6013 elsif Ekind
(E1
) = E_Package
then
6015 (Ekind
(E1
) /= Ekind
(E2
)
6016 or else Renamed_Object
(E1
) /= Renamed_Object
(E2
));
6018 elsif Is_Overloadable
(E1
) then
6020 -- Verify that the actual subprograms match. Note that actuals
6021 -- that are attributes are rewritten as subprograms. If the
6022 -- subprogram in the formal package is defaulted, no check is
6023 -- needed. Note that this can only happen in Ada 2005 when the
6024 -- formal package can be partially parameterized.
6026 if Nkind
(Unit_Declaration_Node
(E1
)) =
6027 N_Subprogram_Renaming_Declaration
6028 and then From_Default
(Unit_Declaration_Node
(E1
))
6032 -- If the formal package has an "others" box association that
6033 -- covers this formal, there is no need for a check either.
6035 elsif Nkind
(Unit_Declaration_Node
(E2
)) in
6036 N_Formal_Subprogram_Declaration
6037 and then Box_Present
(Unit_Declaration_Node
(E2
))
6041 -- No check needed if subprogram is a defaulted null procedure
6043 elsif No
(Alias
(E2
))
6044 and then Ekind
(E2
) = E_Procedure
6046 Null_Present
(Specification
(Unit_Declaration_Node
(E2
)))
6050 -- Otherwise the actual in the formal and the actual in the
6051 -- instantiation of the formal must match, up to renamings.
6055 (Ekind
(E2
) /= Ekind
(E1
) or else (Alias
(E1
)) /= Alias
(E2
));
6059 raise Program_Error
;
6066 end Check_Formal_Package_Instance
;
6068 ---------------------------
6069 -- Check_Formal_Packages --
6070 ---------------------------
6072 procedure Check_Formal_Packages
(P_Id
: Entity_Id
) is
6074 Formal_P
: Entity_Id
;
6077 -- Iterate through the declarations in the instance, looking for package
6078 -- renaming declarations that denote instances of formal packages. Stop
6079 -- when we find the renaming of the current package itself. The
6080 -- declaration for a formal package without a box is followed by an
6081 -- internal entity that repeats the instantiation.
6083 E
:= First_Entity
(P_Id
);
6084 while Present
(E
) loop
6085 if Ekind
(E
) = E_Package
then
6086 if Renamed_Object
(E
) = P_Id
then
6089 elsif Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
then
6092 elsif not Box_Present
(Parent
(Associated_Formal_Package
(E
))) then
6093 Formal_P
:= Next_Entity
(E
);
6094 Check_Formal_Package_Instance
(Formal_P
, E
);
6096 -- After checking, remove the internal validating package. It
6097 -- is only needed for semantic checks, and as it may contain
6098 -- generic formal declarations it should not reach gigi.
6100 Remove
(Unit_Declaration_Node
(Formal_P
));
6106 end Check_Formal_Packages
;
6108 ---------------------------------
6109 -- Check_Forward_Instantiation --
6110 ---------------------------------
6112 procedure Check_Forward_Instantiation
(Decl
: Node_Id
) is
6114 Gen_Comp
: Entity_Id
:= Cunit_Entity
(Get_Source_Unit
(Decl
));
6117 -- The instantiation appears before the generic body if we are in the
6118 -- scope of the unit containing the generic, either in its spec or in
6119 -- the package body, and before the generic body.
6121 if Ekind
(Gen_Comp
) = E_Package_Body
then
6122 Gen_Comp
:= Spec_Entity
(Gen_Comp
);
6125 if In_Open_Scopes
(Gen_Comp
)
6126 and then No
(Corresponding_Body
(Decl
))
6131 and then not Is_Compilation_Unit
(S
)
6132 and then not Is_Child_Unit
(S
)
6134 if Ekind
(S
) = E_Package
then
6135 Set_Has_Forward_Instantiation
(S
);
6141 end Check_Forward_Instantiation
;
6143 ---------------------------
6144 -- Check_Generic_Actuals --
6145 ---------------------------
6147 -- The visibility of the actuals may be different between the point of
6148 -- generic instantiation and the instantiation of the body.
6150 procedure Check_Generic_Actuals
6151 (Instance
: Entity_Id
;
6152 Is_Formal_Box
: Boolean)
6157 function Denotes_Previous_Actual
(Typ
: Entity_Id
) return Boolean;
6158 -- For a formal that is an array type, the component type is often a
6159 -- previous formal in the same unit. The privacy status of the component
6160 -- type will have been examined earlier in the traversal of the
6161 -- corresponding actuals, and this status should not be modified for
6162 -- the array (sub)type itself. However, if the base type of the array
6163 -- (sub)type is private, its full view must be restored in the body to
6164 -- be consistent with subsequent index subtypes, etc.
6166 -- To detect this case we have to rescan the list of formals, which is
6167 -- usually short enough to ignore the resulting inefficiency.
6169 -----------------------------
6170 -- Denotes_Previous_Actual --
6171 -----------------------------
6173 function Denotes_Previous_Actual
(Typ
: Entity_Id
) return Boolean is
6177 Prev
:= First_Entity
(Instance
);
6178 while Present
(Prev
) loop
6180 and then Nkind
(Parent
(Prev
)) = N_Subtype_Declaration
6181 and then Is_Entity_Name
(Subtype_Indication
(Parent
(Prev
)))
6182 and then Entity
(Subtype_Indication
(Parent
(Prev
))) = Typ
6195 end Denotes_Previous_Actual
;
6197 -- Start of processing for Check_Generic_Actuals
6200 E
:= First_Entity
(Instance
);
6201 while Present
(E
) loop
6203 and then Nkind
(Parent
(E
)) = N_Subtype_Declaration
6204 and then Scope
(Etype
(E
)) /= Instance
6205 and then Is_Entity_Name
(Subtype_Indication
(Parent
(E
)))
6207 if Is_Array_Type
(E
)
6208 and then not Is_Private_Type
(Etype
(E
))
6209 and then Denotes_Previous_Actual
(Component_Type
(E
))
6213 Check_Private_View
(Subtype_Indication
(Parent
(E
)));
6216 Set_Is_Generic_Actual_Type
(E
, True);
6217 Set_Is_Hidden
(E
, False);
6218 Set_Is_Potentially_Use_Visible
(E
,
6221 -- We constructed the generic actual type as a subtype of the
6222 -- supplied type. This means that it normally would not inherit
6223 -- subtype specific attributes of the actual, which is wrong for
6224 -- the generic case.
6226 Astype
:= Ancestor_Subtype
(E
);
6230 -- This can happen when E is an itype that is the full view of
6231 -- a private type completed, e.g. with a constrained array. In
6232 -- that case, use the first subtype, which will carry size
6233 -- information. The base type itself is unconstrained and will
6236 Astype
:= First_Subtype
(E
);
6239 Set_Size_Info
(E
, (Astype
));
6240 Set_RM_Size
(E
, RM_Size
(Astype
));
6241 Set_First_Rep_Item
(E
, First_Rep_Item
(Astype
));
6243 if Is_Discrete_Or_Fixed_Point_Type
(E
) then
6244 Set_RM_Size
(E
, RM_Size
(Astype
));
6246 -- In nested instances, the base type of an access actual may
6247 -- itself be private, and need to be exchanged.
6249 elsif Is_Access_Type
(E
)
6250 and then Is_Private_Type
(Etype
(E
))
6253 (New_Occurrence_Of
(Etype
(E
), Sloc
(Instance
)));
6256 elsif Ekind
(E
) = E_Package
then
6258 -- If this is the renaming for the current instance, we're done.
6259 -- Otherwise it is a formal package. If the corresponding formal
6260 -- was declared with a box, the (instantiations of the) generic
6261 -- formal part are also visible. Otherwise, ignore the entity
6262 -- created to validate the actuals.
6264 if Renamed_Object
(E
) = Instance
then
6267 elsif Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
then
6270 -- The visibility of a formal of an enclosing generic is already
6273 elsif Denotes_Formal_Package
(E
) then
6276 elsif Present
(Associated_Formal_Package
(E
))
6277 and then not Is_Generic_Formal
(E
)
6279 if Box_Present
(Parent
(Associated_Formal_Package
(E
))) then
6280 Check_Generic_Actuals
(Renamed_Object
(E
), True);
6283 Check_Generic_Actuals
(Renamed_Object
(E
), False);
6286 Set_Is_Hidden
(E
, False);
6289 -- If this is a subprogram instance (in a wrapper package) the
6290 -- actual is fully visible.
6292 elsif Is_Wrapper_Package
(Instance
) then
6293 Set_Is_Hidden
(E
, False);
6295 -- If the formal package is declared with a box, or if the formal
6296 -- parameter is defaulted, it is visible in the body.
6298 elsif Is_Formal_Box
or else Is_Visible_Formal
(E
) then
6299 Set_Is_Hidden
(E
, False);
6302 if Ekind
(E
) = E_Constant
then
6304 -- If the type of the actual is a private type declared in the
6305 -- enclosing scope of the generic unit, the body of the generic
6306 -- sees the full view of the type (because it has to appear in
6307 -- the corresponding package body). If the type is private now,
6308 -- exchange views to restore the proper visiblity in the instance.
6311 Typ
: constant Entity_Id
:= Base_Type
(Etype
(E
));
6312 -- The type of the actual
6317 Parent_Scope
: Entity_Id
;
6318 -- The enclosing scope of the generic unit
6321 if Is_Wrapper_Package
(Instance
) then
6325 (Unit_Declaration_Node
6326 (Related_Instance
(Instance
))));
6329 Generic_Parent
(Package_Specification
(Instance
));
6332 Parent_Scope
:= Scope
(Gen_Id
);
6334 -- The exchange is only needed if the generic is defined
6335 -- within a package which is not a common ancestor of the
6336 -- scope of the instance, and is not already in scope.
6338 if Is_Private_Type
(Typ
)
6339 and then Scope
(Typ
) = Parent_Scope
6340 and then Scope
(Instance
) /= Parent_Scope
6341 and then Ekind
(Parent_Scope
) = E_Package
6342 and then not Is_Child_Unit
(Gen_Id
)
6346 -- If the type of the entity is a subtype, it may also have
6347 -- to be made visible, together with the base type of its
6348 -- full view, after exchange.
6350 if Is_Private_Type
(Etype
(E
)) then
6351 Switch_View
(Etype
(E
));
6352 Switch_View
(Base_Type
(Etype
(E
)));
6360 end Check_Generic_Actuals
;
6362 ------------------------------
6363 -- Check_Generic_Child_Unit --
6364 ------------------------------
6366 procedure Check_Generic_Child_Unit
6368 Parent_Installed
: in out Boolean)
6370 Loc
: constant Source_Ptr
:= Sloc
(Gen_Id
);
6371 Gen_Par
: Entity_Id
:= Empty
;
6373 Inst_Par
: Entity_Id
;
6376 function Find_Generic_Child
6378 Id
: Node_Id
) return Entity_Id
;
6379 -- Search generic parent for possible child unit with the given name
6381 function In_Enclosing_Instance
return Boolean;
6382 -- Within an instance of the parent, the child unit may be denoted by
6383 -- a simple name, or an abbreviated expanded name. Examine enclosing
6384 -- scopes to locate a possible parent instantiation.
6386 ------------------------
6387 -- Find_Generic_Child --
6388 ------------------------
6390 function Find_Generic_Child
6392 Id
: Node_Id
) return Entity_Id
6397 -- If entity of name is already set, instance has already been
6398 -- resolved, e.g. in an enclosing instantiation.
6400 if Present
(Entity
(Id
)) then
6401 if Scope
(Entity
(Id
)) = Scop
then
6408 E
:= First_Entity
(Scop
);
6409 while Present
(E
) loop
6410 if Chars
(E
) = Chars
(Id
)
6411 and then Is_Child_Unit
(E
)
6413 if Is_Child_Unit
(E
)
6414 and then not Is_Visible_Lib_Unit
(E
)
6417 ("generic child unit& is not visible", Gen_Id
, E
);
6429 end Find_Generic_Child
;
6431 ---------------------------
6432 -- In_Enclosing_Instance --
6433 ---------------------------
6435 function In_Enclosing_Instance
return Boolean is
6436 Enclosing_Instance
: Node_Id
;
6437 Instance_Decl
: Node_Id
;
6440 -- We do not inline any call that contains instantiations, except
6441 -- for instantiations of Unchecked_Conversion, so if we are within
6442 -- an inlined body the current instance does not require parents.
6444 if In_Inlined_Body
then
6445 pragma Assert
(Chars
(Gen_Id
) = Name_Unchecked_Conversion
);
6449 -- Loop to check enclosing scopes
6451 Enclosing_Instance
:= Current_Scope
;
6452 while Present
(Enclosing_Instance
) loop
6453 Instance_Decl
:= Unit_Declaration_Node
(Enclosing_Instance
);
6455 if Ekind
(Enclosing_Instance
) = E_Package
6456 and then Is_Generic_Instance
(Enclosing_Instance
)
6458 (Generic_Parent
(Specification
(Instance_Decl
)))
6460 -- Check whether the generic we are looking for is a child of
6463 E
:= Find_Generic_Child
6464 (Generic_Parent
(Specification
(Instance_Decl
)), Gen_Id
);
6465 exit when Present
(E
);
6471 Enclosing_Instance
:= Scope
(Enclosing_Instance
);
6483 Make_Expanded_Name
(Loc
,
6485 Prefix
=> New_Occurrence_Of
(Enclosing_Instance
, Loc
),
6486 Selector_Name
=> New_Occurrence_Of
(E
, Loc
)));
6488 Set_Entity
(Gen_Id
, E
);
6489 Set_Etype
(Gen_Id
, Etype
(E
));
6490 Parent_Installed
:= False; -- Already in scope.
6493 end In_Enclosing_Instance
;
6495 -- Start of processing for Check_Generic_Child_Unit
6498 -- If the name of the generic is given by a selected component, it may
6499 -- be the name of a generic child unit, and the prefix is the name of an
6500 -- instance of the parent, in which case the child unit must be visible.
6501 -- If this instance is not in scope, it must be placed there and removed
6502 -- after instantiation, because what is being instantiated is not the
6503 -- original child, but the corresponding child present in the instance
6506 -- If the child is instantiated within the parent, it can be given by
6507 -- a simple name. In this case the instance is already in scope, but
6508 -- the child generic must be recovered from the generic parent as well.
6510 if Nkind
(Gen_Id
) = N_Selected_Component
then
6511 S
:= Selector_Name
(Gen_Id
);
6512 Analyze
(Prefix
(Gen_Id
));
6513 Inst_Par
:= Entity
(Prefix
(Gen_Id
));
6515 if Ekind
(Inst_Par
) = E_Package
6516 and then Present
(Renamed_Object
(Inst_Par
))
6518 Inst_Par
:= Renamed_Object
(Inst_Par
);
6521 if Ekind
(Inst_Par
) = E_Package
then
6522 if Nkind
(Parent
(Inst_Par
)) = N_Package_Specification
then
6523 Gen_Par
:= Generic_Parent
(Parent
(Inst_Par
));
6525 elsif Nkind
(Parent
(Inst_Par
)) = N_Defining_Program_Unit_Name
6527 Nkind
(Parent
(Parent
(Inst_Par
))) = N_Package_Specification
6529 Gen_Par
:= Generic_Parent
(Parent
(Parent
(Inst_Par
)));
6532 elsif Ekind
(Inst_Par
) = E_Generic_Package
6533 and then Nkind
(Parent
(Gen_Id
)) = N_Formal_Package_Declaration
6535 -- A formal package may be a real child package, and not the
6536 -- implicit instance within a parent. In this case the child is
6537 -- not visible and has to be retrieved explicitly as well.
6539 Gen_Par
:= Inst_Par
;
6542 if Present
(Gen_Par
) then
6544 -- The prefix denotes an instantiation. The entity itself may be a
6545 -- nested generic, or a child unit.
6547 E
:= Find_Generic_Child
(Gen_Par
, S
);
6550 Change_Selected_Component_To_Expanded_Name
(Gen_Id
);
6551 Set_Entity
(Gen_Id
, E
);
6552 Set_Etype
(Gen_Id
, Etype
(E
));
6554 Set_Etype
(S
, Etype
(E
));
6556 -- Indicate that this is a reference to the parent
6558 if In_Extended_Main_Source_Unit
(Gen_Id
) then
6559 Set_Is_Instantiated
(Inst_Par
);
6562 -- A common mistake is to replicate the naming scheme of a
6563 -- hierarchy by instantiating a generic child directly, rather
6564 -- than the implicit child in a parent instance:
6566 -- generic .. package Gpar is ..
6567 -- generic .. package Gpar.Child is ..
6568 -- package Par is new Gpar ();
6571 -- package Par.Child is new Gpar.Child ();
6572 -- rather than Par.Child
6574 -- In this case the instantiation is within Par, which is an
6575 -- instance, but Gpar does not denote Par because we are not IN
6576 -- the instance of Gpar, so this is illegal. The test below
6577 -- recognizes this particular case.
6579 if Is_Child_Unit
(E
)
6580 and then not Comes_From_Source
(Entity
(Prefix
(Gen_Id
)))
6581 and then (not In_Instance
6582 or else Nkind
(Parent
(Parent
(Gen_Id
))) =
6586 ("prefix of generic child unit must be instance of parent",
6590 if not In_Open_Scopes
(Inst_Par
)
6591 and then Nkind
(Parent
(Gen_Id
)) not in
6592 N_Generic_Renaming_Declaration
6594 Install_Parent
(Inst_Par
);
6595 Parent_Installed
:= True;
6597 elsif In_Open_Scopes
(Inst_Par
) then
6599 -- If the parent is already installed, install the actuals
6600 -- for its formal packages. This is necessary when the child
6601 -- instance is a child of the parent instance: in this case,
6602 -- the parent is placed on the scope stack but the formal
6603 -- packages are not made visible.
6605 Install_Formal_Packages
(Inst_Par
);
6609 -- If the generic parent does not contain an entity that
6610 -- corresponds to the selector, the instance doesn't either.
6611 -- Analyzing the node will yield the appropriate error message.
6612 -- If the entity is not a child unit, then it is an inner
6613 -- generic in the parent.
6621 if Is_Child_Unit
(Entity
(Gen_Id
))
6623 Nkind
(Parent
(Gen_Id
)) not in N_Generic_Renaming_Declaration
6624 and then not In_Open_Scopes
(Inst_Par
)
6626 Install_Parent
(Inst_Par
);
6627 Parent_Installed
:= True;
6629 -- The generic unit may be the renaming of the implicit child
6630 -- present in an instance. In that case the parent instance is
6631 -- obtained from the name of the renamed entity.
6633 elsif Ekind
(Entity
(Gen_Id
)) = E_Generic_Package
6634 and then Present
(Renamed_Entity
(Entity
(Gen_Id
)))
6635 and then Is_Child_Unit
(Renamed_Entity
(Entity
(Gen_Id
)))
6638 Renamed_Package
: constant Node_Id
:=
6639 Name
(Parent
(Entity
(Gen_Id
)));
6641 if Nkind
(Renamed_Package
) = N_Expanded_Name
then
6642 Inst_Par
:= Entity
(Prefix
(Renamed_Package
));
6643 Install_Parent
(Inst_Par
);
6644 Parent_Installed
:= True;
6650 elsif Nkind
(Gen_Id
) = N_Expanded_Name
then
6652 -- Entity already present, analyze prefix, whose meaning may be
6653 -- an instance in the current context. If it is an instance of
6654 -- a relative within another, the proper parent may still have
6655 -- to be installed, if they are not of the same generation.
6657 Analyze
(Prefix
(Gen_Id
));
6659 -- In the unlikely case that a local declaration hides the name
6660 -- of the parent package, locate it on the homonym chain. If the
6661 -- context is an instance of the parent, the renaming entity is
6664 Inst_Par
:= Entity
(Prefix
(Gen_Id
));
6665 while Present
(Inst_Par
)
6666 and then not Is_Package_Or_Generic_Package
(Inst_Par
)
6668 Inst_Par
:= Homonym
(Inst_Par
);
6671 pragma Assert
(Present
(Inst_Par
));
6672 Set_Entity
(Prefix
(Gen_Id
), Inst_Par
);
6674 if In_Enclosing_Instance
then
6677 elsif Present
(Entity
(Gen_Id
))
6678 and then Is_Child_Unit
(Entity
(Gen_Id
))
6679 and then not In_Open_Scopes
(Inst_Par
)
6681 Install_Parent
(Inst_Par
);
6682 Parent_Installed
:= True;
6685 elsif In_Enclosing_Instance
then
6687 -- The child unit is found in some enclosing scope
6694 -- If this is the renaming of the implicit child in a parent
6695 -- instance, recover the parent name and install it.
6697 if Is_Entity_Name
(Gen_Id
) then
6698 E
:= Entity
(Gen_Id
);
6700 if Is_Generic_Unit
(E
)
6701 and then Nkind
(Parent
(E
)) in N_Generic_Renaming_Declaration
6702 and then Is_Child_Unit
(Renamed_Object
(E
))
6703 and then Is_Generic_Unit
(Scope
(Renamed_Object
(E
)))
6704 and then Nkind
(Name
(Parent
(E
))) = N_Expanded_Name
6706 Rewrite
(Gen_Id
, New_Copy_Tree
(Name
(Parent
(E
))));
6707 Inst_Par
:= Entity
(Prefix
(Gen_Id
));
6709 if not In_Open_Scopes
(Inst_Par
) then
6710 Install_Parent
(Inst_Par
);
6711 Parent_Installed
:= True;
6714 -- If it is a child unit of a non-generic parent, it may be
6715 -- use-visible and given by a direct name. Install parent as
6718 elsif Is_Generic_Unit
(E
)
6719 and then Is_Child_Unit
(E
)
6721 Nkind
(Parent
(Gen_Id
)) not in N_Generic_Renaming_Declaration
6722 and then not Is_Generic_Unit
(Scope
(E
))
6724 if not In_Open_Scopes
(Scope
(E
)) then
6725 Install_Parent
(Scope
(E
));
6726 Parent_Installed
:= True;
6731 end Check_Generic_Child_Unit
;
6733 -----------------------------
6734 -- Check_Hidden_Child_Unit --
6735 -----------------------------
6737 procedure Check_Hidden_Child_Unit
6739 Gen_Unit
: Entity_Id
;
6740 Act_Decl_Id
: Entity_Id
)
6742 Gen_Id
: constant Node_Id
:= Name
(N
);
6745 if Is_Child_Unit
(Gen_Unit
)
6746 and then Is_Child_Unit
(Act_Decl_Id
)
6747 and then Nkind
(Gen_Id
) = N_Expanded_Name
6748 and then Entity
(Prefix
(Gen_Id
)) = Scope
(Act_Decl_Id
)
6749 and then Chars
(Gen_Unit
) = Chars
(Act_Decl_Id
)
6751 Error_Msg_Node_2
:= Scope
(Act_Decl_Id
);
6753 ("generic unit & is implicitly declared in &",
6754 Defining_Unit_Name
(N
), Gen_Unit
);
6755 Error_Msg_N
("\instance must have different name",
6756 Defining_Unit_Name
(N
));
6758 end Check_Hidden_Child_Unit
;
6760 ------------------------
6761 -- Check_Private_View --
6762 ------------------------
6764 procedure Check_Private_View
(N
: Node_Id
) is
6765 T
: constant Entity_Id
:= Etype
(N
);
6769 -- Exchange views if the type was not private in the generic but is
6770 -- private at the point of instantiation. Do not exchange views if
6771 -- the scope of the type is in scope. This can happen if both generic
6772 -- and instance are sibling units, or if type is defined in a parent.
6773 -- In this case the visibility of the type will be correct for all
6777 BT
:= Base_Type
(T
);
6779 if Is_Private_Type
(T
)
6780 and then not Has_Private_View
(N
)
6781 and then Present
(Full_View
(T
))
6782 and then not In_Open_Scopes
(Scope
(T
))
6784 -- In the generic, the full type was visible. Save the private
6785 -- entity, for subsequent exchange.
6789 elsif Has_Private_View
(N
)
6790 and then not Is_Private_Type
(T
)
6791 and then not Has_Been_Exchanged
(T
)
6792 and then Etype
(Get_Associated_Node
(N
)) /= T
6794 -- Only the private declaration was visible in the generic. If
6795 -- the type appears in a subtype declaration, the subtype in the
6796 -- instance must have a view compatible with that of its parent,
6797 -- which must be exchanged (see corresponding code in Restore_
6798 -- Private_Views). Otherwise, if the type is defined in a parent
6799 -- unit, leave full visibility within instance, which is safe.
6801 if In_Open_Scopes
(Scope
(Base_Type
(T
)))
6802 and then not Is_Private_Type
(Base_Type
(T
))
6803 and then Comes_From_Source
(Base_Type
(T
))
6807 elsif Nkind
(Parent
(N
)) = N_Subtype_Declaration
6808 or else not In_Private_Part
(Scope
(Base_Type
(T
)))
6810 Prepend_Elmt
(T
, Exchanged_Views
);
6811 Exchange_Declarations
(Etype
(Get_Associated_Node
(N
)));
6814 -- For composite types with inconsistent representation exchange
6815 -- component types accordingly.
6817 elsif Is_Access_Type
(T
)
6818 and then Is_Private_Type
(Designated_Type
(T
))
6819 and then not Has_Private_View
(N
)
6820 and then Present
(Full_View
(Designated_Type
(T
)))
6822 Switch_View
(Designated_Type
(T
));
6824 elsif Is_Array_Type
(T
) then
6825 if Is_Private_Type
(Component_Type
(T
))
6826 and then not Has_Private_View
(N
)
6827 and then Present
(Full_View
(Component_Type
(T
)))
6829 Switch_View
(Component_Type
(T
));
6832 -- The normal exchange mechanism relies on the setting of a
6833 -- flag on the reference in the generic. However, an additional
6834 -- mechanism is needed for types that are not explicitly
6835 -- mentioned in the generic, but may be needed in expanded code
6836 -- in the instance. This includes component types of arrays and
6837 -- designated types of access types. This processing must also
6838 -- include the index types of arrays which we take care of here.
6845 Indx
:= First_Index
(T
);
6846 while Present
(Indx
) loop
6847 Typ
:= Base_Type
(Etype
(Indx
));
6849 if Is_Private_Type
(Typ
)
6850 and then Present
(Full_View
(Typ
))
6859 elsif Is_Private_Type
(T
)
6860 and then Present
(Full_View
(T
))
6861 and then Is_Array_Type
(Full_View
(T
))
6862 and then Is_Private_Type
(Component_Type
(Full_View
(T
)))
6866 -- Finally, a non-private subtype may have a private base type, which
6867 -- must be exchanged for consistency. This can happen when a package
6868 -- body is instantiated, when the scope stack is empty but in fact
6869 -- the subtype and the base type are declared in an enclosing scope.
6871 -- Note that in this case we introduce an inconsistency in the view
6872 -- set, because we switch the base type BT, but there could be some
6873 -- private dependent subtypes of BT which remain unswitched. Such
6874 -- subtypes might need to be switched at a later point (see specific
6875 -- provision for that case in Switch_View).
6877 elsif not Is_Private_Type
(T
)
6878 and then not Has_Private_View
(N
)
6879 and then Is_Private_Type
(BT
)
6880 and then Present
(Full_View
(BT
))
6881 and then not Is_Generic_Type
(BT
)
6882 and then not In_Open_Scopes
(BT
)
6884 Prepend_Elmt
(Full_View
(BT
), Exchanged_Views
);
6885 Exchange_Declarations
(BT
);
6888 end Check_Private_View
;
6890 -----------------------------
6891 -- Check_Hidden_Primitives --
6892 -----------------------------
6894 function Check_Hidden_Primitives
(Assoc_List
: List_Id
) return Elist_Id
is
6897 Result
: Elist_Id
:= No_Elist
;
6900 if No
(Assoc_List
) then
6904 -- Traverse the list of associations between formals and actuals
6905 -- searching for renamings of tagged types
6907 Actual
:= First
(Assoc_List
);
6908 while Present
(Actual
) loop
6909 if Nkind
(Actual
) = N_Subtype_Declaration
then
6910 Gen_T
:= Generic_Parent_Type
(Actual
);
6912 if Present
(Gen_T
) and then Is_Tagged_Type
(Gen_T
) then
6914 -- Traverse the list of primitives of the actual types
6915 -- searching for hidden primitives that are visible in the
6916 -- corresponding generic formal; leave them visible and
6917 -- append them to Result to restore their decoration later.
6919 Install_Hidden_Primitives
6920 (Prims_List
=> Result
,
6922 Act_T
=> Entity
(Subtype_Indication
(Actual
)));
6930 end Check_Hidden_Primitives
;
6932 --------------------------
6933 -- Contains_Instance_Of --
6934 --------------------------
6936 function Contains_Instance_Of
6939 N
: Node_Id
) return Boolean
6947 -- Verify that there are no circular instantiations. We check whether
6948 -- the unit contains an instance of the current scope or some enclosing
6949 -- scope (in case one of the instances appears in a subunit). Longer
6950 -- circularities involving subunits might seem too pathological to
6951 -- consider, but they were not too pathological for the authors of
6952 -- DEC bc30vsq, so we loop over all enclosing scopes, and mark all
6953 -- enclosing generic scopes as containing an instance.
6956 -- Within a generic subprogram body, the scope is not generic, to
6957 -- allow for recursive subprograms. Use the declaration to determine
6958 -- whether this is a generic unit.
6960 if Ekind
(Scop
) = E_Generic_Package
6961 or else (Is_Subprogram
(Scop
)
6962 and then Nkind
(Unit_Declaration_Node
(Scop
)) =
6963 N_Generic_Subprogram_Declaration
)
6965 Elmt
:= First_Elmt
(Inner_Instances
(Inner
));
6967 while Present
(Elmt
) loop
6968 if Node
(Elmt
) = Scop
then
6969 Error_Msg_Node_2
:= Inner
;
6971 ("circular Instantiation: & instantiated within &!",
6975 elsif Node
(Elmt
) = Inner
then
6978 elsif Contains_Instance_Of
(Node
(Elmt
), Scop
, N
) then
6979 Error_Msg_Node_2
:= Inner
;
6981 ("circular Instantiation: & instantiated within &!",
6989 -- Indicate that Inner is being instantiated within Scop
6991 Append_Elmt
(Inner
, Inner_Instances
(Scop
));
6994 if Scop
= Standard_Standard
then
6997 Scop
:= Scope
(Scop
);
7002 end Contains_Instance_Of
;
7004 -----------------------
7005 -- Copy_Generic_Node --
7006 -----------------------
7008 function Copy_Generic_Node
7010 Parent_Id
: Node_Id
;
7011 Instantiating
: Boolean) return Node_Id
7016 function Copy_Generic_Descendant
(D
: Union_Id
) return Union_Id
;
7017 -- Check the given value of one of the Fields referenced by the current
7018 -- node to determine whether to copy it recursively. The field may hold
7019 -- a Node_Id, a List_Id, or an Elist_Id, or a plain value (Sloc, Uint,
7020 -- Char) in which case it need not be copied.
7022 procedure Copy_Descendants
;
7023 -- Common utility for various nodes
7025 function Copy_Generic_Elist
(E
: Elist_Id
) return Elist_Id
;
7026 -- Make copy of element list
7028 function Copy_Generic_List
7030 Parent_Id
: Node_Id
) return List_Id
;
7031 -- Apply Copy_Node recursively to the members of a node list
7033 function In_Defining_Unit_Name
(Nam
: Node_Id
) return Boolean;
7034 -- True if an identifier is part of the defining program unit name of
7035 -- a child unit. The entity of such an identifier must be kept (for
7036 -- ASIS use) even though as the name of an enclosing generic it would
7037 -- otherwise not be preserved in the generic tree.
7039 ----------------------
7040 -- Copy_Descendants --
7041 ----------------------
7043 procedure Copy_Descendants
is
7044 use Atree
.Unchecked_Access
;
7045 -- This code section is part of the implementation of an untyped
7046 -- tree traversal, so it needs direct access to node fields.
7049 Set_Field1
(New_N
, Copy_Generic_Descendant
(Field1
(N
)));
7050 Set_Field2
(New_N
, Copy_Generic_Descendant
(Field2
(N
)));
7051 Set_Field3
(New_N
, Copy_Generic_Descendant
(Field3
(N
)));
7052 Set_Field4
(New_N
, Copy_Generic_Descendant
(Field4
(N
)));
7053 Set_Field5
(New_N
, Copy_Generic_Descendant
(Field5
(N
)));
7054 end Copy_Descendants
;
7056 -----------------------------
7057 -- Copy_Generic_Descendant --
7058 -----------------------------
7060 function Copy_Generic_Descendant
(D
: Union_Id
) return Union_Id
is
7062 if D
= Union_Id
(Empty
) then
7065 elsif D
in Node_Range
then
7067 (Copy_Generic_Node
(Node_Id
(D
), New_N
, Instantiating
));
7069 elsif D
in List_Range
then
7070 return Union_Id
(Copy_Generic_List
(List_Id
(D
), New_N
));
7072 elsif D
in Elist_Range
then
7073 return Union_Id
(Copy_Generic_Elist
(Elist_Id
(D
)));
7075 -- Nothing else is copyable (e.g. Uint values), return as is
7080 end Copy_Generic_Descendant
;
7082 ------------------------
7083 -- Copy_Generic_Elist --
7084 ------------------------
7086 function Copy_Generic_Elist
(E
: Elist_Id
) return Elist_Id
is
7093 M
:= First_Elmt
(E
);
7094 while Present
(M
) loop
7096 (Copy_Generic_Node
(Node
(M
), Empty
, Instantiating
), L
);
7105 end Copy_Generic_Elist
;
7107 -----------------------
7108 -- Copy_Generic_List --
7109 -----------------------
7111 function Copy_Generic_List
7113 Parent_Id
: Node_Id
) return List_Id
7121 Set_Parent
(New_L
, Parent_Id
);
7124 while Present
(N
) loop
7125 Append
(Copy_Generic_Node
(N
, Empty
, Instantiating
), New_L
);
7134 end Copy_Generic_List
;
7136 ---------------------------
7137 -- In_Defining_Unit_Name --
7138 ---------------------------
7140 function In_Defining_Unit_Name
(Nam
: Node_Id
) return Boolean is
7143 Present
(Parent
(Nam
))
7144 and then (Nkind
(Parent
(Nam
)) = N_Defining_Program_Unit_Name
7146 (Nkind
(Parent
(Nam
)) = N_Expanded_Name
7147 and then In_Defining_Unit_Name
(Parent
(Nam
))));
7148 end In_Defining_Unit_Name
;
7150 -- Start of processing for Copy_Generic_Node
7157 New_N
:= New_Copy
(N
);
7159 -- Copy aspects if present
7161 if Has_Aspects
(N
) then
7162 Set_Has_Aspects
(New_N
, False);
7163 Set_Aspect_Specifications
7164 (New_N
, Copy_Generic_List
(Aspect_Specifications
(N
), Parent_Id
));
7167 if Instantiating
then
7168 Adjust_Instantiation_Sloc
(New_N
, S_Adjustment
);
7171 if not Is_List_Member
(N
) then
7172 Set_Parent
(New_N
, Parent_Id
);
7175 -- Special casing for identifiers and other entity names and operators
7177 if Nkind_In
(New_N
, N_Character_Literal
,
7181 or else Nkind
(New_N
) in N_Op
7183 if not Instantiating
then
7185 -- Link both nodes in order to assign subsequently the entity of
7186 -- the copy to the original node, in case this is a global
7189 Set_Associated_Node
(N
, New_N
);
7191 -- If we are within an instantiation, this is a nested generic
7192 -- that has already been analyzed at the point of definition.
7193 -- We must preserve references that were global to the enclosing
7194 -- parent at that point. Other occurrences, whether global or
7195 -- local to the current generic, must be resolved anew, so we
7196 -- reset the entity in the generic copy. A global reference has a
7197 -- smaller depth than the parent, or else the same depth in case
7198 -- both are distinct compilation units.
7200 -- A child unit is implicitly declared within the enclosing parent
7201 -- but is in fact global to it, and must be preserved.
7203 -- It is also possible for Current_Instantiated_Parent to be
7204 -- defined, and for this not to be a nested generic, namely if
7205 -- the unit is loaded through Rtsfind. In that case, the entity of
7206 -- New_N is only a link to the associated node, and not a defining
7209 -- The entities for parent units in the defining_program_unit of a
7210 -- generic child unit are established when the context of the unit
7211 -- is first analyzed, before the generic copy is made. They are
7212 -- preserved in the copy for use in ASIS queries.
7214 Ent
:= Entity
(New_N
);
7216 if No
(Current_Instantiated_Parent
.Gen_Id
) then
7218 or else Nkind
(Ent
) /= N_Defining_Identifier
7219 or else not In_Defining_Unit_Name
(N
)
7221 Set_Associated_Node
(New_N
, Empty
);
7226 not Nkind_In
(Ent
, N_Defining_Identifier
,
7227 N_Defining_Character_Literal
,
7228 N_Defining_Operator_Symbol
)
7229 or else No
(Scope
(Ent
))
7231 (Scope
(Ent
) = Current_Instantiated_Parent
.Gen_Id
7232 and then not Is_Child_Unit
(Ent
))
7234 (Scope_Depth
(Scope
(Ent
)) >
7235 Scope_Depth
(Current_Instantiated_Parent
.Gen_Id
)
7237 Get_Source_Unit
(Ent
) =
7238 Get_Source_Unit
(Current_Instantiated_Parent
.Gen_Id
))
7240 Set_Associated_Node
(New_N
, Empty
);
7243 -- Case of instantiating identifier or some other name or operator
7246 -- If the associated node is still defined, the entity in it
7247 -- is global, and must be copied to the instance. If this copy
7248 -- is being made for a body to inline, it is applied to an
7249 -- instantiated tree, and the entity is already present and
7250 -- must be also preserved.
7253 Assoc
: constant Node_Id
:= Get_Associated_Node
(N
);
7256 if Present
(Assoc
) then
7257 if Nkind
(Assoc
) = Nkind
(N
) then
7258 Set_Entity
(New_N
, Entity
(Assoc
));
7259 Check_Private_View
(N
);
7261 -- The name in the call may be a selected component if the
7262 -- call has not been analyzed yet, as may be the case for
7263 -- pre/post conditions in a generic unit.
7265 elsif Nkind
(Assoc
) = N_Function_Call
7266 and then Is_Entity_Name
(Name
(Assoc
))
7268 Set_Entity
(New_N
, Entity
(Name
(Assoc
)));
7270 elsif Nkind_In
(Assoc
, N_Defining_Identifier
,
7271 N_Defining_Character_Literal
,
7272 N_Defining_Operator_Symbol
)
7273 and then Expander_Active
7275 -- Inlining case: we are copying a tree that contains
7276 -- global entities, which are preserved in the copy to be
7277 -- used for subsequent inlining.
7282 Set_Entity
(New_N
, Empty
);
7288 -- For expanded name, we must copy the Prefix and Selector_Name
7290 if Nkind
(N
) = N_Expanded_Name
then
7292 (New_N
, Copy_Generic_Node
(Prefix
(N
), New_N
, Instantiating
));
7294 Set_Selector_Name
(New_N
,
7295 Copy_Generic_Node
(Selector_Name
(N
), New_N
, Instantiating
));
7297 -- For operators, we must copy the right operand
7299 elsif Nkind
(N
) in N_Op
then
7300 Set_Right_Opnd
(New_N
,
7301 Copy_Generic_Node
(Right_Opnd
(N
), New_N
, Instantiating
));
7303 -- And for binary operators, the left operand as well
7305 if Nkind
(N
) in N_Binary_Op
then
7306 Set_Left_Opnd
(New_N
,
7307 Copy_Generic_Node
(Left_Opnd
(N
), New_N
, Instantiating
));
7311 -- Establish a link between an entity from the generic template and the
7312 -- corresponding entity in the generic copy to be analyzed.
7314 elsif Nkind
(N
) in N_Entity
then
7315 if not Instantiating
then
7316 Set_Associated_Entity
(N
, New_N
);
7319 -- Clear any existing link the copy may inherit from the replicated
7320 -- generic template entity.
7322 Set_Associated_Entity
(New_N
, Empty
);
7324 -- Special casing for stubs
7326 elsif Nkind
(N
) in N_Body_Stub
then
7328 -- In any case, we must copy the specification or defining
7329 -- identifier as appropriate.
7331 if Nkind
(N
) = N_Subprogram_Body_Stub
then
7332 Set_Specification
(New_N
,
7333 Copy_Generic_Node
(Specification
(N
), New_N
, Instantiating
));
7336 Set_Defining_Identifier
(New_N
,
7338 (Defining_Identifier
(N
), New_N
, Instantiating
));
7341 -- If we are not instantiating, then this is where we load and
7342 -- analyze subunits, i.e. at the point where the stub occurs. A
7343 -- more permissive system might defer this analysis to the point
7344 -- of instantiation, but this seems too complicated for now.
7346 if not Instantiating
then
7348 Subunit_Name
: constant Unit_Name_Type
:= Get_Unit_Name
(N
);
7350 Unum
: Unit_Number_Type
;
7354 -- Make sure that, if it is a subunit of the main unit that is
7355 -- preprocessed and if -gnateG is specified, the preprocessed
7356 -- file will be written.
7358 Lib
.Analysing_Subunit_Of_Main
:=
7359 Lib
.In_Extended_Main_Source_Unit
(N
);
7362 (Load_Name
=> Subunit_Name
,
7366 Lib
.Analysing_Subunit_Of_Main
:= False;
7368 -- If the proper body is not found, a warning message will be
7369 -- emitted when analyzing the stub, or later at the point of
7370 -- instantiation. Here we just leave the stub as is.
7372 if Unum
= No_Unit
then
7373 Subunits_Missing
:= True;
7374 goto Subunit_Not_Found
;
7377 Subunit
:= Cunit
(Unum
);
7379 if Nkind
(Unit
(Subunit
)) /= N_Subunit
then
7381 ("found child unit instead of expected SEPARATE subunit",
7383 Error_Msg_Sloc
:= Sloc
(N
);
7384 Error_Msg_N
("\to complete stub #", Subunit
);
7385 goto Subunit_Not_Found
;
7388 -- We must create a generic copy of the subunit, in order to
7389 -- perform semantic analysis on it, and we must replace the
7390 -- stub in the original generic unit with the subunit, in order
7391 -- to preserve non-local references within.
7393 -- Only the proper body needs to be copied. Library_Unit and
7394 -- context clause are simply inherited by the generic copy.
7395 -- Note that the copy (which may be recursive if there are
7396 -- nested subunits) must be done first, before attaching it to
7397 -- the enclosing generic.
7401 (Proper_Body
(Unit
(Subunit
)),
7402 Empty
, Instantiating
=> False);
7404 -- Now place the original proper body in the original generic
7405 -- unit. This is a body, not a compilation unit.
7407 Rewrite
(N
, Proper_Body
(Unit
(Subunit
)));
7408 Set_Is_Compilation_Unit
(Defining_Entity
(N
), False);
7409 Set_Was_Originally_Stub
(N
);
7411 -- Finally replace the body of the subunit with its copy, and
7412 -- make this new subunit into the library unit of the generic
7413 -- copy, which does not have stubs any longer.
7415 Set_Proper_Body
(Unit
(Subunit
), New_Body
);
7416 Set_Library_Unit
(New_N
, Subunit
);
7417 Inherit_Context
(Unit
(Subunit
), N
);
7420 -- If we are instantiating, this must be an error case, since
7421 -- otherwise we would have replaced the stub node by the proper body
7422 -- that corresponds. So just ignore it in the copy (i.e. we have
7423 -- copied it, and that is good enough).
7429 <<Subunit_Not_Found
>> null;
7431 -- If the node is a compilation unit, it is the subunit of a stub, which
7432 -- has been loaded already (see code below). In this case, the library
7433 -- unit field of N points to the parent unit (which is a compilation
7434 -- unit) and need not (and cannot) be copied.
7436 -- When the proper body of the stub is analyzed, the library_unit link
7437 -- is used to establish the proper context (see sem_ch10).
7439 -- The other fields of a compilation unit are copied as usual
7441 elsif Nkind
(N
) = N_Compilation_Unit
then
7443 -- This code can only be executed when not instantiating, because in
7444 -- the copy made for an instantiation, the compilation unit node has
7445 -- disappeared at the point that a stub is replaced by its proper
7448 pragma Assert
(not Instantiating
);
7450 Set_Context_Items
(New_N
,
7451 Copy_Generic_List
(Context_Items
(N
), New_N
));
7454 Copy_Generic_Node
(Unit
(N
), New_N
, False));
7456 Set_First_Inlined_Subprogram
(New_N
,
7458 (First_Inlined_Subprogram
(N
), New_N
, False));
7460 Set_Aux_Decls_Node
(New_N
,
7461 Copy_Generic_Node
(Aux_Decls_Node
(N
), New_N
, False));
7463 -- For an assignment node, the assignment is known to be semantically
7464 -- legal if we are instantiating the template. This avoids incorrect
7465 -- diagnostics in generated code.
7467 elsif Nkind
(N
) = N_Assignment_Statement
then
7469 -- Copy name and expression fields in usual manner
7472 Copy_Generic_Node
(Name
(N
), New_N
, Instantiating
));
7474 Set_Expression
(New_N
,
7475 Copy_Generic_Node
(Expression
(N
), New_N
, Instantiating
));
7477 if Instantiating
then
7478 Set_Assignment_OK
(Name
(New_N
), True);
7481 elsif Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
) then
7482 if not Instantiating
then
7483 Set_Associated_Node
(N
, New_N
);
7486 if Present
(Get_Associated_Node
(N
))
7487 and then Nkind
(Get_Associated_Node
(N
)) = Nkind
(N
)
7489 -- In the generic the aggregate has some composite type. If at
7490 -- the point of instantiation the type has a private view,
7491 -- install the full view (and that of its ancestors, if any).
7494 T
: Entity_Id
:= (Etype
(Get_Associated_Node
(New_N
)));
7498 if Present
(T
) and then Is_Private_Type
(T
) then
7503 and then Is_Tagged_Type
(T
)
7504 and then Is_Derived_Type
(T
)
7506 Rt
:= Root_Type
(T
);
7511 if Is_Private_Type
(T
) then
7522 -- Do not copy the associated node, which points to the generic copy
7523 -- of the aggregate.
7526 use Atree
.Unchecked_Access
;
7527 -- This code section is part of the implementation of an untyped
7528 -- tree traversal, so it needs direct access to node fields.
7531 Set_Field1
(New_N
, Copy_Generic_Descendant
(Field1
(N
)));
7532 Set_Field2
(New_N
, Copy_Generic_Descendant
(Field2
(N
)));
7533 Set_Field3
(New_N
, Copy_Generic_Descendant
(Field3
(N
)));
7534 Set_Field5
(New_N
, Copy_Generic_Descendant
(Field5
(N
)));
7537 -- Allocators do not have an identifier denoting the access type, so we
7538 -- must locate it through the expression to check whether the views are
7541 elsif Nkind
(N
) = N_Allocator
7542 and then Nkind
(Expression
(N
)) = N_Qualified_Expression
7543 and then Is_Entity_Name
(Subtype_Mark
(Expression
(N
)))
7544 and then Instantiating
7547 T
: constant Node_Id
:=
7548 Get_Associated_Node
(Subtype_Mark
(Expression
(N
)));
7554 -- Retrieve the allocator node in the generic copy
7556 Acc_T
:= Etype
(Parent
(Parent
(T
)));
7558 if Present
(Acc_T
) and then Is_Private_Type
(Acc_T
) then
7559 Switch_View
(Acc_T
);
7566 -- For a proper body, we must catch the case of a proper body that
7567 -- replaces a stub. This represents the point at which a separate
7568 -- compilation unit, and hence template file, may be referenced, so we
7569 -- must make a new source instantiation entry for the template of the
7570 -- subunit, and ensure that all nodes in the subunit are adjusted using
7571 -- this new source instantiation entry.
7573 elsif Nkind
(N
) in N_Proper_Body
then
7575 Save_Adjustment
: constant Sloc_Adjustment
:= S_Adjustment
;
7578 if Instantiating
and then Was_Originally_Stub
(N
) then
7579 Create_Instantiation_Source
7580 (Instantiation_Node
,
7581 Defining_Entity
(N
),
7586 -- Now copy the fields of the proper body, using the new
7587 -- adjustment factor if one was needed as per test above.
7591 -- Restore the original adjustment factor in case changed
7593 S_Adjustment
:= Save_Adjustment
;
7596 elsif Nkind
(N
) = N_Pragma
and then Instantiating
then
7598 -- Do not copy Comment or Ident pragmas their content is relevant to
7599 -- the generic unit, not to the instantiating unit.
7601 if Nam_In
(Pragma_Name
(N
), Name_Comment
, Name_Ident
) then
7602 New_N
:= Make_Null_Statement
(Sloc
(N
));
7604 -- Do not copy pragmas generated from aspects because the pragmas do
7605 -- not carry any semantic information, plus they will be regenerated
7608 elsif From_Aspect_Specification
(N
) then
7609 New_N
:= Make_Null_Statement
(Sloc
(N
));
7615 elsif Nkind_In
(N
, N_Integer_Literal
, N_Real_Literal
) then
7617 -- No descendant fields need traversing
7621 elsif Nkind
(N
) = N_String_Literal
7622 and then Present
(Etype
(N
))
7623 and then Instantiating
7625 -- If the string is declared in an outer scope, the string_literal
7626 -- subtype created for it may have the wrong scope. Force reanalysis
7627 -- of the constant to generate a new itype in the proper context.
7629 Set_Etype
(New_N
, Empty
);
7630 Set_Analyzed
(New_N
, False);
7632 -- For the remaining nodes, copy their descendants recursively
7637 if Instantiating
and then Nkind
(N
) = N_Subprogram_Body
then
7638 Set_Generic_Parent
(Specification
(New_N
), N
);
7640 -- Should preserve Corresponding_Spec??? (12.3(14))
7645 end Copy_Generic_Node
;
7647 ----------------------------
7648 -- Denotes_Formal_Package --
7649 ----------------------------
7651 function Denotes_Formal_Package
7653 On_Exit
: Boolean := False;
7654 Instance
: Entity_Id
:= Empty
) return Boolean
7657 Scop
: constant Entity_Id
:= Scope
(Pack
);
7660 function Is_Actual_Of_Previous_Formal
(P
: Entity_Id
) return Boolean;
7661 -- The package in question may be an actual for a previous formal
7662 -- package P of the current instance, so examine its actuals as well.
7663 -- This must be recursive over other formal packages.
7665 ----------------------------------
7666 -- Is_Actual_Of_Previous_Formal --
7667 ----------------------------------
7669 function Is_Actual_Of_Previous_Formal
(P
: Entity_Id
) return Boolean is
7673 E1
:= First_Entity
(P
);
7674 while Present
(E1
) and then E1
/= Instance
loop
7675 if Ekind
(E1
) = E_Package
7676 and then Nkind
(Parent
(E1
)) = N_Package_Renaming_Declaration
7678 if Renamed_Object
(E1
) = Pack
then
7681 elsif E1
= P
or else Renamed_Object
(E1
) = P
then
7684 elsif Is_Actual_Of_Previous_Formal
(E1
) then
7693 end Is_Actual_Of_Previous_Formal
;
7695 -- Start of processing for Denotes_Formal_Package
7701 (Instance_Envs
.Last
).Instantiated_Parent
.Act_Id
;
7703 Par
:= Current_Instantiated_Parent
.Act_Id
;
7706 if Ekind
(Scop
) = E_Generic_Package
7707 or else Nkind
(Unit_Declaration_Node
(Scop
)) =
7708 N_Generic_Subprogram_Declaration
7712 elsif Nkind
(Original_Node
(Unit_Declaration_Node
(Pack
))) =
7713 N_Formal_Package_Declaration
7721 -- Check whether this package is associated with a formal package of
7722 -- the enclosing instantiation. Iterate over the list of renamings.
7724 E
:= First_Entity
(Par
);
7725 while Present
(E
) loop
7726 if Ekind
(E
) /= E_Package
7727 or else Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
7731 elsif Renamed_Object
(E
) = Par
then
7734 elsif Renamed_Object
(E
) = Pack
then
7737 elsif Is_Actual_Of_Previous_Formal
(E
) then
7747 end Denotes_Formal_Package
;
7753 procedure End_Generic
is
7755 -- ??? More things could be factored out in this routine. Should
7756 -- probably be done at a later stage.
7758 Inside_A_Generic
:= Generic_Flags
.Table
(Generic_Flags
.Last
);
7759 Generic_Flags
.Decrement_Last
;
7761 Expander_Mode_Restore
;
7768 function Earlier
(N1
, N2
: Node_Id
) return Boolean is
7769 procedure Find_Depth
(P
: in out Node_Id
; D
: in out Integer);
7770 -- Find distance from given node to enclosing compilation unit
7776 procedure Find_Depth
(P
: in out Node_Id
; D
: in out Integer) is
7779 and then Nkind
(P
) /= N_Compilation_Unit
7781 P
:= True_Parent
(P
);
7786 -- Local declarations
7795 -- Start of processing for Earlier
7798 Find_Depth
(P1
, D1
);
7799 Find_Depth
(P2
, D2
);
7809 P1
:= True_Parent
(P1
);
7814 P2
:= True_Parent
(P2
);
7818 -- At this point P1 and P2 are at the same distance from the root.
7819 -- We examine their parents until we find a common declarative list.
7820 -- If we reach the root, N1 and N2 do not descend from the same
7821 -- declarative list (e.g. one is nested in the declarative part and
7822 -- the other is in a block in the statement part) and the earlier
7823 -- one is already frozen.
7825 while not Is_List_Member
(P1
)
7826 or else not Is_List_Member
(P2
)
7827 or else List_Containing
(P1
) /= List_Containing
(P2
)
7829 P1
:= True_Parent
(P1
);
7830 P2
:= True_Parent
(P2
);
7832 if Nkind
(Parent
(P1
)) = N_Subunit
then
7833 P1
:= Corresponding_Stub
(Parent
(P1
));
7836 if Nkind
(Parent
(P2
)) = N_Subunit
then
7837 P2
:= Corresponding_Stub
(Parent
(P2
));
7845 -- Expanded code usually shares the source location of the original
7846 -- construct it was generated for. This however may not necessarely
7847 -- reflect the true location of the code within the tree.
7849 -- Before comparing the slocs of the two nodes, make sure that we are
7850 -- working with correct source locations. Assume that P1 is to the left
7851 -- of P2. If either one does not come from source, traverse the common
7852 -- list heading towards the other node and locate the first source
7856 -- ----+===+===+--------------+===+===+----
7857 -- expanded code expanded code
7859 if not Comes_From_Source
(P1
) then
7860 while Present
(P1
) loop
7862 -- Neither P2 nor a source statement were located during the
7863 -- search. If we reach the end of the list, then P1 does not
7864 -- occur earlier than P2.
7867 -- start --- P2 ----- P1 --- end
7869 if No
(Next
(P1
)) then
7872 -- We encounter P2 while going to the right of the list. This
7873 -- means that P1 does indeed appear earlier.
7876 -- start --- P1 ===== P2 --- end
7877 -- expanded code in between
7882 -- No need to look any further since we have located a source
7885 elsif Comes_From_Source
(P1
) then
7895 if not Comes_From_Source
(P2
) then
7896 while Present
(P2
) loop
7898 -- Neither P1 nor a source statement were located during the
7899 -- search. If we reach the start of the list, then P1 does not
7900 -- occur earlier than P2.
7903 -- start --- P2 --- P1 --- end
7905 if No
(Prev
(P2
)) then
7908 -- We encounter P1 while going to the left of the list. This
7909 -- means that P1 does indeed appear earlier.
7912 -- start --- P1 ===== P2 --- end
7913 -- expanded code in between
7918 -- No need to look any further since we have located a source
7921 elsif Comes_From_Source
(P2
) then
7931 -- At this point either both nodes came from source or we approximated
7932 -- their source locations through neighbouring source statements.
7934 T1
:= Top_Level_Location
(Sloc
(P1
));
7935 T2
:= Top_Level_Location
(Sloc
(P2
));
7937 -- When two nodes come from the same instance, they have identical top
7938 -- level locations. To determine proper relation within the tree, check
7939 -- their locations within the template.
7942 return Sloc
(P1
) < Sloc
(P2
);
7944 -- The two nodes either come from unrelated instances or do not come
7945 -- from instantiated code at all.
7952 ----------------------
7953 -- Find_Actual_Type --
7954 ----------------------
7956 function Find_Actual_Type
7958 Gen_Type
: Entity_Id
) return Entity_Id
7960 Gen_Scope
: constant Entity_Id
:= Scope
(Gen_Type
);
7964 -- Special processing only applies to child units
7966 if not Is_Child_Unit
(Gen_Scope
) then
7967 return Get_Instance_Of
(Typ
);
7969 -- If designated or component type is itself a formal of the child unit,
7970 -- its instance is available.
7972 elsif Scope
(Typ
) = Gen_Scope
then
7973 return Get_Instance_Of
(Typ
);
7975 -- If the array or access type is not declared in the parent unit,
7976 -- no special processing needed.
7978 elsif not Is_Generic_Type
(Typ
)
7979 and then Scope
(Gen_Scope
) /= Scope
(Typ
)
7981 return Get_Instance_Of
(Typ
);
7983 -- Otherwise, retrieve designated or component type by visibility
7986 T
:= Current_Entity
(Typ
);
7987 while Present
(T
) loop
7988 if In_Open_Scopes
(Scope
(T
)) then
7990 elsif Is_Generic_Actual_Type
(T
) then
7999 end Find_Actual_Type
;
8001 ----------------------------
8002 -- Freeze_Subprogram_Body --
8003 ----------------------------
8005 procedure Freeze_Subprogram_Body
8006 (Inst_Node
: Node_Id
;
8008 Pack_Id
: Entity_Id
)
8010 Gen_Unit
: constant Entity_Id
:= Get_Generic_Entity
(Inst_Node
);
8011 Par
: constant Entity_Id
:= Scope
(Gen_Unit
);
8017 function Enclosing_Package_Body
(N
: Node_Id
) return Node_Id
;
8018 -- Find innermost package body that encloses the given node, and which
8019 -- is not a compilation unit. Freeze nodes for the instance, or for its
8020 -- enclosing body, may be inserted after the enclosing_body of the
8021 -- generic unit. Used to determine proper placement of freeze node for
8022 -- both package and subprogram instances.
8024 function Package_Freeze_Node
(B
: Node_Id
) return Node_Id
;
8025 -- Find entity for given package body, and locate or create a freeze
8028 ----------------------------
8029 -- Enclosing_Package_Body --
8030 ----------------------------
8032 function Enclosing_Package_Body
(N
: Node_Id
) return Node_Id
is
8038 and then Nkind
(Parent
(P
)) /= N_Compilation_Unit
8040 if Nkind
(P
) = N_Package_Body
then
8041 if Nkind
(Parent
(P
)) = N_Subunit
then
8042 return Corresponding_Stub
(Parent
(P
));
8048 P
:= True_Parent
(P
);
8052 end Enclosing_Package_Body
;
8054 -------------------------
8055 -- Package_Freeze_Node --
8056 -------------------------
8058 function Package_Freeze_Node
(B
: Node_Id
) return Node_Id
is
8062 if Nkind
(B
) = N_Package_Body
then
8063 Id
:= Corresponding_Spec
(B
);
8064 else pragma Assert
(Nkind
(B
) = N_Package_Body_Stub
);
8065 Id
:= Corresponding_Spec
(Proper_Body
(Unit
(Library_Unit
(B
))));
8068 Ensure_Freeze_Node
(Id
);
8069 return Freeze_Node
(Id
);
8070 end Package_Freeze_Node
;
8072 -- Start of processing of Freeze_Subprogram_Body
8075 -- If the instance and the generic body appear within the same unit, and
8076 -- the instance precedes the generic, the freeze node for the instance
8077 -- must appear after that of the generic. If the generic is nested
8078 -- within another instance I2, then current instance must be frozen
8079 -- after I2. In both cases, the freeze nodes are those of enclosing
8080 -- packages. Otherwise, the freeze node is placed at the end of the
8081 -- current declarative part.
8083 Enc_G
:= Enclosing_Package_Body
(Gen_Body
);
8084 Enc_I
:= Enclosing_Package_Body
(Inst_Node
);
8085 Ensure_Freeze_Node
(Pack_Id
);
8086 F_Node
:= Freeze_Node
(Pack_Id
);
8088 if Is_Generic_Instance
(Par
)
8089 and then Present
(Freeze_Node
(Par
))
8090 and then In_Same_Declarative_Part
(Freeze_Node
(Par
), Inst_Node
)
8092 -- The parent was a premature instantiation. Insert freeze node at
8093 -- the end the current declarative part.
8095 if ABE_Is_Certain
(Get_Package_Instantiation_Node
(Par
)) then
8096 Insert_Freeze_Node_For_Instance
(Inst_Node
, F_Node
);
8098 -- Handle the following case:
8100 -- package Parent_Inst is new ...
8103 -- procedure P ... -- this body freezes Parent_Inst
8105 -- package Inst is new ...
8107 -- In this particular scenario, the freeze node for Inst must be
8108 -- inserted in the same manner as that of Parent_Inst - before the
8109 -- next source body or at the end of the declarative list (body not
8110 -- available). If body P did not exist and Parent_Inst was frozen
8111 -- after Inst, either by a body following Inst or at the end of the
8112 -- declarative region, the freeze node for Inst must be inserted
8113 -- after that of Parent_Inst. This relation is established by
8114 -- comparing the Slocs of Parent_Inst freeze node and Inst.
8116 elsif List_Containing
(Get_Package_Instantiation_Node
(Par
)) =
8117 List_Containing
(Inst_Node
)
8118 and then Sloc
(Freeze_Node
(Par
)) < Sloc
(Inst_Node
)
8120 Insert_Freeze_Node_For_Instance
(Inst_Node
, F_Node
);
8123 Insert_After
(Freeze_Node
(Par
), F_Node
);
8126 -- The body enclosing the instance should be frozen after the body that
8127 -- includes the generic, because the body of the instance may make
8128 -- references to entities therein. If the two are not in the same
8129 -- declarative part, or if the one enclosing the instance is frozen
8130 -- already, freeze the instance at the end of the current declarative
8133 elsif Is_Generic_Instance
(Par
)
8134 and then Present
(Freeze_Node
(Par
))
8135 and then Present
(Enc_I
)
8137 if In_Same_Declarative_Part
(Freeze_Node
(Par
), Enc_I
)
8139 (Nkind
(Enc_I
) = N_Package_Body
8141 In_Same_Declarative_Part
(Freeze_Node
(Par
), Parent
(Enc_I
)))
8143 -- The enclosing package may contain several instances. Rather
8144 -- than computing the earliest point at which to insert its freeze
8145 -- node, we place it at the end of the declarative part of the
8146 -- parent of the generic.
8148 Insert_Freeze_Node_For_Instance
8149 (Freeze_Node
(Par
), Package_Freeze_Node
(Enc_I
));
8152 Insert_Freeze_Node_For_Instance
(Inst_Node
, F_Node
);
8154 elsif Present
(Enc_G
)
8155 and then Present
(Enc_I
)
8156 and then Enc_G
/= Enc_I
8157 and then Earlier
(Inst_Node
, Gen_Body
)
8159 if Nkind
(Enc_G
) = N_Package_Body
then
8161 Corresponding_Spec
(Enc_G
);
8162 else pragma Assert
(Nkind
(Enc_G
) = N_Package_Body_Stub
);
8164 Corresponding_Spec
(Proper_Body
(Unit
(Library_Unit
(Enc_G
))));
8167 -- Freeze package that encloses instance, and place node after the
8168 -- package that encloses generic. If enclosing package is already
8169 -- frozen we have to assume it is at the proper place. This may be a
8170 -- potential ABE that requires dynamic checking. Do not add a freeze
8171 -- node if the package that encloses the generic is inside the body
8172 -- that encloses the instance, because the freeze node would be in
8173 -- the wrong scope. Additional contortions needed if the bodies are
8174 -- within a subunit.
8177 Enclosing_Body
: Node_Id
;
8180 if Nkind
(Enc_I
) = N_Package_Body_Stub
then
8181 Enclosing_Body
:= Proper_Body
(Unit
(Library_Unit
(Enc_I
)));
8183 Enclosing_Body
:= Enc_I
;
8186 if Parent
(List_Containing
(Enc_G
)) /= Enclosing_Body
then
8187 Insert_Freeze_Node_For_Instance
8188 (Enc_G
, Package_Freeze_Node
(Enc_I
));
8192 -- Freeze enclosing subunit before instance
8194 Ensure_Freeze_Node
(E_G_Id
);
8196 if not Is_List_Member
(Freeze_Node
(E_G_Id
)) then
8197 Insert_After
(Enc_G
, Freeze_Node
(E_G_Id
));
8200 Insert_Freeze_Node_For_Instance
(Inst_Node
, F_Node
);
8203 -- If none of the above, insert freeze node at the end of the current
8204 -- declarative part.
8206 Insert_Freeze_Node_For_Instance
(Inst_Node
, F_Node
);
8208 end Freeze_Subprogram_Body
;
8214 function Get_Gen_Id
(E
: Assoc_Ptr
) return Entity_Id
is
8216 return Generic_Renamings
.Table
(E
).Gen_Id
;
8219 ---------------------
8220 -- Get_Instance_Of --
8221 ---------------------
8223 function Get_Instance_Of
(A
: Entity_Id
) return Entity_Id
is
8224 Res
: constant Assoc_Ptr
:= Generic_Renamings_HTable
.Get
(A
);
8227 if Res
/= Assoc_Null
then
8228 return Generic_Renamings
.Table
(Res
).Act_Id
;
8231 -- On exit, entity is not instantiated: not a generic parameter, or
8232 -- else parameter of an inner generic unit.
8236 end Get_Instance_Of
;
8238 ------------------------------------
8239 -- Get_Package_Instantiation_Node --
8240 ------------------------------------
8242 function Get_Package_Instantiation_Node
(A
: Entity_Id
) return Node_Id
is
8243 Decl
: Node_Id
:= Unit_Declaration_Node
(A
);
8247 -- If the Package_Instantiation attribute has been set on the package
8248 -- entity, then use it directly when it (or its Original_Node) refers
8249 -- to an N_Package_Instantiation node. In principle it should be
8250 -- possible to have this field set in all cases, which should be
8251 -- investigated, and would allow this function to be significantly
8254 Inst
:= Package_Instantiation
(A
);
8256 if Present
(Inst
) then
8257 if Nkind
(Inst
) = N_Package_Instantiation
then
8260 elsif Nkind
(Original_Node
(Inst
)) = N_Package_Instantiation
then
8261 return Original_Node
(Inst
);
8265 -- If the instantiation is a compilation unit that does not need body
8266 -- then the instantiation node has been rewritten as a package
8267 -- declaration for the instance, and we return the original node.
8269 -- If it is a compilation unit and the instance node has not been
8270 -- rewritten, then it is still the unit of the compilation. Finally, if
8271 -- a body is present, this is a parent of the main unit whose body has
8272 -- been compiled for inlining purposes, and the instantiation node has
8273 -- been rewritten with the instance body.
8275 -- Otherwise the instantiation node appears after the declaration. If
8276 -- the entity is a formal package, the declaration may have been
8277 -- rewritten as a generic declaration (in the case of a formal with box)
8278 -- or left as a formal package declaration if it has actuals, and is
8279 -- found with a forward search.
8281 if Nkind
(Parent
(Decl
)) = N_Compilation_Unit
then
8282 if Nkind
(Decl
) = N_Package_Declaration
8283 and then Present
(Corresponding_Body
(Decl
))
8285 Decl
:= Unit_Declaration_Node
(Corresponding_Body
(Decl
));
8288 if Nkind
(Original_Node
(Decl
)) = N_Package_Instantiation
then
8289 return Original_Node
(Decl
);
8291 return Unit
(Parent
(Decl
));
8294 elsif Nkind
(Decl
) = N_Package_Declaration
8295 and then Nkind
(Original_Node
(Decl
)) = N_Formal_Package_Declaration
8297 return Original_Node
(Decl
);
8300 Inst
:= Next
(Decl
);
8301 while not Nkind_In
(Inst
, N_Package_Instantiation
,
8302 N_Formal_Package_Declaration
)
8309 end Get_Package_Instantiation_Node
;
8311 ------------------------
8312 -- Has_Been_Exchanged --
8313 ------------------------
8315 function Has_Been_Exchanged
(E
: Entity_Id
) return Boolean is
8319 Next
:= First_Elmt
(Exchanged_Views
);
8320 while Present
(Next
) loop
8321 if Full_View
(Node
(Next
)) = E
then
8329 end Has_Been_Exchanged
;
8335 function Hash
(F
: Entity_Id
) return HTable_Range
is
8337 return HTable_Range
(F
mod HTable_Size
);
8340 ------------------------
8341 -- Hide_Current_Scope --
8342 ------------------------
8344 procedure Hide_Current_Scope
is
8345 C
: constant Entity_Id
:= Current_Scope
;
8349 Set_Is_Hidden_Open_Scope
(C
);
8351 E
:= First_Entity
(C
);
8352 while Present
(E
) loop
8353 if Is_Immediately_Visible
(E
) then
8354 Set_Is_Immediately_Visible
(E
, False);
8355 Append_Elmt
(E
, Hidden_Entities
);
8361 -- Make the scope name invisible as well. This is necessary, but might
8362 -- conflict with calls to Rtsfind later on, in case the scope is a
8363 -- predefined one. There is no clean solution to this problem, so for
8364 -- now we depend on the user not redefining Standard itself in one of
8365 -- the parent units.
8367 if Is_Immediately_Visible
(C
) and then C
/= Standard_Standard
then
8368 Set_Is_Immediately_Visible
(C
, False);
8369 Append_Elmt
(C
, Hidden_Entities
);
8372 end Hide_Current_Scope
;
8378 procedure Init_Env
is
8379 Saved
: Instance_Env
;
8382 Saved
.Instantiated_Parent
:= Current_Instantiated_Parent
;
8383 Saved
.Exchanged_Views
:= Exchanged_Views
;
8384 Saved
.Hidden_Entities
:= Hidden_Entities
;
8385 Saved
.Current_Sem_Unit
:= Current_Sem_Unit
;
8386 Saved
.Parent_Unit_Visible
:= Parent_Unit_Visible
;
8387 Saved
.Instance_Parent_Unit
:= Instance_Parent_Unit
;
8389 -- Save configuration switches. These may be reset if the unit is a
8390 -- predefined unit, and the current mode is not Ada 2005.
8392 Save_Opt_Config_Switches
(Saved
.Switches
);
8394 Instance_Envs
.Append
(Saved
);
8396 Exchanged_Views
:= New_Elmt_List
;
8397 Hidden_Entities
:= New_Elmt_List
;
8399 -- Make dummy entry for Instantiated parent. If generic unit is legal,
8400 -- this is set properly in Set_Instance_Env.
8402 Current_Instantiated_Parent
:=
8403 (Current_Scope
, Current_Scope
, Assoc_Null
);
8406 ------------------------------
8407 -- In_Same_Declarative_Part --
8408 ------------------------------
8410 function In_Same_Declarative_Part
8412 Inst
: Node_Id
) return Boolean
8414 Decls
: constant Node_Id
:= Parent
(F_Node
);
8418 Nod
:= Parent
(Inst
);
8419 while Present
(Nod
) loop
8423 elsif Nkind_In
(Nod
, N_Subprogram_Body
,
8425 N_Package_Declaration
,
8432 elsif Nkind
(Nod
) = N_Subunit
then
8433 Nod
:= Corresponding_Stub
(Nod
);
8435 elsif Nkind
(Nod
) = N_Compilation_Unit
then
8439 Nod
:= Parent
(Nod
);
8444 end In_Same_Declarative_Part
;
8446 ---------------------
8447 -- In_Main_Context --
8448 ---------------------
8450 function In_Main_Context
(E
: Entity_Id
) return Boolean is
8456 if not Is_Compilation_Unit
(E
)
8457 or else Ekind
(E
) /= E_Package
8458 or else In_Private_Part
(E
)
8463 Context
:= Context_Items
(Cunit
(Main_Unit
));
8465 Clause
:= First
(Context
);
8466 while Present
(Clause
) loop
8467 if Nkind
(Clause
) = N_With_Clause
then
8468 Nam
:= Name
(Clause
);
8470 -- If the current scope is part of the context of the main unit,
8471 -- analysis of the corresponding with_clause is not complete, and
8472 -- the entity is not set. We use the Chars field directly, which
8473 -- might produce false positives in rare cases, but guarantees
8474 -- that we produce all the instance bodies we will need.
8476 if (Is_Entity_Name
(Nam
) and then Chars
(Nam
) = Chars
(E
))
8477 or else (Nkind
(Nam
) = N_Selected_Component
8478 and then Chars
(Selector_Name
(Nam
)) = Chars
(E
))
8488 end In_Main_Context
;
8490 ---------------------
8491 -- Inherit_Context --
8492 ---------------------
8494 procedure Inherit_Context
(Gen_Decl
: Node_Id
; Inst
: Node_Id
) is
8495 Current_Context
: List_Id
;
8496 Current_Unit
: Node_Id
;
8505 if Nkind
(Parent
(Gen_Decl
)) = N_Compilation_Unit
then
8507 -- The inherited context is attached to the enclosing compilation
8508 -- unit. This is either the main unit, or the declaration for the
8509 -- main unit (in case the instantiation appears within the package
8510 -- declaration and the main unit is its body).
8512 Current_Unit
:= Parent
(Inst
);
8513 while Present
(Current_Unit
)
8514 and then Nkind
(Current_Unit
) /= N_Compilation_Unit
8516 Current_Unit
:= Parent
(Current_Unit
);
8519 Current_Context
:= Context_Items
(Current_Unit
);
8521 Item
:= First
(Context_Items
(Parent
(Gen_Decl
)));
8522 while Present
(Item
) loop
8523 if Nkind
(Item
) = N_With_Clause
then
8524 Lib_Unit
:= Library_Unit
(Item
);
8526 -- Take care to prevent direct cyclic with's
8528 if Lib_Unit
/= Current_Unit
then
8530 -- Do not add a unit if it is already in the context
8532 Clause
:= First
(Current_Context
);
8534 while Present
(Clause
) loop
8535 if Nkind
(Clause
) = N_With_Clause
and then
8536 Library_Unit
(Clause
) = Lib_Unit
8546 New_I
:= New_Copy
(Item
);
8547 Set_Implicit_With
(New_I
, True);
8548 Set_Implicit_With_From_Instantiation
(New_I
, True);
8549 Append
(New_I
, Current_Context
);
8557 end Inherit_Context
;
8563 procedure Initialize
is
8565 Generic_Renamings
.Init
;
8568 Generic_Renamings_HTable
.Reset
;
8569 Circularity_Detected
:= False;
8570 Exchanged_Views
:= No_Elist
;
8571 Hidden_Entities
:= No_Elist
;
8574 -------------------------------------
8575 -- Insert_Freeze_Node_For_Instance --
8576 -------------------------------------
8578 procedure Insert_Freeze_Node_For_Instance
8587 function Enclosing_Body
(N
: Node_Id
) return Node_Id
;
8588 -- Find enclosing package or subprogram body, if any. Freeze node may
8589 -- be placed at end of current declarative list if previous instance
8590 -- and current one have different enclosing bodies.
8592 function Previous_Instance
(Gen
: Entity_Id
) return Entity_Id
;
8593 -- Find the local instance, if any, that declares the generic that is
8594 -- being instantiated. If present, the freeze node for this instance
8595 -- must follow the freeze node for the previous instance.
8597 --------------------
8598 -- Enclosing_Body --
8599 --------------------
8601 function Enclosing_Body
(N
: Node_Id
) return Node_Id
is
8607 and then Nkind
(Parent
(P
)) /= N_Compilation_Unit
8609 if Nkind_In
(P
, N_Package_Body
, N_Subprogram_Body
) then
8610 if Nkind
(Parent
(P
)) = N_Subunit
then
8611 return Corresponding_Stub
(Parent
(P
));
8617 P
:= True_Parent
(P
);
8623 -----------------------
8624 -- Previous_Instance --
8625 -----------------------
8627 function Previous_Instance
(Gen
: Entity_Id
) return Entity_Id
is
8632 while Present
(S
) and then S
/= Standard_Standard
loop
8633 if Is_Generic_Instance
(S
)
8634 and then In_Same_Source_Unit
(S
, N
)
8643 end Previous_Instance
;
8645 -- Start of processing for Insert_Freeze_Node_For_Instance
8648 if not Is_List_Member
(F_Node
) then
8650 Decls
:= List_Containing
(N
);
8651 Inst
:= Entity
(F_Node
);
8652 Par_N
:= Parent
(Decls
);
8654 -- When processing a subprogram instantiation, utilize the actual
8655 -- subprogram instantiation rather than its package wrapper as it
8656 -- carries all the context information.
8658 if Is_Wrapper_Package
(Inst
) then
8659 Inst
:= Related_Instance
(Inst
);
8662 -- If this is a package instance, check whether the generic is
8663 -- declared in a previous instance and the current instance is
8664 -- not within the previous one.
8666 if Present
(Generic_Parent
(Parent
(Inst
)))
8667 and then Is_In_Main_Unit
(N
)
8670 Enclosing_N
: constant Node_Id
:= Enclosing_Body
(N
);
8671 Par_I
: constant Entity_Id
:=
8673 (Generic_Parent
(Parent
(Inst
)));
8678 and then Earlier
(N
, Freeze_Node
(Par_I
))
8680 Scop
:= Scope
(Inst
);
8682 -- If the current instance is within the one that contains
8683 -- the generic, the freeze node for the current one must
8684 -- appear in the current declarative part. Ditto, if the
8685 -- current instance is within another package instance or
8686 -- within a body that does not enclose the current instance.
8687 -- In these three cases the freeze node of the previous
8688 -- instance is not relevant.
8690 while Present
(Scop
) and then Scop
/= Standard_Standard
loop
8691 exit when Scop
= Par_I
8693 (Is_Generic_Instance
(Scop
)
8694 and then Scope_Depth
(Scop
) > Scope_Depth
(Par_I
));
8695 Scop
:= Scope
(Scop
);
8698 -- Previous instance encloses current instance
8700 if Scop
= Par_I
then
8703 -- If the next node is a source body we must freeze in
8704 -- the current scope as well.
8706 elsif Present
(Next
(N
))
8707 and then Nkind_In
(Next
(N
), N_Subprogram_Body
,
8709 and then Comes_From_Source
(Next
(N
))
8713 -- Current instance is within an unrelated instance
8715 elsif Is_Generic_Instance
(Scop
) then
8718 -- Current instance is within an unrelated body
8720 elsif Present
(Enclosing_N
)
8721 and then Enclosing_N
/= Enclosing_Body
(Par_I
)
8726 Insert_After
(Freeze_Node
(Par_I
), F_Node
);
8733 -- When the instantiation occurs in a package declaration, append the
8734 -- freeze node to the private declarations (if any).
8736 if Nkind
(Par_N
) = N_Package_Specification
8737 and then Decls
= Visible_Declarations
(Par_N
)
8738 and then Present
(Private_Declarations
(Par_N
))
8739 and then not Is_Empty_List
(Private_Declarations
(Par_N
))
8741 Decls
:= Private_Declarations
(Par_N
);
8742 Decl
:= First
(Decls
);
8745 -- Determine the proper freeze point of a package instantiation. We
8746 -- adhere to the general rule of a package or subprogram body causing
8747 -- freezing of anything before it in the same declarative region. In
8748 -- this case, the proper freeze point of a package instantiation is
8749 -- before the first source body which follows, or before a stub. This
8750 -- ensures that entities coming from the instance are already frozen
8751 -- and usable in source bodies.
8753 if Nkind
(Par_N
) /= N_Package_Declaration
8754 and then Ekind
(Inst
) = E_Package
8755 and then Is_Generic_Instance
(Inst
)
8757 not In_Same_Source_Unit
(Generic_Parent
(Parent
(Inst
)), Inst
)
8759 while Present
(Decl
) loop
8760 if (Nkind
(Decl
) in N_Unit_Body
8762 Nkind
(Decl
) in N_Body_Stub
)
8763 and then Comes_From_Source
(Decl
)
8765 Insert_Before
(Decl
, F_Node
);
8773 -- In a package declaration, or if no previous body, insert at end
8776 Set_Sloc
(F_Node
, Sloc
(Last
(Decls
)));
8777 Insert_After
(Last
(Decls
), F_Node
);
8779 end Insert_Freeze_Node_For_Instance
;
8785 procedure Install_Body
8786 (Act_Body
: Node_Id
;
8791 Act_Id
: constant Entity_Id
:= Corresponding_Spec
(Act_Body
);
8792 Act_Unit
: constant Node_Id
:= Unit
(Cunit
(Get_Source_Unit
(N
)));
8793 Gen_Id
: constant Entity_Id
:= Corresponding_Spec
(Gen_Body
);
8794 Par
: constant Entity_Id
:= Scope
(Gen_Id
);
8795 Gen_Unit
: constant Node_Id
:=
8796 Unit
(Cunit
(Get_Source_Unit
(Gen_Decl
)));
8797 Orig_Body
: Node_Id
:= Gen_Body
;
8799 Body_Unit
: Node_Id
;
8801 Must_Delay
: Boolean;
8803 function In_Same_Enclosing_Subp
return Boolean;
8804 -- Check whether instance and generic body are within same subprogram.
8806 function True_Sloc
(N
: Node_Id
) return Source_Ptr
;
8807 -- If the instance is nested inside a generic unit, the Sloc of the
8808 -- instance indicates the place of the original definition, not the
8809 -- point of the current enclosing instance. Pending a better usage of
8810 -- Slocs to indicate instantiation places, we determine the place of
8811 -- origin of a node by finding the maximum sloc of any ancestor node.
8812 -- Why is this not equivalent to Top_Level_Location ???
8814 ----------------------------
8815 -- In_Same_Enclosing_Subp --
8816 ----------------------------
8818 function In_Same_Enclosing_Subp
return Boolean is
8823 Scop
:= Scope
(Act_Id
);
8824 while Scop
/= Standard_Standard
8825 and then not Is_Overloadable
(Scop
)
8827 Scop
:= Scope
(Scop
);
8830 if Scop
= Standard_Standard
then
8836 Scop
:= Scope
(Gen_Id
);
8837 while Scop
/= Standard_Standard
loop
8841 Scop
:= Scope
(Scop
);
8846 end In_Same_Enclosing_Subp
;
8852 function True_Sloc
(N
: Node_Id
) return Source_Ptr
is
8859 while Present
(N1
) and then N1
/= Act_Unit
loop
8860 if Sloc
(N1
) > Res
then
8870 -- Start of processing for Install_Body
8873 -- Handle first the case of an instance with incomplete actual types.
8874 -- The instance body cannot be placed after the declaration because
8875 -- full views have not been seen yet. Any use of the non-limited views
8876 -- in the instance body requires the presence of a regular with_clause
8877 -- in the enclosing unit, and will fail if this with_clause is missing.
8878 -- We place the instance body at the beginning of the enclosing body,
8879 -- which is the unit being compiled. The freeze node for the instance
8880 -- is then placed after the instance body.
8882 if not Is_Empty_Elmt_List
(Incomplete_Actuals
(Act_Id
))
8883 and then Expander_Active
8884 and then Ekind
(Scope
(Act_Id
)) = E_Package
8887 Scop
: constant Entity_Id
:= Scope
(Act_Id
);
8888 Body_Id
: constant Node_Id
:=
8889 Corresponding_Body
(Unit_Declaration_Node
(Scop
));
8892 Ensure_Freeze_Node
(Act_Id
);
8893 F_Node
:= Freeze_Node
(Act_Id
);
8894 if Present
(Body_Id
) then
8895 Set_Is_Frozen
(Act_Id
, False);
8896 Prepend
(Act_Body
, Declarations
(Parent
(Body_Id
)));
8897 if Is_List_Member
(F_Node
) then
8901 Insert_After
(Act_Body
, F_Node
);
8907 -- If the body is a subunit, the freeze point is the corresponding stub
8908 -- in the current compilation, not the subunit itself.
8910 if Nkind
(Parent
(Gen_Body
)) = N_Subunit
then
8911 Orig_Body
:= Corresponding_Stub
(Parent
(Gen_Body
));
8913 Orig_Body
:= Gen_Body
;
8916 Body_Unit
:= Unit
(Cunit
(Get_Source_Unit
(Orig_Body
)));
8918 -- If the instantiation and the generic definition appear in the same
8919 -- package declaration, this is an early instantiation. If they appear
8920 -- in the same declarative part, it is an early instantiation only if
8921 -- the generic body appears textually later, and the generic body is
8922 -- also in the main unit.
8924 -- If instance is nested within a subprogram, and the generic body
8925 -- is not, the instance is delayed because the enclosing body is. If
8926 -- instance and body are within the same scope, or the same subprogram
8927 -- body, indicate explicitly that the instance is delayed.
8930 (Gen_Unit
= Act_Unit
8931 and then (Nkind_In
(Gen_Unit
, N_Package_Declaration
,
8932 N_Generic_Package_Declaration
)
8933 or else (Gen_Unit
= Body_Unit
8934 and then True_Sloc
(N
) < Sloc
(Orig_Body
)))
8935 and then Is_In_Main_Unit
(Gen_Unit
)
8936 and then (Scope
(Act_Id
) = Scope
(Gen_Id
)
8937 or else In_Same_Enclosing_Subp
));
8939 -- If this is an early instantiation, the freeze node is placed after
8940 -- the generic body. Otherwise, if the generic appears in an instance,
8941 -- we cannot freeze the current instance until the outer one is frozen.
8942 -- This is only relevant if the current instance is nested within some
8943 -- inner scope not itself within the outer instance. If this scope is
8944 -- a package body in the same declarative part as the outer instance,
8945 -- then that body needs to be frozen after the outer instance. Finally,
8946 -- if no delay is needed, we place the freeze node at the end of the
8947 -- current declarative part.
8949 if Expander_Active
then
8950 Ensure_Freeze_Node
(Act_Id
);
8951 F_Node
:= Freeze_Node
(Act_Id
);
8954 Insert_After
(Orig_Body
, F_Node
);
8956 elsif Is_Generic_Instance
(Par
)
8957 and then Present
(Freeze_Node
(Par
))
8958 and then Scope
(Act_Id
) /= Par
8960 -- Freeze instance of inner generic after instance of enclosing
8963 if In_Same_Declarative_Part
(Freeze_Node
(Par
), N
) then
8965 -- Handle the following case:
8967 -- package Parent_Inst is new ...
8970 -- procedure P ... -- this body freezes Parent_Inst
8972 -- package Inst is new ...
8974 -- In this particular scenario, the freeze node for Inst must
8975 -- be inserted in the same manner as that of Parent_Inst,
8976 -- before the next source body or at the end of the declarative
8977 -- list (body not available). If body P did not exist and
8978 -- Parent_Inst was frozen after Inst, either by a body
8979 -- following Inst or at the end of the declarative region,
8980 -- the freeze node for Inst must be inserted after that of
8981 -- Parent_Inst. This relation is established by comparing
8982 -- the Slocs of Parent_Inst freeze node and Inst.
8984 if List_Containing
(Get_Package_Instantiation_Node
(Par
)) =
8986 and then Sloc
(Freeze_Node
(Par
)) < Sloc
(N
)
8988 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
8990 Insert_After
(Freeze_Node
(Par
), F_Node
);
8993 -- Freeze package enclosing instance of inner generic after
8994 -- instance of enclosing generic.
8996 elsif Nkind_In
(Parent
(N
), N_Package_Body
, N_Subprogram_Body
)
8997 and then In_Same_Declarative_Part
(Freeze_Node
(Par
), Parent
(N
))
9000 Enclosing
: Entity_Id
;
9003 Enclosing
:= Corresponding_Spec
(Parent
(N
));
9005 if No
(Enclosing
) then
9006 Enclosing
:= Defining_Entity
(Parent
(N
));
9009 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9010 Ensure_Freeze_Node
(Enclosing
);
9012 if not Is_List_Member
(Freeze_Node
(Enclosing
)) then
9014 -- The enclosing context is a subunit, insert the freeze
9015 -- node after the stub.
9017 if Nkind
(Parent
(Parent
(N
))) = N_Subunit
then
9018 Insert_Freeze_Node_For_Instance
9019 (Corresponding_Stub
(Parent
(Parent
(N
))),
9020 Freeze_Node
(Enclosing
));
9022 -- The enclosing context is a package with a stub body
9023 -- which has already been replaced by the real body.
9024 -- Insert the freeze node after the actual body.
9026 elsif Ekind
(Enclosing
) = E_Package
9027 and then Present
(Body_Entity
(Enclosing
))
9028 and then Was_Originally_Stub
9029 (Parent
(Body_Entity
(Enclosing
)))
9031 Insert_Freeze_Node_For_Instance
9032 (Parent
(Body_Entity
(Enclosing
)),
9033 Freeze_Node
(Enclosing
));
9035 -- The parent instance has been frozen before the body of
9036 -- the enclosing package, insert the freeze node after
9039 elsif List_Containing
(Freeze_Node
(Par
)) =
9040 List_Containing
(Parent
(N
))
9041 and then Sloc
(Freeze_Node
(Par
)) < Sloc
(Parent
(N
))
9043 Insert_Freeze_Node_For_Instance
9044 (Parent
(N
), Freeze_Node
(Enclosing
));
9048 (Freeze_Node
(Par
), Freeze_Node
(Enclosing
));
9054 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9058 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9062 Set_Is_Frozen
(Act_Id
);
9063 Insert_Before
(N
, Act_Body
);
9064 Mark_Rewrite_Insertion
(Act_Body
);
9067 -----------------------------
9068 -- Install_Formal_Packages --
9069 -----------------------------
9071 procedure Install_Formal_Packages
(Par
: Entity_Id
) is
9074 Gen_E
: Entity_Id
:= Empty
;
9077 E
:= First_Entity
(Par
);
9079 -- If we are installing an instance parent, locate the formal packages
9080 -- of its generic parent.
9082 if Is_Generic_Instance
(Par
) then
9083 Gen
:= Generic_Parent
(Package_Specification
(Par
));
9084 Gen_E
:= First_Entity
(Gen
);
9087 while Present
(E
) loop
9088 if Ekind
(E
) = E_Package
9089 and then Nkind
(Parent
(E
)) = N_Package_Renaming_Declaration
9091 -- If this is the renaming for the parent instance, done
9093 if Renamed_Object
(E
) = Par
then
9096 -- The visibility of a formal of an enclosing generic is already
9099 elsif Denotes_Formal_Package
(E
) then
9102 elsif Present
(Associated_Formal_Package
(E
)) then
9103 Check_Generic_Actuals
(Renamed_Object
(E
), True);
9104 Set_Is_Hidden
(E
, False);
9106 -- Find formal package in generic unit that corresponds to
9107 -- (instance of) formal package in instance.
9109 while Present
(Gen_E
) and then Chars
(Gen_E
) /= Chars
(E
) loop
9110 Next_Entity
(Gen_E
);
9113 if Present
(Gen_E
) then
9114 Map_Formal_Package_Entities
(Gen_E
, E
);
9121 if Present
(Gen_E
) then
9122 Next_Entity
(Gen_E
);
9125 end Install_Formal_Packages
;
9127 --------------------
9128 -- Install_Parent --
9129 --------------------
9131 procedure Install_Parent
(P
: Entity_Id
; In_Body
: Boolean := False) is
9132 Ancestors
: constant Elist_Id
:= New_Elmt_List
;
9133 S
: constant Entity_Id
:= Current_Scope
;
9134 Inst_Par
: Entity_Id
;
9135 First_Par
: Entity_Id
;
9136 Inst_Node
: Node_Id
;
9137 Gen_Par
: Entity_Id
;
9138 First_Gen
: Entity_Id
;
9141 procedure Install_Noninstance_Specs
(Par
: Entity_Id
);
9142 -- Install the scopes of noninstance parent units ending with Par
9144 procedure Install_Spec
(Par
: Entity_Id
);
9145 -- The child unit is within the declarative part of the parent, so the
9146 -- declarations within the parent are immediately visible.
9148 -------------------------------
9149 -- Install_Noninstance_Specs --
9150 -------------------------------
9152 procedure Install_Noninstance_Specs
(Par
: Entity_Id
) is
9155 and then Par
/= Standard_Standard
9156 and then not In_Open_Scopes
(Par
)
9158 Install_Noninstance_Specs
(Scope
(Par
));
9161 end Install_Noninstance_Specs
;
9167 procedure Install_Spec
(Par
: Entity_Id
) is
9168 Spec
: constant Node_Id
:= Package_Specification
(Par
);
9171 -- If this parent of the child instance is a top-level unit,
9172 -- then record the unit and its visibility for later resetting in
9173 -- Remove_Parent. We exclude units that are generic instances, as we
9174 -- only want to record this information for the ultimate top-level
9175 -- noninstance parent (is that always correct???).
9177 if Scope
(Par
) = Standard_Standard
9178 and then not Is_Generic_Instance
(Par
)
9180 Parent_Unit_Visible
:= Is_Immediately_Visible
(Par
);
9181 Instance_Parent_Unit
:= Par
;
9184 -- Open the parent scope and make it and its declarations visible.
9185 -- If this point is not within a body, then only the visible
9186 -- declarations should be made visible, and installation of the
9187 -- private declarations is deferred until the appropriate point
9188 -- within analysis of the spec being instantiated (see the handling
9189 -- of parent visibility in Analyze_Package_Specification). This is
9190 -- relaxed in the case where the parent unit is Ada.Tags, to avoid
9191 -- private view problems that occur when compiling instantiations of
9192 -- a generic child of that package (Generic_Dispatching_Constructor).
9193 -- If the instance freezes a tagged type, inlinings of operations
9194 -- from Ada.Tags may need the full view of type Tag. If inlining took
9195 -- proper account of establishing visibility of inlined subprograms'
9196 -- parents then it should be possible to remove this
9197 -- special check. ???
9200 Set_Is_Immediately_Visible
(Par
);
9201 Install_Visible_Declarations
(Par
);
9202 Set_Use
(Visible_Declarations
(Spec
));
9204 if In_Body
or else Is_RTU
(Par
, Ada_Tags
) then
9205 Install_Private_Declarations
(Par
);
9206 Set_Use
(Private_Declarations
(Spec
));
9210 -- Start of processing for Install_Parent
9213 -- We need to install the parent instance to compile the instantiation
9214 -- of the child, but the child instance must appear in the current
9215 -- scope. Given that we cannot place the parent above the current scope
9216 -- in the scope stack, we duplicate the current scope and unstack both
9217 -- after the instantiation is complete.
9219 -- If the parent is itself the instantiation of a child unit, we must
9220 -- also stack the instantiation of its parent, and so on. Each such
9221 -- ancestor is the prefix of the name in a prior instantiation.
9223 -- If this is a nested instance, the parent unit itself resolves to
9224 -- a renaming of the parent instance, whose declaration we need.
9226 -- Finally, the parent may be a generic (not an instance) when the
9227 -- child unit appears as a formal package.
9231 if Present
(Renamed_Entity
(Inst_Par
)) then
9232 Inst_Par
:= Renamed_Entity
(Inst_Par
);
9235 First_Par
:= Inst_Par
;
9237 Gen_Par
:= Generic_Parent
(Package_Specification
(Inst_Par
));
9239 First_Gen
:= Gen_Par
;
9241 while Present
(Gen_Par
) and then Is_Child_Unit
(Gen_Par
) loop
9243 -- Load grandparent instance as well
9245 Inst_Node
:= Get_Package_Instantiation_Node
(Inst_Par
);
9247 if Nkind
(Name
(Inst_Node
)) = N_Expanded_Name
then
9248 Inst_Par
:= Entity
(Prefix
(Name
(Inst_Node
)));
9250 if Present
(Renamed_Entity
(Inst_Par
)) then
9251 Inst_Par
:= Renamed_Entity
(Inst_Par
);
9254 Gen_Par
:= Generic_Parent
(Package_Specification
(Inst_Par
));
9256 if Present
(Gen_Par
) then
9257 Prepend_Elmt
(Inst_Par
, Ancestors
);
9260 -- Parent is not the name of an instantiation
9262 Install_Noninstance_Specs
(Inst_Par
);
9273 if Present
(First_Gen
) then
9274 Append_Elmt
(First_Par
, Ancestors
);
9276 Install_Noninstance_Specs
(First_Par
);
9279 if not Is_Empty_Elmt_List
(Ancestors
) then
9280 Elmt
:= First_Elmt
(Ancestors
);
9281 while Present
(Elmt
) loop
9282 Install_Spec
(Node
(Elmt
));
9283 Install_Formal_Packages
(Node
(Elmt
));
9293 -------------------------------
9294 -- Install_Hidden_Primitives --
9295 -------------------------------
9297 procedure Install_Hidden_Primitives
9298 (Prims_List
: in out Elist_Id
;
9303 List
: Elist_Id
:= No_Elist
;
9304 Prim_G_Elmt
: Elmt_Id
;
9305 Prim_A_Elmt
: Elmt_Id
;
9310 -- No action needed in case of serious errors because we cannot trust
9311 -- in the order of primitives
9313 if Serious_Errors_Detected
> 0 then
9316 -- No action possible if we don't have available the list of primitive
9320 or else not Is_Record_Type
(Gen_T
)
9321 or else not Is_Tagged_Type
(Gen_T
)
9322 or else not Is_Record_Type
(Act_T
)
9323 or else not Is_Tagged_Type
(Act_T
)
9327 -- There is no need to handle interface types since their primitives
9330 elsif Is_Interface
(Gen_T
) then
9334 Prim_G_Elmt
:= First_Elmt
(Primitive_Operations
(Gen_T
));
9336 if not Is_Class_Wide_Type
(Act_T
) then
9337 Prim_A_Elmt
:= First_Elmt
(Primitive_Operations
(Act_T
));
9339 Prim_A_Elmt
:= First_Elmt
(Primitive_Operations
(Root_Type
(Act_T
)));
9343 -- Skip predefined primitives in the generic formal
9345 while Present
(Prim_G_Elmt
)
9346 and then Is_Predefined_Dispatching_Operation
(Node
(Prim_G_Elmt
))
9348 Next_Elmt
(Prim_G_Elmt
);
9351 -- Skip predefined primitives in the generic actual
9353 while Present
(Prim_A_Elmt
)
9354 and then Is_Predefined_Dispatching_Operation
(Node
(Prim_A_Elmt
))
9356 Next_Elmt
(Prim_A_Elmt
);
9359 exit when No
(Prim_G_Elmt
) or else No
(Prim_A_Elmt
);
9361 Prim_G
:= Node
(Prim_G_Elmt
);
9362 Prim_A
:= Node
(Prim_A_Elmt
);
9364 -- There is no need to handle interface primitives because their
9365 -- primitives are not hidden
9367 exit when Present
(Interface_Alias
(Prim_G
));
9369 -- Here we install one hidden primitive
9371 if Chars
(Prim_G
) /= Chars
(Prim_A
)
9372 and then Has_Suffix
(Prim_A
, 'P')
9373 and then Remove_Suffix
(Prim_A
, 'P') = Chars
(Prim_G
)
9375 Set_Chars
(Prim_A
, Chars
(Prim_G
));
9376 Append_New_Elmt
(Prim_A
, To
=> List
);
9379 Next_Elmt
(Prim_A_Elmt
);
9380 Next_Elmt
(Prim_G_Elmt
);
9383 -- Append the elements to the list of temporarily visible primitives
9384 -- avoiding duplicates.
9386 if Present
(List
) then
9387 if No
(Prims_List
) then
9388 Prims_List
:= New_Elmt_List
;
9391 Elmt
:= First_Elmt
(List
);
9392 while Present
(Elmt
) loop
9393 Append_Unique_Elmt
(Node
(Elmt
), Prims_List
);
9397 end Install_Hidden_Primitives
;
9399 -------------------------------
9400 -- Restore_Hidden_Primitives --
9401 -------------------------------
9403 procedure Restore_Hidden_Primitives
(Prims_List
: in out Elist_Id
) is
9404 Prim_Elmt
: Elmt_Id
;
9408 if Prims_List
/= No_Elist
then
9409 Prim_Elmt
:= First_Elmt
(Prims_List
);
9410 while Present
(Prim_Elmt
) loop
9411 Prim
:= Node
(Prim_Elmt
);
9412 Set_Chars
(Prim
, Add_Suffix
(Prim
, 'P'));
9413 Next_Elmt
(Prim_Elmt
);
9416 Prims_List
:= No_Elist
;
9418 end Restore_Hidden_Primitives
;
9420 --------------------------------
9421 -- Instantiate_Formal_Package --
9422 --------------------------------
9424 function Instantiate_Formal_Package
9427 Analyzed_Formal
: Node_Id
) return List_Id
9429 Loc
: constant Source_Ptr
:= Sloc
(Actual
);
9430 Actual_Pack
: Entity_Id
;
9431 Formal_Pack
: Entity_Id
;
9432 Gen_Parent
: Entity_Id
;
9435 Parent_Spec
: Node_Id
;
9437 procedure Find_Matching_Actual
9439 Act
: in out Entity_Id
);
9440 -- We need to associate each formal entity in the formal package with
9441 -- the corresponding entity in the actual package. The actual package
9442 -- has been analyzed and possibly expanded, and as a result there is
9443 -- no one-to-one correspondence between the two lists (for example,
9444 -- the actual may include subtypes, itypes, and inherited primitive
9445 -- operations, interspersed among the renaming declarations for the
9446 -- actuals) . We retrieve the corresponding actual by name because each
9447 -- actual has the same name as the formal, and they do appear in the
9450 function Get_Formal_Entity
(N
: Node_Id
) return Entity_Id
;
9451 -- Retrieve entity of defining entity of generic formal parameter.
9452 -- Only the declarations of formals need to be considered when
9453 -- linking them to actuals, but the declarative list may include
9454 -- internal entities generated during analysis, and those are ignored.
9456 procedure Match_Formal_Entity
9457 (Formal_Node
: Node_Id
;
9458 Formal_Ent
: Entity_Id
;
9459 Actual_Ent
: Entity_Id
);
9460 -- Associates the formal entity with the actual. In the case where
9461 -- Formal_Ent is a formal package, this procedure iterates through all
9462 -- of its formals and enters associations between the actuals occurring
9463 -- in the formal package's corresponding actual package (given by
9464 -- Actual_Ent) and the formal package's formal parameters. This
9465 -- procedure recurses if any of the parameters is itself a package.
9467 function Is_Instance_Of
9468 (Act_Spec
: Entity_Id
;
9469 Gen_Anc
: Entity_Id
) return Boolean;
9470 -- The actual can be an instantiation of a generic within another
9471 -- instance, in which case there is no direct link from it to the
9472 -- original generic ancestor. In that case, we recognize that the
9473 -- ultimate ancestor is the same by examining names and scopes.
9475 procedure Process_Nested_Formal
(Formal
: Entity_Id
);
9476 -- If the current formal is declared with a box, its own formals are
9477 -- visible in the instance, as they were in the generic, and their
9478 -- Hidden flag must be reset. If some of these formals are themselves
9479 -- packages declared with a box, the processing must be recursive.
9481 --------------------------
9482 -- Find_Matching_Actual --
9483 --------------------------
9485 procedure Find_Matching_Actual
9487 Act
: in out Entity_Id
)
9489 Formal_Ent
: Entity_Id
;
9492 case Nkind
(Original_Node
(F
)) is
9493 when N_Formal_Object_Declaration |
9494 N_Formal_Type_Declaration
=>
9495 Formal_Ent
:= Defining_Identifier
(F
);
9497 while Chars
(Act
) /= Chars
(Formal_Ent
) loop
9501 when N_Formal_Subprogram_Declaration |
9502 N_Formal_Package_Declaration |
9503 N_Package_Declaration |
9504 N_Generic_Package_Declaration
=>
9505 Formal_Ent
:= Defining_Entity
(F
);
9507 while Chars
(Act
) /= Chars
(Formal_Ent
) loop
9512 raise Program_Error
;
9514 end Find_Matching_Actual
;
9516 -------------------------
9517 -- Match_Formal_Entity --
9518 -------------------------
9520 procedure Match_Formal_Entity
9521 (Formal_Node
: Node_Id
;
9522 Formal_Ent
: Entity_Id
;
9523 Actual_Ent
: Entity_Id
)
9525 Act_Pkg
: Entity_Id
;
9528 Set_Instance_Of
(Formal_Ent
, Actual_Ent
);
9530 if Ekind
(Actual_Ent
) = E_Package
then
9532 -- Record associations for each parameter
9534 Act_Pkg
:= Actual_Ent
;
9537 A_Ent
: Entity_Id
:= First_Entity
(Act_Pkg
);
9546 -- Retrieve the actual given in the formal package declaration
9548 Actual
:= Entity
(Name
(Original_Node
(Formal_Node
)));
9550 -- The actual in the formal package declaration may be a
9551 -- renamed generic package, in which case we want to retrieve
9552 -- the original generic in order to traverse its formal part.
9554 if Present
(Renamed_Entity
(Actual
)) then
9555 Gen_Decl
:= Unit_Declaration_Node
(Renamed_Entity
(Actual
));
9557 Gen_Decl
:= Unit_Declaration_Node
(Actual
);
9560 Formals
:= Generic_Formal_Declarations
(Gen_Decl
);
9562 if Present
(Formals
) then
9563 F_Node
:= First_Non_Pragma
(Formals
);
9568 while Present
(A_Ent
)
9569 and then Present
(F_Node
)
9570 and then A_Ent
/= First_Private_Entity
(Act_Pkg
)
9572 F_Ent
:= Get_Formal_Entity
(F_Node
);
9574 if Present
(F_Ent
) then
9576 -- This is a formal of the original package. Record
9577 -- association and recurse.
9579 Find_Matching_Actual
(F_Node
, A_Ent
);
9580 Match_Formal_Entity
(F_Node
, F_Ent
, A_Ent
);
9581 Next_Entity
(A_Ent
);
9584 Next_Non_Pragma
(F_Node
);
9588 end Match_Formal_Entity
;
9590 -----------------------
9591 -- Get_Formal_Entity --
9592 -----------------------
9594 function Get_Formal_Entity
(N
: Node_Id
) return Entity_Id
is
9595 Kind
: constant Node_Kind
:= Nkind
(Original_Node
(N
));
9598 when N_Formal_Object_Declaration
=>
9599 return Defining_Identifier
(N
);
9601 when N_Formal_Type_Declaration
=>
9602 return Defining_Identifier
(N
);
9604 when N_Formal_Subprogram_Declaration
=>
9605 return Defining_Unit_Name
(Specification
(N
));
9607 when N_Formal_Package_Declaration
=>
9608 return Defining_Identifier
(Original_Node
(N
));
9610 when N_Generic_Package_Declaration
=>
9611 return Defining_Identifier
(Original_Node
(N
));
9613 -- All other declarations are introduced by semantic analysis and
9614 -- have no match in the actual.
9619 end Get_Formal_Entity
;
9621 --------------------
9622 -- Is_Instance_Of --
9623 --------------------
9625 function Is_Instance_Of
9626 (Act_Spec
: Entity_Id
;
9627 Gen_Anc
: Entity_Id
) return Boolean
9629 Gen_Par
: constant Entity_Id
:= Generic_Parent
(Act_Spec
);
9632 if No
(Gen_Par
) then
9635 -- Simplest case: the generic parent of the actual is the formal
9637 elsif Gen_Par
= Gen_Anc
then
9640 elsif Chars
(Gen_Par
) /= Chars
(Gen_Anc
) then
9643 -- The actual may be obtained through several instantiations. Its
9644 -- scope must itself be an instance of a generic declared in the
9645 -- same scope as the formal. Any other case is detected above.
9647 elsif not Is_Generic_Instance
(Scope
(Gen_Par
)) then
9651 return Generic_Parent
(Parent
(Scope
(Gen_Par
))) = Scope
(Gen_Anc
);
9655 ---------------------------
9656 -- Process_Nested_Formal --
9657 ---------------------------
9659 procedure Process_Nested_Formal
(Formal
: Entity_Id
) is
9663 if Present
(Associated_Formal_Package
(Formal
))
9664 and then Box_Present
(Parent
(Associated_Formal_Package
(Formal
)))
9666 Ent
:= First_Entity
(Formal
);
9667 while Present
(Ent
) loop
9668 Set_Is_Hidden
(Ent
, False);
9669 Set_Is_Visible_Formal
(Ent
);
9670 Set_Is_Potentially_Use_Visible
9671 (Ent
, Is_Potentially_Use_Visible
(Formal
));
9673 if Ekind
(Ent
) = E_Package
then
9674 exit when Renamed_Entity
(Ent
) = Renamed_Entity
(Formal
);
9675 Process_Nested_Formal
(Ent
);
9681 end Process_Nested_Formal
;
9683 -- Start of processing for Instantiate_Formal_Package
9688 if not Is_Entity_Name
(Actual
)
9689 or else Ekind
(Entity
(Actual
)) /= E_Package
9692 ("expect package instance to instantiate formal", Actual
);
9693 Abandon_Instantiation
(Actual
);
9694 raise Program_Error
;
9697 Actual_Pack
:= Entity
(Actual
);
9698 Set_Is_Instantiated
(Actual_Pack
);
9700 -- The actual may be a renamed package, or an outer generic formal
9701 -- package whose instantiation is converted into a renaming.
9703 if Present
(Renamed_Object
(Actual_Pack
)) then
9704 Actual_Pack
:= Renamed_Object
(Actual_Pack
);
9707 if Nkind
(Analyzed_Formal
) = N_Formal_Package_Declaration
then
9708 Gen_Parent
:= Get_Instance_Of
(Entity
(Name
(Analyzed_Formal
)));
9709 Formal_Pack
:= Defining_Identifier
(Analyzed_Formal
);
9712 Generic_Parent
(Specification
(Analyzed_Formal
));
9714 Defining_Unit_Name
(Specification
(Analyzed_Formal
));
9717 if Nkind
(Parent
(Actual_Pack
)) = N_Defining_Program_Unit_Name
then
9718 Parent_Spec
:= Package_Specification
(Actual_Pack
);
9720 Parent_Spec
:= Parent
(Actual_Pack
);
9723 if Gen_Parent
= Any_Id
then
9725 ("previous error in declaration of formal package", Actual
);
9726 Abandon_Instantiation
(Actual
);
9729 Is_Instance_Of
(Parent_Spec
, Get_Instance_Of
(Gen_Parent
))
9735 ("actual parameter must be instance of&", Actual
, Gen_Parent
);
9736 Abandon_Instantiation
(Actual
);
9739 Set_Instance_Of
(Defining_Identifier
(Formal
), Actual_Pack
);
9740 Map_Formal_Package_Entities
(Formal_Pack
, Actual_Pack
);
9743 Make_Package_Renaming_Declaration
(Loc
,
9744 Defining_Unit_Name
=> New_Copy
(Defining_Identifier
(Formal
)),
9745 Name
=> New_Occurrence_Of
(Actual_Pack
, Loc
));
9747 Set_Associated_Formal_Package
9748 (Defining_Unit_Name
(Nod
), Defining_Identifier
(Formal
));
9749 Decls
:= New_List
(Nod
);
9751 -- If the formal F has a box, then the generic declarations are
9752 -- visible in the generic G. In an instance of G, the corresponding
9753 -- entities in the actual for F (which are the actuals for the
9754 -- instantiation of the generic that F denotes) must also be made
9755 -- visible for analysis of the current instance. On exit from the
9756 -- current instance, those entities are made private again. If the
9757 -- actual is currently in use, these entities are also use-visible.
9759 -- The loop through the actual entities also steps through the formal
9760 -- entities and enters associations from formals to actuals into the
9761 -- renaming map. This is necessary to properly handle checking of
9762 -- actual parameter associations for later formals that depend on
9763 -- actuals declared in the formal package.
9765 -- In Ada 2005, partial parameterization requires that we make
9766 -- visible the actuals corresponding to formals that were defaulted
9767 -- in the formal package. There formals are identified because they
9768 -- remain formal generics within the formal package, rather than
9769 -- being renamings of the actuals supplied.
9772 Gen_Decl
: constant Node_Id
:=
9773 Unit_Declaration_Node
(Gen_Parent
);
9774 Formals
: constant List_Id
:=
9775 Generic_Formal_Declarations
(Gen_Decl
);
9777 Actual_Ent
: Entity_Id
;
9778 Actual_Of_Formal
: Node_Id
;
9779 Formal_Node
: Node_Id
;
9780 Formal_Ent
: Entity_Id
;
9783 if Present
(Formals
) then
9784 Formal_Node
:= First_Non_Pragma
(Formals
);
9786 Formal_Node
:= Empty
;
9789 Actual_Ent
:= First_Entity
(Actual_Pack
);
9791 First
(Visible_Declarations
(Specification
(Analyzed_Formal
)));
9792 while Present
(Actual_Ent
)
9793 and then Actual_Ent
/= First_Private_Entity
(Actual_Pack
)
9795 if Present
(Formal_Node
) then
9796 Formal_Ent
:= Get_Formal_Entity
(Formal_Node
);
9798 if Present
(Formal_Ent
) then
9799 Find_Matching_Actual
(Formal_Node
, Actual_Ent
);
9800 Match_Formal_Entity
(Formal_Node
, Formal_Ent
, Actual_Ent
);
9802 -- We iterate at the same time over the actuals of the
9803 -- local package created for the formal, to determine
9804 -- which one of the formals of the original generic were
9805 -- defaulted in the formal. The corresponding actual
9806 -- entities are visible in the enclosing instance.
9808 if Box_Present
(Formal
)
9810 (Present
(Actual_Of_Formal
)
9813 (Get_Formal_Entity
(Actual_Of_Formal
)))
9815 Set_Is_Hidden
(Actual_Ent
, False);
9816 Set_Is_Visible_Formal
(Actual_Ent
);
9817 Set_Is_Potentially_Use_Visible
9818 (Actual_Ent
, In_Use
(Actual_Pack
));
9820 if Ekind
(Actual_Ent
) = E_Package
then
9821 Process_Nested_Formal
(Actual_Ent
);
9825 Set_Is_Hidden
(Actual_Ent
);
9826 Set_Is_Potentially_Use_Visible
(Actual_Ent
, False);
9830 Next_Non_Pragma
(Formal_Node
);
9831 Next
(Actual_Of_Formal
);
9834 -- No further formals to match, but the generic part may
9835 -- contain inherited operation that are not hidden in the
9836 -- enclosing instance.
9838 Next_Entity
(Actual_Ent
);
9842 -- Inherited subprograms generated by formal derived types are
9843 -- also visible if the types are.
9845 Actual_Ent
:= First_Entity
(Actual_Pack
);
9846 while Present
(Actual_Ent
)
9847 and then Actual_Ent
/= First_Private_Entity
(Actual_Pack
)
9849 if Is_Overloadable
(Actual_Ent
)
9851 Nkind
(Parent
(Actual_Ent
)) = N_Subtype_Declaration
9853 not Is_Hidden
(Defining_Identifier
(Parent
(Actual_Ent
)))
9855 Set_Is_Hidden
(Actual_Ent
, False);
9856 Set_Is_Potentially_Use_Visible
9857 (Actual_Ent
, In_Use
(Actual_Pack
));
9860 Next_Entity
(Actual_Ent
);
9864 -- If the formal is not declared with a box, reanalyze it as an
9865 -- abbreviated instantiation, to verify the matching rules of 12.7.
9866 -- The actual checks are performed after the generic associations
9867 -- have been analyzed, to guarantee the same visibility for this
9868 -- instantiation and for the actuals.
9870 -- In Ada 2005, the generic associations for the formal can include
9871 -- defaulted parameters. These are ignored during check. This
9872 -- internal instantiation is removed from the tree after conformance
9873 -- checking, because it contains formal declarations for those
9874 -- defaulted parameters, and those should not reach the back-end.
9876 if not Box_Present
(Formal
) then
9878 I_Pack
: constant Entity_Id
:=
9879 Make_Temporary
(Sloc
(Actual
), 'P');
9882 Set_Is_Internal
(I_Pack
);
9885 Make_Package_Instantiation
(Sloc
(Actual
),
9886 Defining_Unit_Name
=> I_Pack
,
9889 (Get_Instance_Of
(Gen_Parent
), Sloc
(Actual
)),
9890 Generic_Associations
=> Generic_Associations
(Formal
)));
9896 end Instantiate_Formal_Package
;
9898 -----------------------------------
9899 -- Instantiate_Formal_Subprogram --
9900 -----------------------------------
9902 function Instantiate_Formal_Subprogram
9905 Analyzed_Formal
: Node_Id
) return Node_Id
9907 Analyzed_S
: constant Entity_Id
:=
9908 Defining_Unit_Name
(Specification
(Analyzed_Formal
));
9909 Formal_Sub
: constant Entity_Id
:=
9910 Defining_Unit_Name
(Specification
(Formal
));
9912 function From_Parent_Scope
(Subp
: Entity_Id
) return Boolean;
9913 -- If the generic is a child unit, the parent has been installed on the
9914 -- scope stack, but a default subprogram cannot resolve to something
9915 -- on the parent because that parent is not really part of the visible
9916 -- context (it is there to resolve explicit local entities). If the
9917 -- default has resolved in this way, we remove the entity from immediate
9918 -- visibility and analyze the node again to emit an error message or
9919 -- find another visible candidate.
9921 procedure Valid_Actual_Subprogram
(Act
: Node_Id
);
9922 -- Perform legality check and raise exception on failure
9924 -----------------------
9925 -- From_Parent_Scope --
9926 -----------------------
9928 function From_Parent_Scope
(Subp
: Entity_Id
) return Boolean is
9929 Gen_Scope
: Node_Id
;
9932 Gen_Scope
:= Scope
(Analyzed_S
);
9933 while Present
(Gen_Scope
) and then Is_Child_Unit
(Gen_Scope
) loop
9934 if Scope
(Subp
) = Scope
(Gen_Scope
) then
9938 Gen_Scope
:= Scope
(Gen_Scope
);
9942 end From_Parent_Scope
;
9944 -----------------------------
9945 -- Valid_Actual_Subprogram --
9946 -----------------------------
9948 procedure Valid_Actual_Subprogram
(Act
: Node_Id
) is
9952 if Is_Entity_Name
(Act
) then
9953 Act_E
:= Entity
(Act
);
9955 elsif Nkind
(Act
) = N_Selected_Component
9956 and then Is_Entity_Name
(Selector_Name
(Act
))
9958 Act_E
:= Entity
(Selector_Name
(Act
));
9964 if (Present
(Act_E
) and then Is_Overloadable
(Act_E
))
9965 or else Nkind_In
(Act
, N_Attribute_Reference
,
9966 N_Indexed_Component
,
9967 N_Character_Literal
,
9968 N_Explicit_Dereference
)
9974 ("expect subprogram or entry name in instantiation of &",
9975 Instantiation_Node
, Formal_Sub
);
9976 Abandon_Instantiation
(Instantiation_Node
);
9977 end Valid_Actual_Subprogram
;
9981 Decl_Node
: Node_Id
;
9985 New_Subp
: Entity_Id
;
9987 -- Start of processing for Instantiate_Formal_Subprogram
9990 New_Spec
:= New_Copy_Tree
(Specification
(Formal
));
9992 -- The tree copy has created the proper instantiation sloc for the
9993 -- new specification. Use this location for all other constructed
9996 Loc
:= Sloc
(Defining_Unit_Name
(New_Spec
));
9998 -- Create new entity for the actual (New_Copy_Tree does not), and
9999 -- indicate that it is an actual.
10001 New_Subp
:= Make_Defining_Identifier
(Loc
, Chars
(Formal_Sub
));
10002 Set_Ekind
(New_Subp
, Ekind
(Analyzed_S
));
10003 Set_Is_Generic_Actual_Subprogram
(New_Subp
);
10004 Set_Defining_Unit_Name
(New_Spec
, New_Subp
);
10006 -- Create new entities for the each of the formals in the specification
10007 -- of the renaming declaration built for the actual.
10009 if Present
(Parameter_Specifications
(New_Spec
)) then
10015 F
:= First
(Parameter_Specifications
(New_Spec
));
10016 while Present
(F
) loop
10017 F_Id
:= Defining_Identifier
(F
);
10019 Set_Defining_Identifier
(F
,
10020 Make_Defining_Identifier
(Sloc
(F_Id
), Chars
(F_Id
)));
10026 -- Find entity of actual. If the actual is an attribute reference, it
10027 -- cannot be resolved here (its formal is missing) but is handled
10028 -- instead in Attribute_Renaming. If the actual is overloaded, it is
10029 -- fully resolved subsequently, when the renaming declaration for the
10030 -- formal is analyzed. If it is an explicit dereference, resolve the
10031 -- prefix but not the actual itself, to prevent interpretation as call.
10033 if Present
(Actual
) then
10034 Loc
:= Sloc
(Actual
);
10035 Set_Sloc
(New_Spec
, Loc
);
10037 if Nkind
(Actual
) = N_Operator_Symbol
then
10038 Find_Direct_Name
(Actual
);
10040 elsif Nkind
(Actual
) = N_Explicit_Dereference
then
10041 Analyze
(Prefix
(Actual
));
10043 elsif Nkind
(Actual
) /= N_Attribute_Reference
then
10047 Valid_Actual_Subprogram
(Actual
);
10050 elsif Present
(Default_Name
(Formal
)) then
10051 if not Nkind_In
(Default_Name
(Formal
), N_Attribute_Reference
,
10052 N_Selected_Component
,
10053 N_Indexed_Component
,
10054 N_Character_Literal
)
10055 and then Present
(Entity
(Default_Name
(Formal
)))
10057 Nam
:= New_Occurrence_Of
(Entity
(Default_Name
(Formal
)), Loc
);
10059 Nam
:= New_Copy
(Default_Name
(Formal
));
10060 Set_Sloc
(Nam
, Loc
);
10063 elsif Box_Present
(Formal
) then
10065 -- Actual is resolved at the point of instantiation. Create an
10066 -- identifier or operator with the same name as the formal.
10068 if Nkind
(Formal_Sub
) = N_Defining_Operator_Symbol
then
10070 Make_Operator_Symbol
(Loc
,
10071 Chars
=> Chars
(Formal_Sub
),
10072 Strval
=> No_String
);
10074 Nam
:= Make_Identifier
(Loc
, Chars
(Formal_Sub
));
10077 elsif Nkind
(Specification
(Formal
)) = N_Procedure_Specification
10078 and then Null_Present
(Specification
(Formal
))
10080 -- Generate null body for procedure, for use in the instance
10083 Make_Subprogram_Body
(Loc
,
10084 Specification
=> New_Spec
,
10085 Declarations
=> New_List
,
10086 Handled_Statement_Sequence
=>
10087 Make_Handled_Sequence_Of_Statements
(Loc
,
10088 Statements
=> New_List
(Make_Null_Statement
(Loc
))));
10090 Set_Is_Intrinsic_Subprogram
(Defining_Unit_Name
(New_Spec
));
10094 Error_Msg_Sloc
:= Sloc
(Scope
(Analyzed_S
));
10096 ("missing actual&", Instantiation_Node
, Formal_Sub
);
10098 ("\in instantiation of & declared#",
10099 Instantiation_Node
, Scope
(Analyzed_S
));
10100 Abandon_Instantiation
(Instantiation_Node
);
10104 Make_Subprogram_Renaming_Declaration
(Loc
,
10105 Specification
=> New_Spec
,
10108 -- If we do not have an actual and the formal specified <> then set to
10109 -- get proper default.
10111 if No
(Actual
) and then Box_Present
(Formal
) then
10112 Set_From_Default
(Decl_Node
);
10115 -- Gather possible interpretations for the actual before analyzing the
10116 -- instance. If overloaded, it will be resolved when analyzing the
10117 -- renaming declaration.
10119 if Box_Present
(Formal
) and then No
(Actual
) then
10122 if Is_Child_Unit
(Scope
(Analyzed_S
))
10123 and then Present
(Entity
(Nam
))
10125 if not Is_Overloaded
(Nam
) then
10126 if From_Parent_Scope
(Entity
(Nam
)) then
10127 Set_Is_Immediately_Visible
(Entity
(Nam
), False);
10128 Set_Entity
(Nam
, Empty
);
10129 Set_Etype
(Nam
, Empty
);
10132 Set_Is_Immediately_Visible
(Entity
(Nam
));
10141 Get_First_Interp
(Nam
, I
, It
);
10142 while Present
(It
.Nam
) loop
10143 if From_Parent_Scope
(It
.Nam
) then
10147 Get_Next_Interp
(I
, It
);
10154 -- The generic instantiation freezes the actual. This can only be done
10155 -- once the actual is resolved, in the analysis of the renaming
10156 -- declaration. To make the formal subprogram entity available, we set
10157 -- Corresponding_Formal_Spec to point to the formal subprogram entity.
10158 -- This is also needed in Analyze_Subprogram_Renaming for the processing
10159 -- of formal abstract subprograms.
10161 Set_Corresponding_Formal_Spec
(Decl_Node
, Analyzed_S
);
10163 -- We cannot analyze the renaming declaration, and thus find the actual,
10164 -- until all the actuals are assembled in the instance. For subsequent
10165 -- checks of other actuals, indicate the node that will hold the
10166 -- instance of this formal.
10168 Set_Instance_Of
(Analyzed_S
, Nam
);
10170 if Nkind
(Actual
) = N_Selected_Component
10171 and then Is_Task_Type
(Etype
(Prefix
(Actual
)))
10172 and then not Is_Frozen
(Etype
(Prefix
(Actual
)))
10174 -- The renaming declaration will create a body, which must appear
10175 -- outside of the instantiation, We move the renaming declaration
10176 -- out of the instance, and create an additional renaming inside,
10177 -- to prevent freezing anomalies.
10180 Anon_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'E');
10183 Set_Defining_Unit_Name
(New_Spec
, Anon_Id
);
10184 Insert_Before
(Instantiation_Node
, Decl_Node
);
10185 Analyze
(Decl_Node
);
10187 -- Now create renaming within the instance
10190 Make_Subprogram_Renaming_Declaration
(Loc
,
10191 Specification
=> New_Copy_Tree
(New_Spec
),
10192 Name
=> New_Occurrence_Of
(Anon_Id
, Loc
));
10194 Set_Defining_Unit_Name
(Specification
(Decl_Node
),
10195 Make_Defining_Identifier
(Loc
, Chars
(Formal_Sub
)));
10200 end Instantiate_Formal_Subprogram
;
10202 ------------------------
10203 -- Instantiate_Object --
10204 ------------------------
10206 function Instantiate_Object
10209 Analyzed_Formal
: Node_Id
) return List_Id
10211 Gen_Obj
: constant Entity_Id
:= Defining_Identifier
(Formal
);
10212 A_Gen_Obj
: constant Entity_Id
:=
10213 Defining_Identifier
(Analyzed_Formal
);
10214 Acc_Def
: Node_Id
:= Empty
;
10215 Act_Assoc
: constant Node_Id
:= Parent
(Actual
);
10216 Actual_Decl
: Node_Id
:= Empty
;
10217 Decl_Node
: Node_Id
;
10220 List
: constant List_Id
:= New_List
;
10221 Loc
: constant Source_Ptr
:= Sloc
(Actual
);
10222 Orig_Ftyp
: constant Entity_Id
:= Etype
(A_Gen_Obj
);
10223 Subt_Decl
: Node_Id
:= Empty
;
10224 Subt_Mark
: Node_Id
:= Empty
;
10226 function Copy_Access_Def
return Node_Id
;
10227 -- If formal is an anonymous access, copy access definition of formal
10228 -- for generated object declaration.
10230 ---------------------
10231 -- Copy_Access_Def --
10232 ---------------------
10234 function Copy_Access_Def
return Node_Id
is
10236 Def
:= New_Copy_Tree
(Acc_Def
);
10238 -- In addition, if formal is an access to subprogram we need to
10239 -- generate new formals for the signature of the default, so that
10240 -- the tree is properly formatted for ASIS use.
10242 if Present
(Access_To_Subprogram_Definition
(Acc_Def
)) then
10244 Par_Spec
: Node_Id
;
10247 First
(Parameter_Specifications
10248 (Access_To_Subprogram_Definition
(Def
)));
10249 while Present
(Par_Spec
) loop
10250 Set_Defining_Identifier
(Par_Spec
,
10251 Make_Defining_Identifier
(Sloc
(Acc_Def
),
10252 Chars
=> Chars
(Defining_Identifier
(Par_Spec
))));
10259 end Copy_Access_Def
;
10261 -- Start of processing for Instantiate_Object
10264 -- Formal may be an anonymous access
10266 if Present
(Subtype_Mark
(Formal
)) then
10267 Subt_Mark
:= Subtype_Mark
(Formal
);
10269 Check_Access_Definition
(Formal
);
10270 Acc_Def
:= Access_Definition
(Formal
);
10273 -- Sloc for error message on missing actual
10275 Error_Msg_Sloc
:= Sloc
(Scope
(A_Gen_Obj
));
10277 if Get_Instance_Of
(Gen_Obj
) /= Gen_Obj
then
10278 Error_Msg_N
("duplicate instantiation of generic parameter", Actual
);
10281 Set_Parent
(List
, Parent
(Actual
));
10285 if Out_Present
(Formal
) then
10287 -- An IN OUT generic actual must be a name. The instantiation is a
10288 -- renaming declaration. The actual is the name being renamed. We
10289 -- use the actual directly, rather than a copy, because it is not
10290 -- used further in the list of actuals, and because a copy or a use
10291 -- of relocate_node is incorrect if the instance is nested within a
10292 -- generic. In order to simplify ASIS searches, the Generic_Parent
10293 -- field links the declaration to the generic association.
10295 if No
(Actual
) then
10297 ("missing actual &",
10298 Instantiation_Node
, Gen_Obj
);
10300 ("\in instantiation of & declared#",
10301 Instantiation_Node
, Scope
(A_Gen_Obj
));
10302 Abandon_Instantiation
(Instantiation_Node
);
10305 if Present
(Subt_Mark
) then
10307 Make_Object_Renaming_Declaration
(Loc
,
10308 Defining_Identifier
=> New_Copy
(Gen_Obj
),
10309 Subtype_Mark
=> New_Copy_Tree
(Subt_Mark
),
10312 else pragma Assert
(Present
(Acc_Def
));
10314 Make_Object_Renaming_Declaration
(Loc
,
10315 Defining_Identifier
=> New_Copy
(Gen_Obj
),
10316 Access_Definition
=> New_Copy_Tree
(Acc_Def
),
10320 Set_Corresponding_Generic_Association
(Decl_Node
, Act_Assoc
);
10322 -- The analysis of the actual may produce Insert_Action nodes, so
10323 -- the declaration must have a context in which to attach them.
10325 Append
(Decl_Node
, List
);
10328 -- Return if the analysis of the actual reported some error
10330 if Etype
(Actual
) = Any_Type
then
10334 -- This check is performed here because Analyze_Object_Renaming will
10335 -- not check it when Comes_From_Source is False. Note though that the
10336 -- check for the actual being the name of an object will be performed
10337 -- in Analyze_Object_Renaming.
10339 if Is_Object_Reference
(Actual
)
10340 and then Is_Dependent_Component_Of_Mutable_Object
(Actual
)
10343 ("illegal discriminant-dependent component for in out parameter",
10347 -- The actual has to be resolved in order to check that it is a
10348 -- variable (due to cases such as F (1), where F returns access to
10349 -- an array, and for overloaded prefixes).
10351 Ftyp
:= Get_Instance_Of
(Etype
(A_Gen_Obj
));
10353 -- If the type of the formal is not itself a formal, and the current
10354 -- unit is a child unit, the formal type must be declared in a
10355 -- parent, and must be retrieved by visibility.
10357 if Ftyp
= Orig_Ftyp
10358 and then Is_Generic_Unit
(Scope
(Ftyp
))
10359 and then Is_Child_Unit
(Scope
(A_Gen_Obj
))
10362 Temp
: constant Node_Id
:=
10363 New_Copy_Tree
(Subtype_Mark
(Analyzed_Formal
));
10365 Set_Entity
(Temp
, Empty
);
10367 Ftyp
:= Entity
(Temp
);
10371 if Is_Private_Type
(Ftyp
)
10372 and then not Is_Private_Type
(Etype
(Actual
))
10373 and then (Base_Type
(Full_View
(Ftyp
)) = Base_Type
(Etype
(Actual
))
10374 or else Base_Type
(Etype
(Actual
)) = Ftyp
)
10376 -- If the actual has the type of the full view of the formal, or
10377 -- else a non-private subtype of the formal, then the visibility
10378 -- of the formal type has changed. Add to the actuals a subtype
10379 -- declaration that will force the exchange of views in the body
10380 -- of the instance as well.
10383 Make_Subtype_Declaration
(Loc
,
10384 Defining_Identifier
=> Make_Temporary
(Loc
, 'P'),
10385 Subtype_Indication
=> New_Occurrence_Of
(Ftyp
, Loc
));
10387 Prepend
(Subt_Decl
, List
);
10389 Prepend_Elmt
(Full_View
(Ftyp
), Exchanged_Views
);
10390 Exchange_Declarations
(Ftyp
);
10393 Resolve
(Actual
, Ftyp
);
10395 if not Denotes_Variable
(Actual
) then
10396 Error_Msg_NE
("actual for& must be a variable", Actual
, Gen_Obj
);
10398 elsif Base_Type
(Ftyp
) /= Base_Type
(Etype
(Actual
)) then
10400 -- Ada 2005 (AI-423): For a generic formal object of mode in out,
10401 -- the type of the actual shall resolve to a specific anonymous
10404 if Ada_Version
< Ada_2005
10405 or else Ekind
(Base_Type
(Ftyp
)) /=
10406 E_Anonymous_Access_Type
10407 or else Ekind
(Base_Type
(Etype
(Actual
))) /=
10408 E_Anonymous_Access_Type
10411 ("type of actual does not match type of&", Actual
, Gen_Obj
);
10415 Note_Possible_Modification
(Actual
, Sure
=> True);
10417 -- Check for instantiation of atomic/volatile actual for
10418 -- non-atomic/volatile formal (RM C.6 (12)).
10420 if Is_Atomic_Object
(Actual
) and then not Is_Atomic
(Orig_Ftyp
) then
10422 ("cannot instantiate non-atomic formal object "
10423 & "with atomic actual", Actual
);
10425 elsif Is_Volatile_Object
(Actual
) and then not Is_Volatile
(Orig_Ftyp
)
10428 ("cannot instantiate non-volatile formal object "
10429 & "with volatile actual", Actual
);
10432 -- Formal in-parameter
10435 -- The instantiation of a generic formal in-parameter is constant
10436 -- declaration. The actual is the expression for that declaration.
10437 -- Its type is a full copy of the type of the formal. This may be
10438 -- an access to subprogram, for which we need to generate entities
10439 -- for the formals in the new signature.
10441 if Present
(Actual
) then
10442 if Present
(Subt_Mark
) then
10443 Def
:= New_Copy_Tree
(Subt_Mark
);
10444 else pragma Assert
(Present
(Acc_Def
));
10445 Def
:= Copy_Access_Def
;
10449 Make_Object_Declaration
(Loc
,
10450 Defining_Identifier
=> New_Copy
(Gen_Obj
),
10451 Constant_Present
=> True,
10452 Null_Exclusion_Present
=> Null_Exclusion_Present
(Formal
),
10453 Object_Definition
=> Def
,
10454 Expression
=> Actual
);
10456 Set_Corresponding_Generic_Association
(Decl_Node
, Act_Assoc
);
10458 -- A generic formal object of a tagged type is defined to be
10459 -- aliased so the new constant must also be treated as aliased.
10461 if Is_Tagged_Type
(Etype
(A_Gen_Obj
)) then
10462 Set_Aliased_Present
(Decl_Node
);
10465 Append
(Decl_Node
, List
);
10467 -- No need to repeat (pre-)analysis of some expression nodes
10468 -- already handled in Preanalyze_Actuals.
10470 if Nkind
(Actual
) /= N_Allocator
then
10473 -- Return if the analysis of the actual reported some error
10475 if Etype
(Actual
) = Any_Type
then
10481 Formal_Type
: constant Entity_Id
:= Etype
(A_Gen_Obj
);
10485 Typ
:= Get_Instance_Of
(Formal_Type
);
10487 -- If the actual appears in the current or an enclosing scope,
10488 -- use its type directly. This is relevant if it has an actual
10489 -- subtype that is distinct from its nominal one. This cannot
10490 -- be done in general because the type of the actual may
10491 -- depend on other actuals, and only be fully determined when
10492 -- the enclosing instance is analyzed.
10494 if Present
(Etype
(Actual
))
10495 and then Is_Constr_Subt_For_U_Nominal
(Etype
(Actual
))
10497 Freeze_Before
(Instantiation_Node
, Etype
(Actual
));
10499 Freeze_Before
(Instantiation_Node
, Typ
);
10502 -- If the actual is an aggregate, perform name resolution on
10503 -- its components (the analysis of an aggregate does not do it)
10504 -- to capture local names that may be hidden if the generic is
10507 if Nkind
(Actual
) = N_Aggregate
then
10508 Preanalyze_And_Resolve
(Actual
, Typ
);
10511 if Is_Limited_Type
(Typ
)
10512 and then not OK_For_Limited_Init
(Typ
, Actual
)
10515 ("initialization not allowed for limited types", Actual
);
10516 Explain_Limited_Type
(Typ
, Actual
);
10520 elsif Present
(Default_Expression
(Formal
)) then
10522 -- Use default to construct declaration
10524 if Present
(Subt_Mark
) then
10525 Def
:= New_Copy
(Subt_Mark
);
10526 else pragma Assert
(Present
(Acc_Def
));
10527 Def
:= Copy_Access_Def
;
10531 Make_Object_Declaration
(Sloc
(Formal
),
10532 Defining_Identifier
=> New_Copy
(Gen_Obj
),
10533 Constant_Present
=> True,
10534 Null_Exclusion_Present
=> Null_Exclusion_Present
(Formal
),
10535 Object_Definition
=> Def
,
10536 Expression
=> New_Copy_Tree
10537 (Default_Expression
(Formal
)));
10539 Append
(Decl_Node
, List
);
10540 Set_Analyzed
(Expression
(Decl_Node
), False);
10543 Error_Msg_NE
("missing actual&", Instantiation_Node
, Gen_Obj
);
10544 Error_Msg_NE
("\in instantiation of & declared#",
10545 Instantiation_Node
, Scope
(A_Gen_Obj
));
10547 if Is_Scalar_Type
(Etype
(A_Gen_Obj
)) then
10549 -- Create dummy constant declaration so that instance can be
10550 -- analyzed, to minimize cascaded visibility errors.
10552 if Present
(Subt_Mark
) then
10554 else pragma Assert
(Present
(Acc_Def
));
10559 Make_Object_Declaration
(Loc
,
10560 Defining_Identifier
=> New_Copy
(Gen_Obj
),
10561 Constant_Present
=> True,
10562 Null_Exclusion_Present
=> Null_Exclusion_Present
(Formal
),
10563 Object_Definition
=> New_Copy
(Def
),
10565 Make_Attribute_Reference
(Sloc
(Gen_Obj
),
10566 Attribute_Name
=> Name_First
,
10567 Prefix
=> New_Copy
(Def
)));
10569 Append
(Decl_Node
, List
);
10572 Abandon_Instantiation
(Instantiation_Node
);
10577 if Nkind
(Actual
) in N_Has_Entity
then
10578 Actual_Decl
:= Parent
(Entity
(Actual
));
10581 -- Ada 2005 (AI-423): For a formal object declaration with a null
10582 -- exclusion or an access definition that has a null exclusion: If the
10583 -- actual matching the formal object declaration denotes a generic
10584 -- formal object of another generic unit G, and the instantiation
10585 -- containing the actual occurs within the body of G or within the body
10586 -- of a generic unit declared within the declarative region of G, then
10587 -- the declaration of the formal object of G must have a null exclusion.
10588 -- Otherwise, the subtype of the actual matching the formal object
10589 -- declaration shall exclude null.
10591 if Ada_Version
>= Ada_2005
10592 and then Present
(Actual_Decl
)
10593 and then Nkind_In
(Actual_Decl
, N_Formal_Object_Declaration
,
10594 N_Object_Declaration
)
10595 and then Nkind
(Analyzed_Formal
) = N_Formal_Object_Declaration
10596 and then not Has_Null_Exclusion
(Actual_Decl
)
10597 and then Has_Null_Exclusion
(Analyzed_Formal
)
10599 Error_Msg_Sloc
:= Sloc
(Analyzed_Formal
);
10601 ("actual must exclude null to match generic formal#", Actual
);
10604 -- An effectively volatile object cannot be used as an actual in
10605 -- a generic instance. The following check is only relevant when
10606 -- SPARK_Mode is on as it is not a standard Ada legality rule.
10609 and then Present
(Actual
)
10610 and then Is_Effectively_Volatile_Object
(Actual
)
10613 ("volatile object cannot act as actual in generic instantiation "
10614 & "(SPARK RM 7.1.3(8))", Actual
);
10618 end Instantiate_Object
;
10620 ------------------------------
10621 -- Instantiate_Package_Body --
10622 ------------------------------
10624 procedure Instantiate_Package_Body
10625 (Body_Info
: Pending_Body_Info
;
10626 Inlined_Body
: Boolean := False;
10627 Body_Optional
: Boolean := False)
10629 Act_Decl
: constant Node_Id
:= Body_Info
.Act_Decl
;
10630 Inst_Node
: constant Node_Id
:= Body_Info
.Inst_Node
;
10631 Loc
: constant Source_Ptr
:= Sloc
(Inst_Node
);
10633 Gen_Id
: constant Node_Id
:= Name
(Inst_Node
);
10634 Gen_Unit
: constant Entity_Id
:= Get_Generic_Entity
(Inst_Node
);
10635 Gen_Decl
: constant Node_Id
:= Unit_Declaration_Node
(Gen_Unit
);
10636 Act_Spec
: constant Node_Id
:= Specification
(Act_Decl
);
10637 Act_Decl_Id
: constant Entity_Id
:= Defining_Entity
(Act_Spec
);
10639 Act_Body_Name
: Node_Id
;
10640 Gen_Body
: Node_Id
;
10641 Gen_Body_Id
: Node_Id
;
10642 Act_Body
: Node_Id
;
10643 Act_Body_Id
: Entity_Id
;
10645 Parent_Installed
: Boolean := False;
10646 Save_Style_Check
: constant Boolean := Style_Check
;
10648 Par_Ent
: Entity_Id
:= Empty
;
10649 Par_Vis
: Boolean := False;
10651 Vis_Prims_List
: Elist_Id
:= No_Elist
;
10652 -- List of primitives made temporarily visible in the instantiation
10653 -- to match the visibility of the formal type
10655 procedure Check_Initialized_Types
;
10656 -- In a generic package body, an entity of a generic private type may
10657 -- appear uninitialized. This is suspicious, unless the actual is a
10658 -- fully initialized type.
10660 -----------------------------
10661 -- Check_Initialized_Types --
10662 -----------------------------
10664 procedure Check_Initialized_Types
is
10666 Formal
: Entity_Id
;
10667 Actual
: Entity_Id
;
10668 Uninit_Var
: Entity_Id
;
10671 Decl
:= First
(Generic_Formal_Declarations
(Gen_Decl
));
10672 while Present
(Decl
) loop
10673 Uninit_Var
:= Empty
;
10675 if Nkind
(Decl
) = N_Private_Extension_Declaration
then
10676 Uninit_Var
:= Uninitialized_Variable
(Decl
);
10678 elsif Nkind
(Decl
) = N_Formal_Type_Declaration
10679 and then Nkind
(Formal_Type_Definition
(Decl
)) =
10680 N_Formal_Private_Type_Definition
10683 Uninitialized_Variable
(Formal_Type_Definition
(Decl
));
10686 if Present
(Uninit_Var
) then
10687 Formal
:= Defining_Identifier
(Decl
);
10688 Actual
:= First_Entity
(Act_Decl_Id
);
10690 -- For each formal there is a subtype declaration that renames
10691 -- the actual and has the same name as the formal. Locate the
10692 -- formal for warning message about uninitialized variables
10693 -- in the generic, for which the actual type should be a fully
10694 -- initialized type.
10696 while Present
(Actual
) loop
10697 exit when Ekind
(Actual
) = E_Package
10698 and then Present
(Renamed_Object
(Actual
));
10700 if Chars
(Actual
) = Chars
(Formal
)
10701 and then not Is_Scalar_Type
(Actual
)
10702 and then not Is_Fully_Initialized_Type
(Actual
)
10703 and then Warn_On_No_Value_Assigned
10705 Error_Msg_Node_2
:= Formal
;
10707 ("generic unit has uninitialized variable& of "
10708 & "formal private type &?v?", Actual
, Uninit_Var
);
10710 ("actual type for& should be fully initialized type?v?",
10715 Next_Entity
(Actual
);
10721 end Check_Initialized_Types
;
10723 -- Start of processing for Instantiate_Package_Body
10726 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
10728 -- The instance body may already have been processed, as the parent of
10729 -- another instance that is inlined (Load_Parent_Of_Generic).
10731 if Present
(Corresponding_Body
(Instance_Spec
(Inst_Node
))) then
10735 Expander_Mode_Save_And_Set
(Body_Info
.Expander_Status
);
10737 -- Re-establish the state of information on which checks are suppressed.
10738 -- This information was set in Body_Info at the point of instantiation,
10739 -- and now we restore it so that the instance is compiled using the
10740 -- check status at the instantiation (RM 11.5 (7.2/2), AI95-00224-01).
10742 Local_Suppress_Stack_Top
:= Body_Info
.Local_Suppress_Stack_Top
;
10743 Scope_Suppress
:= Body_Info
.Scope_Suppress
;
10744 Opt
.Ada_Version
:= Body_Info
.Version
;
10745 Opt
.Ada_Version_Pragma
:= Body_Info
.Version_Pragma
;
10746 Restore_Warnings
(Body_Info
.Warnings
);
10747 Opt
.SPARK_Mode
:= Body_Info
.SPARK_Mode
;
10748 Opt
.SPARK_Mode_Pragma
:= Body_Info
.SPARK_Mode_Pragma
;
10750 if No
(Gen_Body_Id
) then
10752 -- Do not look for parent of generic body if none is required.
10753 -- This may happen when the routine is called as part of the
10754 -- Pending_Instantiations processing, when nested instances
10755 -- may precede the one generated from the main unit.
10757 if not Unit_Requires_Body
(Defining_Entity
(Gen_Decl
))
10758 and then Body_Optional
10762 Load_Parent_Of_Generic
10763 (Inst_Node
, Specification
(Gen_Decl
), Body_Optional
);
10764 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
10768 -- Establish global variable for sloc adjustment and for error recovery
10769 -- In the case of an instance body for an instantiation with actuals
10770 -- from a limited view, the instance body is placed at the beginning
10771 -- of the enclosing package body: use the body entity as the source
10772 -- location for nodes of the instance body.
10774 if not Is_Empty_Elmt_List
(Incomplete_Actuals
(Act_Decl_Id
)) then
10776 Scop
: constant Entity_Id
:= Scope
(Act_Decl_Id
);
10777 Body_Id
: constant Node_Id
:=
10778 Corresponding_Body
(Unit_Declaration_Node
(Scop
));
10781 Instantiation_Node
:= Body_Id
;
10784 Instantiation_Node
:= Inst_Node
;
10787 if Present
(Gen_Body_Id
) then
10788 Save_Env
(Gen_Unit
, Act_Decl_Id
);
10789 Style_Check
:= False;
10790 Current_Sem_Unit
:= Body_Info
.Current_Sem_Unit
;
10792 Gen_Body
:= Unit_Declaration_Node
(Gen_Body_Id
);
10794 Create_Instantiation_Source
10795 (Inst_Node
, Gen_Body_Id
, False, S_Adjustment
);
10799 (Original_Node
(Gen_Body
), Empty
, Instantiating
=> True);
10801 -- Build new name (possibly qualified) for body declaration
10803 Act_Body_Id
:= New_Copy
(Act_Decl_Id
);
10805 -- Some attributes of spec entity are not inherited by body entity
10807 Set_Handler_Records
(Act_Body_Id
, No_List
);
10809 if Nkind
(Defining_Unit_Name
(Act_Spec
)) =
10810 N_Defining_Program_Unit_Name
10813 Make_Defining_Program_Unit_Name
(Loc
,
10814 Name
=> New_Copy_Tree
(Name
(Defining_Unit_Name
(Act_Spec
))),
10815 Defining_Identifier
=> Act_Body_Id
);
10817 Act_Body_Name
:= Act_Body_Id
;
10820 Set_Defining_Unit_Name
(Act_Body
, Act_Body_Name
);
10822 Set_Corresponding_Spec
(Act_Body
, Act_Decl_Id
);
10823 Check_Generic_Actuals
(Act_Decl_Id
, False);
10824 Check_Initialized_Types
;
10826 -- Install primitives hidden at the point of the instantiation but
10827 -- visible when processing the generic formals
10833 E
:= First_Entity
(Act_Decl_Id
);
10834 while Present
(E
) loop
10836 and then Is_Generic_Actual_Type
(E
)
10837 and then Is_Tagged_Type
(E
)
10839 Install_Hidden_Primitives
10840 (Prims_List
=> Vis_Prims_List
,
10841 Gen_T
=> Generic_Parent_Type
(Parent
(E
)),
10849 -- If it is a child unit, make the parent instance (which is an
10850 -- instance of the parent of the generic) visible. The parent
10851 -- instance is the prefix of the name of the generic unit.
10853 if Ekind
(Scope
(Gen_Unit
)) = E_Generic_Package
10854 and then Nkind
(Gen_Id
) = N_Expanded_Name
10856 Par_Ent
:= Entity
(Prefix
(Gen_Id
));
10857 Par_Vis
:= Is_Immediately_Visible
(Par_Ent
);
10858 Install_Parent
(Par_Ent
, In_Body
=> True);
10859 Parent_Installed
:= True;
10861 elsif Is_Child_Unit
(Gen_Unit
) then
10862 Par_Ent
:= Scope
(Gen_Unit
);
10863 Par_Vis
:= Is_Immediately_Visible
(Par_Ent
);
10864 Install_Parent
(Par_Ent
, In_Body
=> True);
10865 Parent_Installed
:= True;
10868 -- If the instantiation is a library unit, and this is the main unit,
10869 -- then build the resulting compilation unit nodes for the instance.
10870 -- If this is a compilation unit but it is not the main unit, then it
10871 -- is the body of a unit in the context, that is being compiled
10872 -- because it is encloses some inlined unit or another generic unit
10873 -- being instantiated. In that case, this body is not part of the
10874 -- current compilation, and is not attached to the tree, but its
10875 -- parent must be set for analysis.
10877 if Nkind
(Parent
(Inst_Node
)) = N_Compilation_Unit
then
10879 -- Replace instance node with body of instance, and create new
10880 -- node for corresponding instance declaration.
10882 Build_Instance_Compilation_Unit_Nodes
10883 (Inst_Node
, Act_Body
, Act_Decl
);
10884 Analyze
(Inst_Node
);
10886 if Parent
(Inst_Node
) = Cunit
(Main_Unit
) then
10888 -- If the instance is a child unit itself, then set the scope
10889 -- of the expanded body to be the parent of the instantiation
10890 -- (ensuring that the fully qualified name will be generated
10891 -- for the elaboration subprogram).
10893 if Nkind
(Defining_Unit_Name
(Act_Spec
)) =
10894 N_Defining_Program_Unit_Name
10896 Set_Scope
(Defining_Entity
(Inst_Node
), Scope
(Act_Decl_Id
));
10900 -- Case where instantiation is not a library unit
10903 -- If this is an early instantiation, i.e. appears textually
10904 -- before the corresponding body and must be elaborated first,
10905 -- indicate that the body instance is to be delayed.
10907 Install_Body
(Act_Body
, Inst_Node
, Gen_Body
, Gen_Decl
);
10909 -- Now analyze the body. We turn off all checks if this is an
10910 -- internal unit, since there is no reason to have checks on for
10911 -- any predefined run-time library code. All such code is designed
10912 -- to be compiled with checks off.
10914 -- Note that we do NOT apply this criterion to children of GNAT
10915 -- The latter units must suppress checks explicitly if needed.
10917 if Is_Predefined_File_Name
10918 (Unit_File_Name
(Get_Source_Unit
(Gen_Decl
)))
10920 Analyze
(Act_Body
, Suppress
=> All_Checks
);
10922 Analyze
(Act_Body
);
10926 Inherit_Context
(Gen_Body
, Inst_Node
);
10928 -- Remove the parent instances if they have been placed on the scope
10929 -- stack to compile the body.
10931 if Parent_Installed
then
10932 Remove_Parent
(In_Body
=> True);
10934 -- Restore the previous visibility of the parent
10936 Set_Is_Immediately_Visible
(Par_Ent
, Par_Vis
);
10939 Restore_Hidden_Primitives
(Vis_Prims_List
);
10940 Restore_Private_Views
(Act_Decl_Id
);
10942 -- Remove the current unit from visibility if this is an instance
10943 -- that is not elaborated on the fly for inlining purposes.
10945 if not Inlined_Body
then
10946 Set_Is_Immediately_Visible
(Act_Decl_Id
, False);
10950 Style_Check
:= Save_Style_Check
;
10952 -- If we have no body, and the unit requires a body, then complain. This
10953 -- complaint is suppressed if we have detected other errors (since a
10954 -- common reason for missing the body is that it had errors).
10955 -- In CodePeer mode, a warning has been emitted already, no need for
10956 -- further messages.
10958 elsif Unit_Requires_Body
(Gen_Unit
)
10959 and then not Body_Optional
10961 if CodePeer_Mode
then
10964 elsif Serious_Errors_Detected
= 0 then
10966 ("cannot find body of generic package &", Inst_Node
, Gen_Unit
);
10968 -- Don't attempt to perform any cleanup actions if some other error
10969 -- was already detected, since this can cause blowups.
10975 -- Case of package that does not need a body
10978 -- If the instantiation of the declaration is a library unit, rewrite
10979 -- the original package instantiation as a package declaration in the
10980 -- compilation unit node.
10982 if Nkind
(Parent
(Inst_Node
)) = N_Compilation_Unit
then
10983 Set_Parent_Spec
(Act_Decl
, Parent_Spec
(Inst_Node
));
10984 Rewrite
(Inst_Node
, Act_Decl
);
10986 -- Generate elaboration entity, in case spec has elaboration code.
10987 -- This cannot be done when the instance is analyzed, because it
10988 -- is not known yet whether the body exists.
10990 Set_Elaboration_Entity_Required
(Act_Decl_Id
, False);
10991 Build_Elaboration_Entity
(Parent
(Inst_Node
), Act_Decl_Id
);
10993 -- If the instantiation is not a library unit, then append the
10994 -- declaration to the list of implicitly generated entities, unless
10995 -- it is already a list member which means that it was already
10998 elsif not Is_List_Member
(Act_Decl
) then
10999 Mark_Rewrite_Insertion
(Act_Decl
);
11000 Insert_Before
(Inst_Node
, Act_Decl
);
11004 Expander_Mode_Restore
;
11005 end Instantiate_Package_Body
;
11007 ---------------------------------
11008 -- Instantiate_Subprogram_Body --
11009 ---------------------------------
11011 procedure Instantiate_Subprogram_Body
11012 (Body_Info
: Pending_Body_Info
;
11013 Body_Optional
: Boolean := False)
11015 Act_Decl
: constant Node_Id
:= Body_Info
.Act_Decl
;
11016 Inst_Node
: constant Node_Id
:= Body_Info
.Inst_Node
;
11017 Loc
: constant Source_Ptr
:= Sloc
(Inst_Node
);
11018 Gen_Id
: constant Node_Id
:= Name
(Inst_Node
);
11019 Gen_Unit
: constant Entity_Id
:= Get_Generic_Entity
(Inst_Node
);
11020 Gen_Decl
: constant Node_Id
:= Unit_Declaration_Node
(Gen_Unit
);
11021 Anon_Id
: constant Entity_Id
:=
11022 Defining_Unit_Name
(Specification
(Act_Decl
));
11023 Pack_Id
: constant Entity_Id
:=
11024 Defining_Unit_Name
(Parent
(Act_Decl
));
11026 Saved_Style_Check
: constant Boolean := Style_Check
;
11027 Saved_Warnings
: constant Warning_Record
:= Save_Warnings
;
11029 Act_Body
: Node_Id
;
11030 Gen_Body
: Node_Id
;
11031 Gen_Body_Id
: Node_Id
;
11032 Pack_Body
: Node_Id
;
11033 Par_Ent
: Entity_Id
:= Empty
;
11034 Par_Vis
: Boolean := False;
11035 Ret_Expr
: Node_Id
;
11037 Parent_Installed
: Boolean := False;
11040 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
11042 -- Subprogram body may have been created already because of an inline
11043 -- pragma, or because of multiple elaborations of the enclosing package
11044 -- when several instances of the subprogram appear in the main unit.
11046 if Present
(Corresponding_Body
(Act_Decl
)) then
11050 Expander_Mode_Save_And_Set
(Body_Info
.Expander_Status
);
11052 -- Re-establish the state of information on which checks are suppressed.
11053 -- This information was set in Body_Info at the point of instantiation,
11054 -- and now we restore it so that the instance is compiled using the
11055 -- check status at the instantiation (RM 11.5 (7.2/2), AI95-00224-01).
11057 Local_Suppress_Stack_Top
:= Body_Info
.Local_Suppress_Stack_Top
;
11058 Scope_Suppress
:= Body_Info
.Scope_Suppress
;
11059 Opt
.Ada_Version
:= Body_Info
.Version
;
11060 Opt
.Ada_Version_Pragma
:= Body_Info
.Version_Pragma
;
11061 Restore_Warnings
(Body_Info
.Warnings
);
11062 Opt
.SPARK_Mode
:= Body_Info
.SPARK_Mode
;
11063 Opt
.SPARK_Mode_Pragma
:= Body_Info
.SPARK_Mode_Pragma
;
11065 if No
(Gen_Body_Id
) then
11067 -- For imported generic subprogram, no body to compile, complete
11068 -- the spec entity appropriately.
11070 if Is_Imported
(Gen_Unit
) then
11071 Set_Is_Imported
(Anon_Id
);
11072 Set_First_Rep_Item
(Anon_Id
, First_Rep_Item
(Gen_Unit
));
11073 Set_Interface_Name
(Anon_Id
, Interface_Name
(Gen_Unit
));
11074 Set_Convention
(Anon_Id
, Convention
(Gen_Unit
));
11075 Set_Has_Completion
(Anon_Id
);
11078 -- For other cases, compile the body
11081 Load_Parent_Of_Generic
11082 (Inst_Node
, Specification
(Gen_Decl
), Body_Optional
);
11083 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
11087 Instantiation_Node
:= Inst_Node
;
11089 if Present
(Gen_Body_Id
) then
11090 Gen_Body
:= Unit_Declaration_Node
(Gen_Body_Id
);
11092 if Nkind
(Gen_Body
) = N_Subprogram_Body_Stub
then
11094 -- Either body is not present, or context is non-expanding, as
11095 -- when compiling a subunit. Mark the instance as completed, and
11096 -- diagnose a missing body when needed.
11099 and then Operating_Mode
= Generate_Code
11102 ("missing proper body for instantiation", Gen_Body
);
11105 Set_Has_Completion
(Anon_Id
);
11109 Save_Env
(Gen_Unit
, Anon_Id
);
11110 Style_Check
:= False;
11111 Current_Sem_Unit
:= Body_Info
.Current_Sem_Unit
;
11112 Create_Instantiation_Source
11120 (Original_Node
(Gen_Body
), Empty
, Instantiating
=> True);
11122 -- Create proper defining name for the body, to correspond to
11123 -- the one in the spec.
11125 Set_Defining_Unit_Name
(Specification
(Act_Body
),
11126 Make_Defining_Identifier
11127 (Sloc
(Defining_Entity
(Inst_Node
)), Chars
(Anon_Id
)));
11128 Set_Corresponding_Spec
(Act_Body
, Anon_Id
);
11129 Set_Has_Completion
(Anon_Id
);
11130 Check_Generic_Actuals
(Pack_Id
, False);
11132 -- Generate a reference to link the visible subprogram instance to
11133 -- the generic body, which for navigation purposes is the only
11134 -- available source for the instance.
11137 (Related_Instance
(Pack_Id
),
11138 Gen_Body_Id
, 'b', Set_Ref
=> False, Force
=> True);
11140 -- If it is a child unit, make the parent instance (which is an
11141 -- instance of the parent of the generic) visible. The parent
11142 -- instance is the prefix of the name of the generic unit.
11144 if Ekind
(Scope
(Gen_Unit
)) = E_Generic_Package
11145 and then Nkind
(Gen_Id
) = N_Expanded_Name
11147 Par_Ent
:= Entity
(Prefix
(Gen_Id
));
11148 Par_Vis
:= Is_Immediately_Visible
(Par_Ent
);
11149 Install_Parent
(Par_Ent
, In_Body
=> True);
11150 Parent_Installed
:= True;
11152 elsif Is_Child_Unit
(Gen_Unit
) then
11153 Par_Ent
:= Scope
(Gen_Unit
);
11154 Par_Vis
:= Is_Immediately_Visible
(Par_Ent
);
11155 Install_Parent
(Par_Ent
, In_Body
=> True);
11156 Parent_Installed
:= True;
11159 -- Subprogram body is placed in the body of wrapper package,
11160 -- whose spec contains the subprogram declaration as well as
11161 -- the renaming declarations for the generic parameters.
11164 Make_Package_Body
(Loc
,
11165 Defining_Unit_Name
=> New_Copy
(Pack_Id
),
11166 Declarations
=> New_List
(Act_Body
));
11168 Set_Corresponding_Spec
(Pack_Body
, Pack_Id
);
11170 -- If the instantiation is a library unit, then build resulting
11171 -- compilation unit nodes for the instance. The declaration of
11172 -- the enclosing package is the grandparent of the subprogram
11173 -- declaration. First replace the instantiation node as the unit
11174 -- of the corresponding compilation.
11176 if Nkind
(Parent
(Inst_Node
)) = N_Compilation_Unit
then
11177 if Parent
(Inst_Node
) = Cunit
(Main_Unit
) then
11178 Set_Unit
(Parent
(Inst_Node
), Inst_Node
);
11179 Build_Instance_Compilation_Unit_Nodes
11180 (Inst_Node
, Pack_Body
, Parent
(Parent
(Act_Decl
)));
11181 Analyze
(Inst_Node
);
11183 Set_Parent
(Pack_Body
, Parent
(Inst_Node
));
11184 Analyze
(Pack_Body
);
11188 Insert_Before
(Inst_Node
, Pack_Body
);
11189 Mark_Rewrite_Insertion
(Pack_Body
);
11190 Analyze
(Pack_Body
);
11192 if Expander_Active
then
11193 Freeze_Subprogram_Body
(Inst_Node
, Gen_Body
, Pack_Id
);
11197 Inherit_Context
(Gen_Body
, Inst_Node
);
11199 Restore_Private_Views
(Pack_Id
, False);
11201 if Parent_Installed
then
11202 Remove_Parent
(In_Body
=> True);
11204 -- Restore the previous visibility of the parent
11206 Set_Is_Immediately_Visible
(Par_Ent
, Par_Vis
);
11210 Style_Check
:= Saved_Style_Check
;
11211 Restore_Warnings
(Saved_Warnings
);
11213 -- Body not found. Error was emitted already. If there were no previous
11214 -- errors, this may be an instance whose scope is a premature instance.
11215 -- In that case we must insure that the (legal) program does raise
11216 -- program error if executed. We generate a subprogram body for this
11217 -- purpose. See DEC ac30vso.
11219 -- Should not reference proprietary DEC tests in comments ???
11221 elsif Serious_Errors_Detected
= 0
11222 and then Nkind
(Parent
(Inst_Node
)) /= N_Compilation_Unit
11224 if Body_Optional
then
11227 elsif Ekind
(Anon_Id
) = E_Procedure
then
11229 Make_Subprogram_Body
(Loc
,
11231 Make_Procedure_Specification
(Loc
,
11232 Defining_Unit_Name
=>
11233 Make_Defining_Identifier
(Loc
, Chars
(Anon_Id
)),
11234 Parameter_Specifications
=>
11236 (Parameter_Specifications
(Parent
(Anon_Id
)))),
11238 Declarations
=> Empty_List
,
11239 Handled_Statement_Sequence
=>
11240 Make_Handled_Sequence_Of_Statements
(Loc
,
11243 Make_Raise_Program_Error
(Loc
,
11245 PE_Access_Before_Elaboration
))));
11249 Make_Raise_Program_Error
(Loc
,
11250 Reason
=> PE_Access_Before_Elaboration
);
11252 Set_Etype
(Ret_Expr
, (Etype
(Anon_Id
)));
11253 Set_Analyzed
(Ret_Expr
);
11256 Make_Subprogram_Body
(Loc
,
11258 Make_Function_Specification
(Loc
,
11259 Defining_Unit_Name
=>
11260 Make_Defining_Identifier
(Loc
, Chars
(Anon_Id
)),
11261 Parameter_Specifications
=>
11263 (Parameter_Specifications
(Parent
(Anon_Id
))),
11264 Result_Definition
=>
11265 New_Occurrence_Of
(Etype
(Anon_Id
), Loc
)),
11267 Declarations
=> Empty_List
,
11268 Handled_Statement_Sequence
=>
11269 Make_Handled_Sequence_Of_Statements
(Loc
,
11272 (Make_Simple_Return_Statement
(Loc
, Ret_Expr
))));
11275 Pack_Body
:= Make_Package_Body
(Loc
,
11276 Defining_Unit_Name
=> New_Copy
(Pack_Id
),
11277 Declarations
=> New_List
(Act_Body
));
11279 Insert_After
(Inst_Node
, Pack_Body
);
11280 Set_Corresponding_Spec
(Pack_Body
, Pack_Id
);
11281 Analyze
(Pack_Body
);
11284 Expander_Mode_Restore
;
11285 end Instantiate_Subprogram_Body
;
11287 ----------------------
11288 -- Instantiate_Type --
11289 ----------------------
11291 function Instantiate_Type
11294 Analyzed_Formal
: Node_Id
;
11295 Actual_Decls
: List_Id
) return List_Id
11297 Gen_T
: constant Entity_Id
:= Defining_Identifier
(Formal
);
11298 A_Gen_T
: constant Entity_Id
:=
11299 Defining_Identifier
(Analyzed_Formal
);
11300 Ancestor
: Entity_Id
:= Empty
;
11301 Def
: constant Node_Id
:= Formal_Type_Definition
(Formal
);
11303 Decl_Node
: Node_Id
;
11304 Decl_Nodes
: List_Id
;
11308 procedure Diagnose_Predicated_Actual
;
11309 -- There are a number of constructs in which a discrete type with
11310 -- predicates is illegal, e.g. as an index in an array type declaration.
11311 -- If a generic type is used is such a construct in a generic package
11312 -- declaration, it carries the flag No_Predicate_On_Actual. it is part
11313 -- of the generic contract that the actual cannot have predicates.
11315 procedure Validate_Array_Type_Instance
;
11316 procedure Validate_Access_Subprogram_Instance
;
11317 procedure Validate_Access_Type_Instance
;
11318 procedure Validate_Derived_Type_Instance
;
11319 procedure Validate_Derived_Interface_Type_Instance
;
11320 procedure Validate_Discriminated_Formal_Type
;
11321 procedure Validate_Interface_Type_Instance
;
11322 procedure Validate_Private_Type_Instance
;
11323 procedure Validate_Incomplete_Type_Instance
;
11324 -- These procedures perform validation tests for the named case.
11325 -- Validate_Discriminated_Formal_Type is shared by formal private
11326 -- types and Ada 2012 formal incomplete types.
11328 function Subtypes_Match
(Gen_T
, Act_T
: Entity_Id
) return Boolean;
11329 -- Check that base types are the same and that the subtypes match
11330 -- statically. Used in several of the above.
11332 ---------------------------------
11333 -- Diagnose_Predicated_Actual --
11334 ---------------------------------
11336 procedure Diagnose_Predicated_Actual
is
11338 if No_Predicate_On_Actual
(A_Gen_T
)
11339 and then Has_Predicates
(Act_T
)
11342 ("actual for& cannot be a type with predicate",
11343 Instantiation_Node
, A_Gen_T
);
11345 elsif No_Dynamic_Predicate_On_Actual
(A_Gen_T
)
11346 and then Has_Predicates
(Act_T
)
11347 and then not Has_Static_Predicate_Aspect
(Act_T
)
11350 ("actual for& cannot be a type with a dynamic predicate",
11351 Instantiation_Node
, A_Gen_T
);
11353 end Diagnose_Predicated_Actual
;
11355 --------------------
11356 -- Subtypes_Match --
11357 --------------------
11359 function Subtypes_Match
(Gen_T
, Act_T
: Entity_Id
) return Boolean is
11360 T
: constant Entity_Id
:= Get_Instance_Of
(Gen_T
);
11363 -- Some detailed comments would be useful here ???
11365 return ((Base_Type
(T
) = Act_T
11366 or else Base_Type
(T
) = Base_Type
(Act_T
))
11367 and then Subtypes_Statically_Match
(T
, Act_T
))
11369 or else (Is_Class_Wide_Type
(Gen_T
)
11370 and then Is_Class_Wide_Type
(Act_T
)
11371 and then Subtypes_Match
11372 (Get_Instance_Of
(Root_Type
(Gen_T
)),
11373 Root_Type
(Act_T
)))
11376 (Ekind_In
(Gen_T
, E_Anonymous_Access_Subprogram_Type
,
11377 E_Anonymous_Access_Type
)
11378 and then Ekind
(Act_T
) = Ekind
(Gen_T
)
11379 and then Subtypes_Statically_Match
11380 (Designated_Type
(Gen_T
), Designated_Type
(Act_T
)));
11381 end Subtypes_Match
;
11383 -----------------------------------------
11384 -- Validate_Access_Subprogram_Instance --
11385 -----------------------------------------
11387 procedure Validate_Access_Subprogram_Instance
is
11389 if not Is_Access_Type
(Act_T
)
11390 or else Ekind
(Designated_Type
(Act_T
)) /= E_Subprogram_Type
11393 ("expect access type in instantiation of &", Actual
, Gen_T
);
11394 Abandon_Instantiation
(Actual
);
11397 -- According to AI05-288, actuals for access_to_subprograms must be
11398 -- subtype conformant with the generic formal. Previous to AI05-288
11399 -- only mode conformance was required.
11401 -- This is a binding interpretation that applies to previous versions
11402 -- of the language, no need to maintain previous weaker checks.
11404 Check_Subtype_Conformant
11405 (Designated_Type
(Act_T
),
11406 Designated_Type
(A_Gen_T
),
11410 if Ekind
(Base_Type
(Act_T
)) = E_Access_Protected_Subprogram_Type
then
11411 if Ekind
(A_Gen_T
) = E_Access_Subprogram_Type
then
11413 ("protected access type not allowed for formal &",
11417 elsif Ekind
(A_Gen_T
) = E_Access_Protected_Subprogram_Type
then
11419 ("expect protected access type for formal &",
11423 -- If the formal has a specified convention (which in most cases
11424 -- will be StdCall) verify that the actual has the same convention.
11426 if Has_Convention_Pragma
(A_Gen_T
)
11427 and then Convention
(A_Gen_T
) /= Convention
(Act_T
)
11429 Error_Msg_Name_1
:= Get_Convention_Name
(Convention
(A_Gen_T
));
11431 ("actual for formal & must have convention %", Actual
, Gen_T
);
11433 end Validate_Access_Subprogram_Instance
;
11435 -----------------------------------
11436 -- Validate_Access_Type_Instance --
11437 -----------------------------------
11439 procedure Validate_Access_Type_Instance
is
11440 Desig_Type
: constant Entity_Id
:=
11441 Find_Actual_Type
(Designated_Type
(A_Gen_T
), A_Gen_T
);
11442 Desig_Act
: Entity_Id
;
11445 if not Is_Access_Type
(Act_T
) then
11447 ("expect access type in instantiation of &", Actual
, Gen_T
);
11448 Abandon_Instantiation
(Actual
);
11451 if Is_Access_Constant
(A_Gen_T
) then
11452 if not Is_Access_Constant
(Act_T
) then
11454 ("actual type must be access-to-constant type", Actual
);
11455 Abandon_Instantiation
(Actual
);
11458 if Is_Access_Constant
(Act_T
) then
11460 ("actual type must be access-to-variable type", Actual
);
11461 Abandon_Instantiation
(Actual
);
11463 elsif Ekind
(A_Gen_T
) = E_General_Access_Type
11464 and then Ekind
(Base_Type
(Act_T
)) /= E_General_Access_Type
11466 Error_Msg_N
-- CODEFIX
11467 ("actual must be general access type!", Actual
);
11468 Error_Msg_NE
-- CODEFIX
11469 ("add ALL to }!", Actual
, Act_T
);
11470 Abandon_Instantiation
(Actual
);
11474 -- The designated subtypes, that is to say the subtypes introduced
11475 -- by an access type declaration (and not by a subtype declaration)
11478 Desig_Act
:= Designated_Type
(Base_Type
(Act_T
));
11480 -- The designated type may have been introduced through a limited_
11481 -- with clause, in which case retrieve the non-limited view. This
11482 -- applies to incomplete types as well as to class-wide types.
11484 if From_Limited_With
(Desig_Act
) then
11485 Desig_Act
:= Available_View
(Desig_Act
);
11488 if not Subtypes_Match
(Desig_Type
, Desig_Act
) then
11490 ("designated type of actual does not match that of formal &",
11493 if not Predicates_Match
(Desig_Type
, Desig_Act
) then
11494 Error_Msg_N
("\predicates do not match", Actual
);
11497 Abandon_Instantiation
(Actual
);
11499 elsif Is_Access_Type
(Designated_Type
(Act_T
))
11500 and then Is_Constrained
(Designated_Type
(Designated_Type
(Act_T
)))
11502 Is_Constrained
(Designated_Type
(Desig_Type
))
11505 ("designated type of actual does not match that of formal &",
11508 if not Predicates_Match
(Desig_Type
, Desig_Act
) then
11509 Error_Msg_N
("\predicates do not match", Actual
);
11512 Abandon_Instantiation
(Actual
);
11515 -- Ada 2005: null-exclusion indicators of the two types must agree
11517 if Can_Never_Be_Null
(A_Gen_T
) /= Can_Never_Be_Null
(Act_T
) then
11519 ("non null exclusion of actual and formal & do not match",
11522 end Validate_Access_Type_Instance
;
11524 ----------------------------------
11525 -- Validate_Array_Type_Instance --
11526 ----------------------------------
11528 procedure Validate_Array_Type_Instance
is
11533 function Formal_Dimensions
return Int
;
11534 -- Count number of dimensions in array type formal
11536 -----------------------
11537 -- Formal_Dimensions --
11538 -----------------------
11540 function Formal_Dimensions
return Int
is
11545 if Nkind
(Def
) = N_Constrained_Array_Definition
then
11546 Index
:= First
(Discrete_Subtype_Definitions
(Def
));
11548 Index
:= First
(Subtype_Marks
(Def
));
11551 while Present
(Index
) loop
11553 Next_Index
(Index
);
11557 end Formal_Dimensions
;
11559 -- Start of processing for Validate_Array_Type_Instance
11562 if not Is_Array_Type
(Act_T
) then
11564 ("expect array type in instantiation of &", Actual
, Gen_T
);
11565 Abandon_Instantiation
(Actual
);
11567 elsif Nkind
(Def
) = N_Constrained_Array_Definition
then
11568 if not (Is_Constrained
(Act_T
)) then
11570 ("expect constrained array in instantiation of &",
11572 Abandon_Instantiation
(Actual
);
11576 if Is_Constrained
(Act_T
) then
11578 ("expect unconstrained array in instantiation of &",
11580 Abandon_Instantiation
(Actual
);
11584 if Formal_Dimensions
/= Number_Dimensions
(Act_T
) then
11586 ("dimensions of actual do not match formal &", Actual
, Gen_T
);
11587 Abandon_Instantiation
(Actual
);
11590 I1
:= First_Index
(A_Gen_T
);
11591 I2
:= First_Index
(Act_T
);
11592 for J
in 1 .. Formal_Dimensions
loop
11594 -- If the indexes of the actual were given by a subtype_mark,
11595 -- the index was transformed into a range attribute. Retrieve
11596 -- the original type mark for checking.
11598 if Is_Entity_Name
(Original_Node
(I2
)) then
11599 T2
:= Entity
(Original_Node
(I2
));
11604 if not Subtypes_Match
11605 (Find_Actual_Type
(Etype
(I1
), A_Gen_T
), T2
)
11608 ("index types of actual do not match those of formal &",
11610 Abandon_Instantiation
(Actual
);
11617 -- Check matching subtypes. Note that there are complex visibility
11618 -- issues when the generic is a child unit and some aspect of the
11619 -- generic type is declared in a parent unit of the generic. We do
11620 -- the test to handle this special case only after a direct check
11621 -- for static matching has failed. The case where both the component
11622 -- type and the array type are separate formals, and the component
11623 -- type is a private view may also require special checking in
11627 (Component_Type
(A_Gen_T
), Component_Type
(Act_T
))
11630 (Find_Actual_Type
(Component_Type
(A_Gen_T
), A_Gen_T
),
11631 Component_Type
(Act_T
))
11636 ("component subtype of actual does not match that of formal &",
11638 Abandon_Instantiation
(Actual
);
11641 if Has_Aliased_Components
(A_Gen_T
)
11642 and then not Has_Aliased_Components
(Act_T
)
11645 ("actual must have aliased components to match formal type &",
11648 end Validate_Array_Type_Instance
;
11650 -----------------------------------------------
11651 -- Validate_Derived_Interface_Type_Instance --
11652 -----------------------------------------------
11654 procedure Validate_Derived_Interface_Type_Instance
is
11655 Par
: constant Entity_Id
:= Entity
(Subtype_Indication
(Def
));
11659 -- First apply interface instance checks
11661 Validate_Interface_Type_Instance
;
11663 -- Verify that immediate parent interface is an ancestor of
11667 and then not Interface_Present_In_Ancestor
(Act_T
, Par
)
11670 ("interface actual must include progenitor&", Actual
, Par
);
11673 -- Now verify that the actual includes all other ancestors of
11676 Elmt
:= First_Elmt
(Interfaces
(A_Gen_T
));
11677 while Present
(Elmt
) loop
11678 if not Interface_Present_In_Ancestor
11679 (Act_T
, Get_Instance_Of
(Node
(Elmt
)))
11682 ("interface actual must include progenitor&",
11683 Actual
, Node
(Elmt
));
11688 end Validate_Derived_Interface_Type_Instance
;
11690 ------------------------------------
11691 -- Validate_Derived_Type_Instance --
11692 ------------------------------------
11694 procedure Validate_Derived_Type_Instance
is
11695 Actual_Discr
: Entity_Id
;
11696 Ancestor_Discr
: Entity_Id
;
11699 -- If the parent type in the generic declaration is itself a previous
11700 -- formal type, then it is local to the generic and absent from the
11701 -- analyzed generic definition. In that case the ancestor is the
11702 -- instance of the formal (which must have been instantiated
11703 -- previously), unless the ancestor is itself a formal derived type.
11704 -- In this latter case (which is the subject of Corrigendum 8652/0038
11705 -- (AI-202) the ancestor of the formals is the ancestor of its
11706 -- parent. Otherwise, the analyzed generic carries the parent type.
11707 -- If the parent type is defined in a previous formal package, then
11708 -- the scope of that formal package is that of the generic type
11709 -- itself, and it has already been mapped into the corresponding type
11710 -- in the actual package.
11712 -- Common case: parent type defined outside of the generic
11714 if Is_Entity_Name
(Subtype_Mark
(Def
))
11715 and then Present
(Entity
(Subtype_Mark
(Def
)))
11717 Ancestor
:= Get_Instance_Of
(Entity
(Subtype_Mark
(Def
)));
11719 -- Check whether parent is defined in a previous formal package
11722 Scope
(Scope
(Base_Type
(Etype
(A_Gen_T
)))) = Scope
(A_Gen_T
)
11725 Get_Instance_Of
(Base_Type
(Etype
(A_Gen_T
)));
11727 -- The type may be a local derivation, or a type extension of a
11728 -- previous formal, or of a formal of a parent package.
11730 elsif Is_Derived_Type
(Get_Instance_Of
(A_Gen_T
))
11732 Ekind
(Get_Instance_Of
(A_Gen_T
)) = E_Record_Type_With_Private
11734 -- Check whether the parent is another derived formal type in the
11735 -- same generic unit.
11737 if Etype
(A_Gen_T
) /= A_Gen_T
11738 and then Is_Generic_Type
(Etype
(A_Gen_T
))
11739 and then Scope
(Etype
(A_Gen_T
)) = Scope
(A_Gen_T
)
11740 and then Etype
(Etype
(A_Gen_T
)) /= Etype
(A_Gen_T
)
11742 -- Locate ancestor of parent from the subtype declaration
11743 -- created for the actual.
11749 Decl
:= First
(Actual_Decls
);
11750 while Present
(Decl
) loop
11751 if Nkind
(Decl
) = N_Subtype_Declaration
11752 and then Chars
(Defining_Identifier
(Decl
)) =
11753 Chars
(Etype
(A_Gen_T
))
11755 Ancestor
:= Generic_Parent_Type
(Decl
);
11763 pragma Assert
(Present
(Ancestor
));
11765 -- The ancestor itself may be a previous formal that has been
11768 Ancestor
:= Get_Instance_Of
(Ancestor
);
11772 Get_Instance_Of
(Base_Type
(Get_Instance_Of
(A_Gen_T
)));
11775 -- Check whether parent is a previous formal of the current generic
11777 elsif Is_Derived_Type
(A_Gen_T
)
11778 and then Is_Generic_Type
(Etype
(A_Gen_T
))
11779 and then Scope
(A_Gen_T
) = Scope
(Etype
(A_Gen_T
))
11781 Ancestor
:= Get_Instance_Of
(First_Subtype
(Etype
(A_Gen_T
)));
11783 -- An unusual case: the actual is a type declared in a parent unit,
11784 -- but is not a formal type so there is no instance_of for it.
11785 -- Retrieve it by analyzing the record extension.
11787 elsif Is_Child_Unit
(Scope
(A_Gen_T
))
11788 and then In_Open_Scopes
(Scope
(Act_T
))
11789 and then Is_Generic_Instance
(Scope
(Act_T
))
11791 Analyze
(Subtype_Mark
(Def
));
11792 Ancestor
:= Entity
(Subtype_Mark
(Def
));
11795 Ancestor
:= Get_Instance_Of
(Etype
(Base_Type
(A_Gen_T
)));
11798 -- If the formal derived type has pragma Preelaborable_Initialization
11799 -- then the actual type must have preelaborable initialization.
11801 if Known_To_Have_Preelab_Init
(A_Gen_T
)
11802 and then not Has_Preelaborable_Initialization
(Act_T
)
11805 ("actual for & must have preelaborable initialization",
11809 -- Ada 2005 (AI-251)
11811 if Ada_Version
>= Ada_2005
and then Is_Interface
(Ancestor
) then
11812 if not Interface_Present_In_Ancestor
(Act_T
, Ancestor
) then
11814 ("(Ada 2005) expected type implementing & in instantiation",
11818 -- Finally verify that the (instance of) the ancestor is an ancestor
11821 elsif not Is_Ancestor
(Base_Type
(Ancestor
), Act_T
) then
11823 ("expect type derived from & in instantiation",
11824 Actual
, First_Subtype
(Ancestor
));
11825 Abandon_Instantiation
(Actual
);
11828 -- Ada 2005 (AI-443): Synchronized formal derived type checks. Note
11829 -- that the formal type declaration has been rewritten as a private
11832 if Ada_Version
>= Ada_2005
11833 and then Nkind
(Parent
(A_Gen_T
)) = N_Private_Extension_Declaration
11834 and then Synchronized_Present
(Parent
(A_Gen_T
))
11836 -- The actual must be a synchronized tagged type
11838 if not Is_Tagged_Type
(Act_T
) then
11840 ("actual of synchronized type must be tagged", Actual
);
11841 Abandon_Instantiation
(Actual
);
11843 elsif Nkind
(Parent
(Act_T
)) = N_Full_Type_Declaration
11844 and then Nkind
(Type_Definition
(Parent
(Act_T
))) =
11845 N_Derived_Type_Definition
11846 and then not Synchronized_Present
11847 (Type_Definition
(Parent
(Act_T
)))
11850 ("actual of synchronized type must be synchronized", Actual
);
11851 Abandon_Instantiation
(Actual
);
11855 -- Perform atomic/volatile checks (RM C.6(12)). Note that AI05-0218-1
11856 -- removes the second instance of the phrase "or allow pass by copy".
11858 if Is_Atomic
(Act_T
) and then not Is_Atomic
(Ancestor
) then
11860 ("cannot have atomic actual type for non-atomic formal type",
11863 elsif Is_Volatile
(Act_T
) and then not Is_Volatile
(Ancestor
) then
11865 ("cannot have volatile actual type for non-volatile formal type",
11869 -- It should not be necessary to check for unknown discriminants on
11870 -- Formal, but for some reason Has_Unknown_Discriminants is false for
11871 -- A_Gen_T, so Is_Definite_Subtype incorrectly returns True. This
11872 -- needs fixing. ???
11874 if Is_Definite_Subtype
(A_Gen_T
)
11875 and then not Unknown_Discriminants_Present
(Formal
)
11876 and then not Is_Definite_Subtype
(Act_T
)
11878 Error_Msg_N
("actual subtype must be constrained", Actual
);
11879 Abandon_Instantiation
(Actual
);
11882 if not Unknown_Discriminants_Present
(Formal
) then
11883 if Is_Constrained
(Ancestor
) then
11884 if not Is_Constrained
(Act_T
) then
11885 Error_Msg_N
("actual subtype must be constrained", Actual
);
11886 Abandon_Instantiation
(Actual
);
11889 -- Ancestor is unconstrained, Check if generic formal and actual
11890 -- agree on constrainedness. The check only applies to array types
11891 -- and discriminated types.
11893 elsif Is_Constrained
(Act_T
) then
11894 if Ekind
(Ancestor
) = E_Access_Type
11895 or else (not Is_Constrained
(A_Gen_T
)
11896 and then Is_Composite_Type
(A_Gen_T
))
11898 Error_Msg_N
("actual subtype must be unconstrained", Actual
);
11899 Abandon_Instantiation
(Actual
);
11902 -- A class-wide type is only allowed if the formal has unknown
11905 elsif Is_Class_Wide_Type
(Act_T
)
11906 and then not Has_Unknown_Discriminants
(Ancestor
)
11909 ("actual for & cannot be a class-wide type", Actual
, Gen_T
);
11910 Abandon_Instantiation
(Actual
);
11912 -- Otherwise, the formal and actual must have the same number
11913 -- of discriminants and each discriminant of the actual must
11914 -- correspond to a discriminant of the formal.
11916 elsif Has_Discriminants
(Act_T
)
11917 and then not Has_Unknown_Discriminants
(Act_T
)
11918 and then Has_Discriminants
(Ancestor
)
11920 Actual_Discr
:= First_Discriminant
(Act_T
);
11921 Ancestor_Discr
:= First_Discriminant
(Ancestor
);
11922 while Present
(Actual_Discr
)
11923 and then Present
(Ancestor_Discr
)
11925 if Base_Type
(Act_T
) /= Base_Type
(Ancestor
) and then
11926 No
(Corresponding_Discriminant
(Actual_Discr
))
11929 ("discriminant & does not correspond "
11930 & "to ancestor discriminant", Actual
, Actual_Discr
);
11931 Abandon_Instantiation
(Actual
);
11934 Next_Discriminant
(Actual_Discr
);
11935 Next_Discriminant
(Ancestor_Discr
);
11938 if Present
(Actual_Discr
) or else Present
(Ancestor_Discr
) then
11940 ("actual for & must have same number of discriminants",
11942 Abandon_Instantiation
(Actual
);
11945 -- This case should be caught by the earlier check for
11946 -- constrainedness, but the check here is added for completeness.
11948 elsif Has_Discriminants
(Act_T
)
11949 and then not Has_Unknown_Discriminants
(Act_T
)
11952 ("actual for & must not have discriminants", Actual
, Gen_T
);
11953 Abandon_Instantiation
(Actual
);
11955 elsif Has_Discriminants
(Ancestor
) then
11957 ("actual for & must have known discriminants", Actual
, Gen_T
);
11958 Abandon_Instantiation
(Actual
);
11961 if not Subtypes_Statically_Compatible
11962 (Act_T
, Ancestor
, Formal_Derived_Matching
=> True)
11965 ("constraint on actual is incompatible with formal", Actual
);
11966 Abandon_Instantiation
(Actual
);
11970 -- If the formal and actual types are abstract, check that there
11971 -- are no abstract primitives of the actual type that correspond to
11972 -- nonabstract primitives of the formal type (second sentence of
11975 if Is_Abstract_Type
(A_Gen_T
) and then Is_Abstract_Type
(Act_T
) then
11976 Check_Abstract_Primitives
: declare
11977 Gen_Prims
: constant Elist_Id
:=
11978 Primitive_Operations
(A_Gen_T
);
11979 Gen_Elmt
: Elmt_Id
;
11980 Gen_Subp
: Entity_Id
;
11981 Anc_Subp
: Entity_Id
;
11982 Anc_Formal
: Entity_Id
;
11983 Anc_F_Type
: Entity_Id
;
11985 Act_Prims
: constant Elist_Id
:= Primitive_Operations
(Act_T
);
11986 Act_Elmt
: Elmt_Id
;
11987 Act_Subp
: Entity_Id
;
11988 Act_Formal
: Entity_Id
;
11989 Act_F_Type
: Entity_Id
;
11991 Subprograms_Correspond
: Boolean;
11993 function Is_Tagged_Ancestor
(T1
, T2
: Entity_Id
) return Boolean;
11994 -- Returns true if T2 is derived directly or indirectly from
11995 -- T1, including derivations from interfaces. T1 and T2 are
11996 -- required to be specific tagged base types.
11998 ------------------------
11999 -- Is_Tagged_Ancestor --
12000 ------------------------
12002 function Is_Tagged_Ancestor
(T1
, T2
: Entity_Id
) return Boolean
12004 Intfc_Elmt
: Elmt_Id
;
12007 -- The predicate is satisfied if the types are the same
12012 -- If we've reached the top of the derivation chain then
12013 -- we know that T1 is not an ancestor of T2.
12015 elsif Etype
(T2
) = T2
then
12018 -- Proceed to check T2's immediate parent
12020 elsif Is_Ancestor
(T1
, Base_Type
(Etype
(T2
))) then
12023 -- Finally, check to see if T1 is an ancestor of any of T2's
12027 Intfc_Elmt
:= First_Elmt
(Interfaces
(T2
));
12028 while Present
(Intfc_Elmt
) loop
12029 if Is_Ancestor
(T1
, Node
(Intfc_Elmt
)) then
12033 Next_Elmt
(Intfc_Elmt
);
12038 end Is_Tagged_Ancestor
;
12040 -- Start of processing for Check_Abstract_Primitives
12043 -- Loop over all of the formal derived type's primitives
12045 Gen_Elmt
:= First_Elmt
(Gen_Prims
);
12046 while Present
(Gen_Elmt
) loop
12047 Gen_Subp
:= Node
(Gen_Elmt
);
12049 -- If the primitive of the formal is not abstract, then
12050 -- determine whether there is a corresponding primitive of
12051 -- the actual type that's abstract.
12053 if not Is_Abstract_Subprogram
(Gen_Subp
) then
12054 Act_Elmt
:= First_Elmt
(Act_Prims
);
12055 while Present
(Act_Elmt
) loop
12056 Act_Subp
:= Node
(Act_Elmt
);
12058 -- If we find an abstract primitive of the actual,
12059 -- then we need to test whether it corresponds to the
12060 -- subprogram from which the generic formal primitive
12063 if Is_Abstract_Subprogram
(Act_Subp
) then
12064 Anc_Subp
:= Alias
(Gen_Subp
);
12066 -- Test whether we have a corresponding primitive
12067 -- by comparing names, kinds, formal types, and
12070 if Chars
(Anc_Subp
) = Chars
(Act_Subp
)
12071 and then Ekind
(Anc_Subp
) = Ekind
(Act_Subp
)
12073 Anc_Formal
:= First_Formal
(Anc_Subp
);
12074 Act_Formal
:= First_Formal
(Act_Subp
);
12075 while Present
(Anc_Formal
)
12076 and then Present
(Act_Formal
)
12078 Anc_F_Type
:= Etype
(Anc_Formal
);
12079 Act_F_Type
:= Etype
(Act_Formal
);
12081 if Ekind
(Anc_F_Type
) =
12082 E_Anonymous_Access_Type
12084 Anc_F_Type
:= Designated_Type
(Anc_F_Type
);
12086 if Ekind
(Act_F_Type
) =
12087 E_Anonymous_Access_Type
12090 Designated_Type
(Act_F_Type
);
12096 Ekind
(Act_F_Type
) = E_Anonymous_Access_Type
12101 Anc_F_Type
:= Base_Type
(Anc_F_Type
);
12102 Act_F_Type
:= Base_Type
(Act_F_Type
);
12104 -- If the formal is controlling, then the
12105 -- the type of the actual primitive's formal
12106 -- must be derived directly or indirectly
12107 -- from the type of the ancestor primitive's
12110 if Is_Controlling_Formal
(Anc_Formal
) then
12111 if not Is_Tagged_Ancestor
12112 (Anc_F_Type
, Act_F_Type
)
12117 -- Otherwise the types of the formals must
12120 elsif Anc_F_Type
/= Act_F_Type
then
12124 Next_Entity
(Anc_Formal
);
12125 Next_Entity
(Act_Formal
);
12128 -- If we traversed through all of the formals
12129 -- then so far the subprograms correspond, so
12130 -- now check that any result types correspond.
12132 if No
(Anc_Formal
) and then No
(Act_Formal
) then
12133 Subprograms_Correspond
:= True;
12135 if Ekind
(Act_Subp
) = E_Function
then
12136 Anc_F_Type
:= Etype
(Anc_Subp
);
12137 Act_F_Type
:= Etype
(Act_Subp
);
12139 if Ekind
(Anc_F_Type
) =
12140 E_Anonymous_Access_Type
12143 Designated_Type
(Anc_F_Type
);
12145 if Ekind
(Act_F_Type
) =
12146 E_Anonymous_Access_Type
12149 Designated_Type
(Act_F_Type
);
12151 Subprograms_Correspond
:= False;
12156 = E_Anonymous_Access_Type
12158 Subprograms_Correspond
:= False;
12161 Anc_F_Type
:= Base_Type
(Anc_F_Type
);
12162 Act_F_Type
:= Base_Type
(Act_F_Type
);
12164 -- Now either the result types must be
12165 -- the same or, if the result type is
12166 -- controlling, the result type of the
12167 -- actual primitive must descend from the
12168 -- result type of the ancestor primitive.
12170 if Subprograms_Correspond
12171 and then Anc_F_Type
/= Act_F_Type
12173 Has_Controlling_Result
(Anc_Subp
)
12174 and then not Is_Tagged_Ancestor
12175 (Anc_F_Type
, Act_F_Type
)
12177 Subprograms_Correspond
:= False;
12181 -- Found a matching subprogram belonging to
12182 -- formal ancestor type, so actual subprogram
12183 -- corresponds and this violates 3.9.3(9).
12185 if Subprograms_Correspond
then
12187 ("abstract subprogram & overrides "
12188 & "nonabstract subprogram of ancestor",
12195 Next_Elmt
(Act_Elmt
);
12199 Next_Elmt
(Gen_Elmt
);
12201 end Check_Abstract_Primitives
;
12204 -- Verify that limitedness matches. If parent is a limited
12205 -- interface then the generic formal is not unless declared
12206 -- explicitly so. If not declared limited, the actual cannot be
12207 -- limited (see AI05-0087).
12209 -- Even though this AI is a binding interpretation, we enable the
12210 -- check only in Ada 2012 mode, because this improper construct
12211 -- shows up in user code and in existing B-tests.
12213 if Is_Limited_Type
(Act_T
)
12214 and then not Is_Limited_Type
(A_Gen_T
)
12215 and then Ada_Version
>= Ada_2012
12217 if In_Instance
then
12221 ("actual for non-limited & cannot be a limited type",
12223 Explain_Limited_Type
(Act_T
, Actual
);
12224 Abandon_Instantiation
(Actual
);
12227 end Validate_Derived_Type_Instance
;
12229 ----------------------------------------
12230 -- Validate_Discriminated_Formal_Type --
12231 ----------------------------------------
12233 procedure Validate_Discriminated_Formal_Type
is
12234 Formal_Discr
: Entity_Id
;
12235 Actual_Discr
: Entity_Id
;
12236 Formal_Subt
: Entity_Id
;
12239 if Has_Discriminants
(A_Gen_T
) then
12240 if not Has_Discriminants
(Act_T
) then
12242 ("actual for & must have discriminants", Actual
, Gen_T
);
12243 Abandon_Instantiation
(Actual
);
12245 elsif Is_Constrained
(Act_T
) then
12247 ("actual for & must be unconstrained", Actual
, Gen_T
);
12248 Abandon_Instantiation
(Actual
);
12251 Formal_Discr
:= First_Discriminant
(A_Gen_T
);
12252 Actual_Discr
:= First_Discriminant
(Act_T
);
12253 while Formal_Discr
/= Empty
loop
12254 if Actual_Discr
= Empty
then
12256 ("discriminants on actual do not match formal",
12258 Abandon_Instantiation
(Actual
);
12261 Formal_Subt
:= Get_Instance_Of
(Etype
(Formal_Discr
));
12263 -- Access discriminants match if designated types do
12265 if Ekind
(Base_Type
(Formal_Subt
)) = E_Anonymous_Access_Type
12266 and then (Ekind
(Base_Type
(Etype
(Actual_Discr
)))) =
12267 E_Anonymous_Access_Type
12270 (Designated_Type
(Base_Type
(Formal_Subt
))) =
12271 Designated_Type
(Base_Type
(Etype
(Actual_Discr
)))
12275 elsif Base_Type
(Formal_Subt
) /=
12276 Base_Type
(Etype
(Actual_Discr
))
12279 ("types of actual discriminants must match formal",
12281 Abandon_Instantiation
(Actual
);
12283 elsif not Subtypes_Statically_Match
12284 (Formal_Subt
, Etype
(Actual_Discr
))
12285 and then Ada_Version
>= Ada_95
12288 ("subtypes of actual discriminants must match formal",
12290 Abandon_Instantiation
(Actual
);
12293 Next_Discriminant
(Formal_Discr
);
12294 Next_Discriminant
(Actual_Discr
);
12297 if Actual_Discr
/= Empty
then
12299 ("discriminants on actual do not match formal",
12301 Abandon_Instantiation
(Actual
);
12305 end Validate_Discriminated_Formal_Type
;
12307 ---------------------------------------
12308 -- Validate_Incomplete_Type_Instance --
12309 ---------------------------------------
12311 procedure Validate_Incomplete_Type_Instance
is
12313 if not Is_Tagged_Type
(Act_T
)
12314 and then Is_Tagged_Type
(A_Gen_T
)
12317 ("actual for & must be a tagged type", Actual
, Gen_T
);
12320 Validate_Discriminated_Formal_Type
;
12321 end Validate_Incomplete_Type_Instance
;
12323 --------------------------------------
12324 -- Validate_Interface_Type_Instance --
12325 --------------------------------------
12327 procedure Validate_Interface_Type_Instance
is
12329 if not Is_Interface
(Act_T
) then
12331 ("actual for formal interface type must be an interface",
12334 elsif Is_Limited_Type
(Act_T
) /= Is_Limited_Type
(A_Gen_T
)
12335 or else Is_Task_Interface
(A_Gen_T
) /= Is_Task_Interface
(Act_T
)
12336 or else Is_Protected_Interface
(A_Gen_T
) /=
12337 Is_Protected_Interface
(Act_T
)
12338 or else Is_Synchronized_Interface
(A_Gen_T
) /=
12339 Is_Synchronized_Interface
(Act_T
)
12342 ("actual for interface& does not match (RM 12.5.5(4))",
12345 end Validate_Interface_Type_Instance
;
12347 ------------------------------------
12348 -- Validate_Private_Type_Instance --
12349 ------------------------------------
12351 procedure Validate_Private_Type_Instance
is
12353 if Is_Limited_Type
(Act_T
)
12354 and then not Is_Limited_Type
(A_Gen_T
)
12356 if In_Instance
then
12360 ("actual for non-limited & cannot be a limited type", Actual
,
12362 Explain_Limited_Type
(Act_T
, Actual
);
12363 Abandon_Instantiation
(Actual
);
12366 elsif Known_To_Have_Preelab_Init
(A_Gen_T
)
12367 and then not Has_Preelaborable_Initialization
(Act_T
)
12370 ("actual for & must have preelaborable initialization", Actual
,
12373 elsif not Is_Definite_Subtype
(Act_T
)
12374 and then Is_Definite_Subtype
(A_Gen_T
)
12375 and then Ada_Version
>= Ada_95
12378 ("actual for & must be a definite subtype", Actual
, Gen_T
);
12380 elsif not Is_Tagged_Type
(Act_T
)
12381 and then Is_Tagged_Type
(A_Gen_T
)
12384 ("actual for & must be a tagged type", Actual
, Gen_T
);
12387 Validate_Discriminated_Formal_Type
;
12389 end Validate_Private_Type_Instance
;
12391 -- Start of processing for Instantiate_Type
12394 if Get_Instance_Of
(A_Gen_T
) /= A_Gen_T
then
12395 Error_Msg_N
("duplicate instantiation of generic type", Actual
);
12396 return New_List
(Error
);
12398 elsif not Is_Entity_Name
(Actual
)
12399 or else not Is_Type
(Entity
(Actual
))
12402 ("expect valid subtype mark to instantiate &", Actual
, Gen_T
);
12403 Abandon_Instantiation
(Actual
);
12406 Act_T
:= Entity
(Actual
);
12408 -- Ada 2005 (AI-216): An Unchecked_Union subtype shall only be passed
12409 -- as a generic actual parameter if the corresponding formal type
12410 -- does not have a known_discriminant_part, or is a formal derived
12411 -- type that is an Unchecked_Union type.
12413 if Is_Unchecked_Union
(Base_Type
(Act_T
)) then
12414 if not Has_Discriminants
(A_Gen_T
)
12415 or else (Is_Derived_Type
(A_Gen_T
)
12416 and then Is_Unchecked_Union
(A_Gen_T
))
12420 Error_Msg_N
("unchecked union cannot be the actual for a "
12421 & "discriminated formal type", Act_T
);
12426 -- Deal with fixed/floating restrictions
12428 if Is_Floating_Point_Type
(Act_T
) then
12429 Check_Restriction
(No_Floating_Point
, Actual
);
12430 elsif Is_Fixed_Point_Type
(Act_T
) then
12431 Check_Restriction
(No_Fixed_Point
, Actual
);
12434 -- Deal with error of using incomplete type as generic actual.
12435 -- This includes limited views of a type, even if the non-limited
12436 -- view may be available.
12438 if Ekind
(Act_T
) = E_Incomplete_Type
12439 or else (Is_Class_Wide_Type
(Act_T
)
12440 and then Ekind
(Root_Type
(Act_T
)) = E_Incomplete_Type
)
12442 -- If the formal is an incomplete type, the actual can be
12443 -- incomplete as well.
12445 if Ekind
(A_Gen_T
) = E_Incomplete_Type
then
12448 elsif Is_Class_Wide_Type
(Act_T
)
12449 or else No
(Full_View
(Act_T
))
12451 Error_Msg_N
("premature use of incomplete type", Actual
);
12452 Abandon_Instantiation
(Actual
);
12454 Act_T
:= Full_View
(Act_T
);
12455 Set_Entity
(Actual
, Act_T
);
12457 if Has_Private_Component
(Act_T
) then
12459 ("premature use of type with private component", Actual
);
12463 -- Deal with error of premature use of private type as generic actual
12465 elsif Is_Private_Type
(Act_T
)
12466 and then Is_Private_Type
(Base_Type
(Act_T
))
12467 and then not Is_Generic_Type
(Act_T
)
12468 and then not Is_Derived_Type
(Act_T
)
12469 and then No
(Full_View
(Root_Type
(Act_T
)))
12471 -- If the formal is an incomplete type, the actual can be
12472 -- private or incomplete as well.
12474 if Ekind
(A_Gen_T
) = E_Incomplete_Type
then
12477 Error_Msg_N
("premature use of private type", Actual
);
12480 elsif Has_Private_Component
(Act_T
) then
12482 ("premature use of type with private component", Actual
);
12485 Set_Instance_Of
(A_Gen_T
, Act_T
);
12487 -- If the type is generic, the class-wide type may also be used
12489 if Is_Tagged_Type
(A_Gen_T
)
12490 and then Is_Tagged_Type
(Act_T
)
12491 and then not Is_Class_Wide_Type
(A_Gen_T
)
12493 Set_Instance_Of
(Class_Wide_Type
(A_Gen_T
),
12494 Class_Wide_Type
(Act_T
));
12497 if not Is_Abstract_Type
(A_Gen_T
)
12498 and then Is_Abstract_Type
(Act_T
)
12501 ("actual of non-abstract formal cannot be abstract", Actual
);
12504 -- A generic scalar type is a first subtype for which we generate
12505 -- an anonymous base type. Indicate that the instance of this base
12506 -- is the base type of the actual.
12508 if Is_Scalar_Type
(A_Gen_T
) then
12509 Set_Instance_Of
(Etype
(A_Gen_T
), Etype
(Act_T
));
12513 if Error_Posted
(Act_T
) then
12516 case Nkind
(Def
) is
12517 when N_Formal_Private_Type_Definition
=>
12518 Validate_Private_Type_Instance
;
12520 when N_Formal_Incomplete_Type_Definition
=>
12521 Validate_Incomplete_Type_Instance
;
12523 when N_Formal_Derived_Type_Definition
=>
12524 Validate_Derived_Type_Instance
;
12526 when N_Formal_Discrete_Type_Definition
=>
12527 if not Is_Discrete_Type
(Act_T
) then
12529 ("expect discrete type in instantiation of&",
12531 Abandon_Instantiation
(Actual
);
12534 Diagnose_Predicated_Actual
;
12536 when N_Formal_Signed_Integer_Type_Definition
=>
12537 if not Is_Signed_Integer_Type
(Act_T
) then
12539 ("expect signed integer type in instantiation of&",
12541 Abandon_Instantiation
(Actual
);
12544 Diagnose_Predicated_Actual
;
12546 when N_Formal_Modular_Type_Definition
=>
12547 if not Is_Modular_Integer_Type
(Act_T
) then
12549 ("expect modular type in instantiation of &",
12551 Abandon_Instantiation
(Actual
);
12554 Diagnose_Predicated_Actual
;
12556 when N_Formal_Floating_Point_Definition
=>
12557 if not Is_Floating_Point_Type
(Act_T
) then
12559 ("expect float type in instantiation of &", Actual
, Gen_T
);
12560 Abandon_Instantiation
(Actual
);
12563 when N_Formal_Ordinary_Fixed_Point_Definition
=>
12564 if not Is_Ordinary_Fixed_Point_Type
(Act_T
) then
12566 ("expect ordinary fixed point type in instantiation of &",
12568 Abandon_Instantiation
(Actual
);
12571 when N_Formal_Decimal_Fixed_Point_Definition
=>
12572 if not Is_Decimal_Fixed_Point_Type
(Act_T
) then
12574 ("expect decimal type in instantiation of &",
12576 Abandon_Instantiation
(Actual
);
12579 when N_Array_Type_Definition
=>
12580 Validate_Array_Type_Instance
;
12582 when N_Access_To_Object_Definition
=>
12583 Validate_Access_Type_Instance
;
12585 when N_Access_Function_Definition |
12586 N_Access_Procedure_Definition
=>
12587 Validate_Access_Subprogram_Instance
;
12589 when N_Record_Definition
=>
12590 Validate_Interface_Type_Instance
;
12592 when N_Derived_Type_Definition
=>
12593 Validate_Derived_Interface_Type_Instance
;
12596 raise Program_Error
;
12601 Subt
:= New_Copy
(Gen_T
);
12603 -- Use adjusted sloc of subtype name as the location for other nodes in
12604 -- the subtype declaration.
12606 Loc
:= Sloc
(Subt
);
12609 Make_Subtype_Declaration
(Loc
,
12610 Defining_Identifier
=> Subt
,
12611 Subtype_Indication
=> New_Occurrence_Of
(Act_T
, Loc
));
12613 if Is_Private_Type
(Act_T
) then
12614 Set_Has_Private_View
(Subtype_Indication
(Decl_Node
));
12616 elsif Is_Access_Type
(Act_T
)
12617 and then Is_Private_Type
(Designated_Type
(Act_T
))
12619 Set_Has_Private_View
(Subtype_Indication
(Decl_Node
));
12622 -- In Ada 2012 the actual may be a limited view. Indicate that
12623 -- the local subtype must be treated as such.
12625 if From_Limited_With
(Act_T
) then
12626 Set_Ekind
(Subt
, E_Incomplete_Subtype
);
12627 Set_From_Limited_With
(Subt
);
12630 Decl_Nodes
:= New_List
(Decl_Node
);
12632 -- Flag actual derived types so their elaboration produces the
12633 -- appropriate renamings for the primitive operations of the ancestor.
12634 -- Flag actual for formal private types as well, to determine whether
12635 -- operations in the private part may override inherited operations.
12636 -- If the formal has an interface list, the ancestor is not the
12637 -- parent, but the analyzed formal that includes the interface
12638 -- operations of all its progenitors.
12640 -- Same treatment for formal private types, so we can check whether the
12641 -- type is tagged limited when validating derivations in the private
12642 -- part. (See AI05-096).
12644 if Nkind
(Def
) = N_Formal_Derived_Type_Definition
then
12645 if Present
(Interface_List
(Def
)) then
12646 Set_Generic_Parent_Type
(Decl_Node
, A_Gen_T
);
12648 Set_Generic_Parent_Type
(Decl_Node
, Ancestor
);
12651 elsif Nkind_In
(Def
, N_Formal_Private_Type_Definition
,
12652 N_Formal_Incomplete_Type_Definition
)
12654 Set_Generic_Parent_Type
(Decl_Node
, A_Gen_T
);
12657 -- If the actual is a synchronized type that implements an interface,
12658 -- the primitive operations are attached to the corresponding record,
12659 -- and we have to treat it as an additional generic actual, so that its
12660 -- primitive operations become visible in the instance. The task or
12661 -- protected type itself does not carry primitive operations.
12663 if Is_Concurrent_Type
(Act_T
)
12664 and then Is_Tagged_Type
(Act_T
)
12665 and then Present
(Corresponding_Record_Type
(Act_T
))
12666 and then Present
(Ancestor
)
12667 and then Is_Interface
(Ancestor
)
12670 Corr_Rec
: constant Entity_Id
:=
12671 Corresponding_Record_Type
(Act_T
);
12672 New_Corr
: Entity_Id
;
12673 Corr_Decl
: Node_Id
;
12676 New_Corr
:= Make_Temporary
(Loc
, 'S');
12678 Make_Subtype_Declaration
(Loc
,
12679 Defining_Identifier
=> New_Corr
,
12680 Subtype_Indication
=>
12681 New_Occurrence_Of
(Corr_Rec
, Loc
));
12682 Append_To
(Decl_Nodes
, Corr_Decl
);
12684 if Ekind
(Act_T
) = E_Task_Type
then
12685 Set_Ekind
(Subt
, E_Task_Subtype
);
12687 Set_Ekind
(Subt
, E_Protected_Subtype
);
12690 Set_Corresponding_Record_Type
(Subt
, Corr_Rec
);
12691 Set_Generic_Parent_Type
(Corr_Decl
, Ancestor
);
12692 Set_Generic_Parent_Type
(Decl_Node
, Empty
);
12696 -- For a floating-point type, capture dimension info if any, because
12697 -- the generated subtype declaration does not come from source and
12698 -- will not process dimensions.
12700 if Is_Floating_Point_Type
(Act_T
) then
12701 Copy_Dimensions
(Act_T
, Subt
);
12705 end Instantiate_Type
;
12707 ---------------------
12708 -- Is_In_Main_Unit --
12709 ---------------------
12711 function Is_In_Main_Unit
(N
: Node_Id
) return Boolean is
12712 Unum
: constant Unit_Number_Type
:= Get_Source_Unit
(N
);
12713 Current_Unit
: Node_Id
;
12716 if Unum
= Main_Unit
then
12719 -- If the current unit is a subunit then it is either the main unit or
12720 -- is being compiled as part of the main unit.
12722 elsif Nkind
(N
) = N_Compilation_Unit
then
12723 return Nkind
(Unit
(N
)) = N_Subunit
;
12726 Current_Unit
:= Parent
(N
);
12727 while Present
(Current_Unit
)
12728 and then Nkind
(Current_Unit
) /= N_Compilation_Unit
12730 Current_Unit
:= Parent
(Current_Unit
);
12733 -- The instantiation node is in the main unit, or else the current node
12734 -- (perhaps as the result of nested instantiations) is in the main unit,
12735 -- or in the declaration of the main unit, which in this last case must
12738 return Unum
= Main_Unit
12739 or else Current_Unit
= Cunit
(Main_Unit
)
12740 or else Current_Unit
= Library_Unit
(Cunit
(Main_Unit
))
12741 or else (Present
(Library_Unit
(Current_Unit
))
12742 and then Is_In_Main_Unit
(Library_Unit
(Current_Unit
)));
12743 end Is_In_Main_Unit
;
12745 ----------------------------
12746 -- Load_Parent_Of_Generic --
12747 ----------------------------
12749 procedure Load_Parent_Of_Generic
12752 Body_Optional
: Boolean := False)
12754 Comp_Unit
: constant Node_Id
:= Cunit
(Get_Source_Unit
(Spec
));
12755 Saved_Style_Check
: constant Boolean := Style_Check
;
12756 Saved_Warnings
: constant Warning_Record
:= Save_Warnings
;
12757 True_Parent
: Node_Id
;
12758 Inst_Node
: Node_Id
;
12760 Previous_Instances
: constant Elist_Id
:= New_Elmt_List
;
12762 procedure Collect_Previous_Instances
(Decls
: List_Id
);
12763 -- Collect all instantiations in the given list of declarations, that
12764 -- precede the generic that we need to load. If the bodies of these
12765 -- instantiations are available, we must analyze them, to ensure that
12766 -- the public symbols generated are the same when the unit is compiled
12767 -- to generate code, and when it is compiled in the context of a unit
12768 -- that needs a particular nested instance. This process is applied to
12769 -- both package and subprogram instances.
12771 --------------------------------
12772 -- Collect_Previous_Instances --
12773 --------------------------------
12775 procedure Collect_Previous_Instances
(Decls
: List_Id
) is
12779 Decl
:= First
(Decls
);
12780 while Present
(Decl
) loop
12781 if Sloc
(Decl
) >= Sloc
(Inst_Node
) then
12784 -- If Decl is an instantiation, then record it as requiring
12785 -- instantiation of the corresponding body, except if it is an
12786 -- abbreviated instantiation generated internally for conformance
12787 -- checking purposes only for the case of a formal package
12788 -- declared without a box (see Instantiate_Formal_Package). Such
12789 -- an instantiation does not generate any code (the actual code
12790 -- comes from actual) and thus does not need to be analyzed here.
12791 -- If the instantiation appears with a generic package body it is
12792 -- not analyzed here either.
12794 elsif Nkind
(Decl
) = N_Package_Instantiation
12795 and then not Is_Internal
(Defining_Entity
(Decl
))
12797 Append_Elmt
(Decl
, Previous_Instances
);
12799 -- For a subprogram instantiation, omit instantiations intrinsic
12800 -- operations (Unchecked_Conversions, etc.) that have no bodies.
12802 elsif Nkind_In
(Decl
, N_Function_Instantiation
,
12803 N_Procedure_Instantiation
)
12804 and then not Is_Intrinsic_Subprogram
(Entity
(Name
(Decl
)))
12806 Append_Elmt
(Decl
, Previous_Instances
);
12808 elsif Nkind
(Decl
) = N_Package_Declaration
then
12809 Collect_Previous_Instances
12810 (Visible_Declarations
(Specification
(Decl
)));
12811 Collect_Previous_Instances
12812 (Private_Declarations
(Specification
(Decl
)));
12814 -- Previous non-generic bodies may contain instances as well
12816 elsif Nkind
(Decl
) = N_Package_Body
12817 and then Ekind
(Corresponding_Spec
(Decl
)) /= E_Generic_Package
12819 Collect_Previous_Instances
(Declarations
(Decl
));
12821 elsif Nkind
(Decl
) = N_Subprogram_Body
12822 and then not Acts_As_Spec
(Decl
)
12823 and then not Is_Generic_Subprogram
(Corresponding_Spec
(Decl
))
12825 Collect_Previous_Instances
(Declarations
(Decl
));
12830 end Collect_Previous_Instances
;
12832 -- Start of processing for Load_Parent_Of_Generic
12835 if not In_Same_Source_Unit
(N
, Spec
)
12836 or else Nkind
(Unit
(Comp_Unit
)) = N_Package_Declaration
12837 or else (Nkind
(Unit
(Comp_Unit
)) = N_Package_Body
12838 and then not Is_In_Main_Unit
(Spec
))
12840 -- Find body of parent of spec, and analyze it. A special case arises
12841 -- when the parent is an instantiation, that is to say when we are
12842 -- currently instantiating a nested generic. In that case, there is
12843 -- no separate file for the body of the enclosing instance. Instead,
12844 -- the enclosing body must be instantiated as if it were a pending
12845 -- instantiation, in order to produce the body for the nested generic
12846 -- we require now. Note that in that case the generic may be defined
12847 -- in a package body, the instance defined in the same package body,
12848 -- and the original enclosing body may not be in the main unit.
12850 Inst_Node
:= Empty
;
12852 True_Parent
:= Parent
(Spec
);
12853 while Present
(True_Parent
)
12854 and then Nkind
(True_Parent
) /= N_Compilation_Unit
12856 if Nkind
(True_Parent
) = N_Package_Declaration
12858 Nkind
(Original_Node
(True_Parent
)) = N_Package_Instantiation
12860 -- Parent is a compilation unit that is an instantiation.
12861 -- Instantiation node has been replaced with package decl.
12863 Inst_Node
:= Original_Node
(True_Parent
);
12866 elsif Nkind
(True_Parent
) = N_Package_Declaration
12867 and then Present
(Generic_Parent
(Specification
(True_Parent
)))
12868 and then Nkind
(Parent
(True_Parent
)) /= N_Compilation_Unit
12870 -- Parent is an instantiation within another specification.
12871 -- Declaration for instance has been inserted before original
12872 -- instantiation node. A direct link would be preferable?
12874 Inst_Node
:= Next
(True_Parent
);
12875 while Present
(Inst_Node
)
12876 and then Nkind
(Inst_Node
) /= N_Package_Instantiation
12881 -- If the instance appears within a generic, and the generic
12882 -- unit is defined within a formal package of the enclosing
12883 -- generic, there is no generic body available, and none
12884 -- needed. A more precise test should be used ???
12886 if No
(Inst_Node
) then
12893 True_Parent
:= Parent
(True_Parent
);
12897 -- Case where we are currently instantiating a nested generic
12899 if Present
(Inst_Node
) then
12900 if Nkind
(Parent
(True_Parent
)) = N_Compilation_Unit
then
12902 -- Instantiation node and declaration of instantiated package
12903 -- were exchanged when only the declaration was needed.
12904 -- Restore instantiation node before proceeding with body.
12906 Set_Unit
(Parent
(True_Parent
), Inst_Node
);
12909 -- Now complete instantiation of enclosing body, if it appears in
12910 -- some other unit. If it appears in the current unit, the body
12911 -- will have been instantiated already.
12913 if No
(Corresponding_Body
(Instance_Spec
(Inst_Node
))) then
12915 -- We need to determine the expander mode to instantiate the
12916 -- enclosing body. Because the generic body we need may use
12917 -- global entities declared in the enclosing package (including
12918 -- aggregates) it is in general necessary to compile this body
12919 -- with expansion enabled, except if we are within a generic
12920 -- package, in which case the usual generic rule applies.
12923 Exp_Status
: Boolean := True;
12927 -- Loop through scopes looking for generic package
12929 Scop
:= Scope
(Defining_Entity
(Instance_Spec
(Inst_Node
)));
12930 while Present
(Scop
)
12931 and then Scop
/= Standard_Standard
12933 if Ekind
(Scop
) = E_Generic_Package
then
12934 Exp_Status
:= False;
12938 Scop
:= Scope
(Scop
);
12941 -- Collect previous instantiations in the unit that contains
12942 -- the desired generic.
12944 if Nkind
(Parent
(True_Parent
)) /= N_Compilation_Unit
12945 and then not Body_Optional
12949 Info
: Pending_Body_Info
;
12953 Par
:= Parent
(Inst_Node
);
12954 while Present
(Par
) loop
12955 exit when Nkind
(Parent
(Par
)) = N_Compilation_Unit
;
12956 Par
:= Parent
(Par
);
12959 pragma Assert
(Present
(Par
));
12961 if Nkind
(Par
) = N_Package_Body
then
12962 Collect_Previous_Instances
(Declarations
(Par
));
12964 elsif Nkind
(Par
) = N_Package_Declaration
then
12965 Collect_Previous_Instances
12966 (Visible_Declarations
(Specification
(Par
)));
12967 Collect_Previous_Instances
12968 (Private_Declarations
(Specification
(Par
)));
12971 -- Enclosing unit is a subprogram body. In this
12972 -- case all instance bodies are processed in order
12973 -- and there is no need to collect them separately.
12978 Decl
:= First_Elmt
(Previous_Instances
);
12979 while Present
(Decl
) loop
12981 (Inst_Node
=> Node
(Decl
),
12983 Instance_Spec
(Node
(Decl
)),
12984 Expander_Status
=> Exp_Status
,
12985 Current_Sem_Unit
=>
12986 Get_Code_Unit
(Sloc
(Node
(Decl
))),
12987 Scope_Suppress
=> Scope_Suppress
,
12988 Local_Suppress_Stack_Top
=>
12989 Local_Suppress_Stack_Top
,
12990 Version
=> Ada_Version
,
12991 Version_Pragma
=> Ada_Version_Pragma
,
12992 Warnings
=> Save_Warnings
,
12993 SPARK_Mode
=> SPARK_Mode
,
12994 SPARK_Mode_Pragma
=> SPARK_Mode_Pragma
);
12996 -- Package instance
12999 Nkind
(Node
(Decl
)) = N_Package_Instantiation
13001 Instantiate_Package_Body
13002 (Info
, Body_Optional
=> True);
13004 -- Subprogram instance
13007 -- The instance_spec is in the wrapper package,
13008 -- usually followed by its local renaming
13009 -- declaration. See Build_Subprogram_Renaming
13014 (Last
(Visible_Declarations
13015 (Specification
(Info
.Act_Decl
))));
13018 N_Subprogram_Renaming_Declaration
13020 Decl
:= Prev
(Decl
);
13023 Info
.Act_Decl
:= Decl
;
13026 Instantiate_Subprogram_Body
13027 (Info
, Body_Optional
=> True);
13035 Instantiate_Package_Body
13037 ((Inst_Node
=> Inst_Node
,
13038 Act_Decl
=> True_Parent
,
13039 Expander_Status
=> Exp_Status
,
13040 Current_Sem_Unit
=> Get_Code_Unit
13041 (Sloc
(Inst_Node
)),
13042 Scope_Suppress
=> Scope_Suppress
,
13043 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
13044 Version
=> Ada_Version
,
13045 Version_Pragma
=> Ada_Version_Pragma
,
13046 Warnings
=> Save_Warnings
,
13047 SPARK_Mode
=> SPARK_Mode
,
13048 SPARK_Mode_Pragma
=> SPARK_Mode_Pragma
)),
13049 Body_Optional
=> Body_Optional
);
13053 -- Case where we are not instantiating a nested generic
13056 Opt
.Style_Check
:= False;
13057 Expander_Mode_Save_And_Set
(True);
13058 Load_Needed_Body
(Comp_Unit
, OK
);
13059 Opt
.Style_Check
:= Saved_Style_Check
;
13060 Restore_Warnings
(Saved_Warnings
);
13061 Expander_Mode_Restore
;
13064 and then Unit_Requires_Body
(Defining_Entity
(Spec
))
13065 and then not Body_Optional
13068 Bname
: constant Unit_Name_Type
:=
13069 Get_Body_Name
(Get_Unit_Name
(Unit
(Comp_Unit
)));
13072 -- In CodePeer mode, the missing body may make the analysis
13073 -- incomplete, but we do not treat it as fatal.
13075 if CodePeer_Mode
then
13079 Error_Msg_Unit_1
:= Bname
;
13080 Error_Msg_N
("this instantiation requires$!", N
);
13081 Error_Msg_File_1
:=
13082 Get_File_Name
(Bname
, Subunit
=> False);
13083 Error_Msg_N
("\but file{ was not found!", N
);
13084 raise Unrecoverable_Error
;
13091 -- If loading parent of the generic caused an instantiation circularity,
13092 -- we abandon compilation at this point, because otherwise in some cases
13093 -- we get into trouble with infinite recursions after this point.
13095 if Circularity_Detected
then
13096 raise Unrecoverable_Error
;
13098 end Load_Parent_Of_Generic
;
13100 ---------------------------------
13101 -- Map_Formal_Package_Entities --
13102 ---------------------------------
13104 procedure Map_Formal_Package_Entities
(Form
: Entity_Id
; Act
: Entity_Id
) is
13109 Set_Instance_Of
(Form
, Act
);
13111 -- Traverse formal and actual package to map the corresponding entities.
13112 -- We skip over internal entities that may be generated during semantic
13113 -- analysis, and find the matching entities by name, given that they
13114 -- must appear in the same order.
13116 E1
:= First_Entity
(Form
);
13117 E2
:= First_Entity
(Act
);
13118 while Present
(E1
) and then E1
/= First_Private_Entity
(Form
) loop
13119 -- Could this test be a single condition??? Seems like it could, and
13120 -- isn't FPE (Form) a constant anyway???
13122 if not Is_Internal
(E1
)
13123 and then Present
(Parent
(E1
))
13124 and then not Is_Class_Wide_Type
(E1
)
13125 and then not Is_Internal_Name
(Chars
(E1
))
13127 while Present
(E2
) and then Chars
(E2
) /= Chars
(E1
) loop
13134 Set_Instance_Of
(E1
, E2
);
13136 if Is_Type
(E1
) and then Is_Tagged_Type
(E2
) then
13137 Set_Instance_Of
(Class_Wide_Type
(E1
), Class_Wide_Type
(E2
));
13140 if Is_Constrained
(E1
) then
13141 Set_Instance_Of
(Base_Type
(E1
), Base_Type
(E2
));
13144 if Ekind
(E1
) = E_Package
and then No
(Renamed_Object
(E1
)) then
13145 Map_Formal_Package_Entities
(E1
, E2
);
13152 end Map_Formal_Package_Entities
;
13154 -----------------------
13155 -- Move_Freeze_Nodes --
13156 -----------------------
13158 procedure Move_Freeze_Nodes
13159 (Out_Of
: Entity_Id
;
13164 Next_Decl
: Node_Id
;
13165 Next_Node
: Node_Id
:= After
;
13168 function Is_Outer_Type
(T
: Entity_Id
) return Boolean;
13169 -- Check whether entity is declared in a scope external to that of the
13172 -------------------
13173 -- Is_Outer_Type --
13174 -------------------
13176 function Is_Outer_Type
(T
: Entity_Id
) return Boolean is
13177 Scop
: Entity_Id
:= Scope
(T
);
13180 if Scope_Depth
(Scop
) < Scope_Depth
(Out_Of
) then
13184 while Scop
/= Standard_Standard
loop
13185 if Scop
= Out_Of
then
13188 Scop
:= Scope
(Scop
);
13196 -- Start of processing for Move_Freeze_Nodes
13203 -- First remove the freeze nodes that may appear before all other
13207 while Present
(Decl
)
13208 and then Nkind
(Decl
) = N_Freeze_Entity
13209 and then Is_Outer_Type
(Entity
(Decl
))
13211 Decl
:= Remove_Head
(L
);
13212 Insert_After
(Next_Node
, Decl
);
13213 Set_Analyzed
(Decl
, False);
13218 -- Next scan the list of declarations and remove each freeze node that
13219 -- appears ahead of the current node.
13221 while Present
(Decl
) loop
13222 while Present
(Next
(Decl
))
13223 and then Nkind
(Next
(Decl
)) = N_Freeze_Entity
13224 and then Is_Outer_Type
(Entity
(Next
(Decl
)))
13226 Next_Decl
:= Remove_Next
(Decl
);
13227 Insert_After
(Next_Node
, Next_Decl
);
13228 Set_Analyzed
(Next_Decl
, False);
13229 Next_Node
:= Next_Decl
;
13232 -- If the declaration is a nested package or concurrent type, then
13233 -- recurse. Nested generic packages will have been processed from the
13236 case Nkind
(Decl
) is
13237 when N_Package_Declaration
=>
13238 Spec
:= Specification
(Decl
);
13240 when N_Task_Type_Declaration
=>
13241 Spec
:= Task_Definition
(Decl
);
13243 when N_Protected_Type_Declaration
=>
13244 Spec
:= Protected_Definition
(Decl
);
13250 if Present
(Spec
) then
13251 Move_Freeze_Nodes
(Out_Of
, Next_Node
, Visible_Declarations
(Spec
));
13252 Move_Freeze_Nodes
(Out_Of
, Next_Node
, Private_Declarations
(Spec
));
13257 end Move_Freeze_Nodes
;
13263 function Next_Assoc
(E
: Assoc_Ptr
) return Assoc_Ptr
is
13265 return Generic_Renamings
.Table
(E
).Next_In_HTable
;
13268 ------------------------
13269 -- Preanalyze_Actuals --
13270 ------------------------
13272 procedure Preanalyze_Actuals
(N
: Node_Id
; Inst
: Entity_Id
:= Empty
) is
13275 Errs
: constant Int
:= Serious_Errors_Detected
;
13277 Cur
: Entity_Id
:= Empty
;
13278 -- Current homograph of the instance name
13281 -- Saved visibility status of the current homograph
13284 Assoc
:= First
(Generic_Associations
(N
));
13286 -- If the instance is a child unit, its name may hide an outer homonym,
13287 -- so make it invisible to perform name resolution on the actuals.
13289 if Nkind
(Defining_Unit_Name
(N
)) = N_Defining_Program_Unit_Name
13291 (Current_Entity
(Defining_Identifier
(Defining_Unit_Name
(N
))))
13293 Cur
:= Current_Entity
(Defining_Identifier
(Defining_Unit_Name
(N
)));
13295 if Is_Compilation_Unit
(Cur
) then
13296 Vis
:= Is_Immediately_Visible
(Cur
);
13297 Set_Is_Immediately_Visible
(Cur
, False);
13303 while Present
(Assoc
) loop
13304 if Nkind
(Assoc
) /= N_Others_Choice
then
13305 Act
:= Explicit_Generic_Actual_Parameter
(Assoc
);
13307 -- Within a nested instantiation, a defaulted actual is an empty
13308 -- association, so nothing to analyze. If the subprogram actual
13309 -- is an attribute, analyze prefix only, because actual is not a
13310 -- complete attribute reference.
13312 -- If actual is an allocator, analyze expression only. The full
13313 -- analysis can generate code, and if instance is a compilation
13314 -- unit we have to wait until the package instance is installed
13315 -- to have a proper place to insert this code.
13317 -- String literals may be operators, but at this point we do not
13318 -- know whether the actual is a formal subprogram or a string.
13323 elsif Nkind
(Act
) = N_Attribute_Reference
then
13324 Analyze
(Prefix
(Act
));
13326 elsif Nkind
(Act
) = N_Explicit_Dereference
then
13327 Analyze
(Prefix
(Act
));
13329 elsif Nkind
(Act
) = N_Allocator
then
13331 Expr
: constant Node_Id
:= Expression
(Act
);
13334 if Nkind
(Expr
) = N_Subtype_Indication
then
13335 Analyze
(Subtype_Mark
(Expr
));
13337 -- Analyze separately each discriminant constraint, when
13338 -- given with a named association.
13344 Constr
:= First
(Constraints
(Constraint
(Expr
)));
13345 while Present
(Constr
) loop
13346 if Nkind
(Constr
) = N_Discriminant_Association
then
13347 Analyze
(Expression
(Constr
));
13361 elsif Nkind
(Act
) /= N_Operator_Symbol
then
13364 if Is_Entity_Name
(Act
)
13365 and then Is_Type
(Entity
(Act
))
13366 and then From_Limited_With
(Entity
(Act
))
13368 Append_Elmt
(Entity
(Act
), Incomplete_Actuals
(Inst
));
13372 if Errs
/= Serious_Errors_Detected
then
13374 -- Do a minimal analysis of the generic, to prevent spurious
13375 -- warnings complaining about the generic being unreferenced,
13376 -- before abandoning the instantiation.
13378 Analyze
(Name
(N
));
13380 if Is_Entity_Name
(Name
(N
))
13381 and then Etype
(Name
(N
)) /= Any_Type
13383 Generate_Reference
(Entity
(Name
(N
)), Name
(N
));
13384 Set_Is_Instantiated
(Entity
(Name
(N
)));
13387 if Present
(Cur
) then
13389 -- For the case of a child instance hiding an outer homonym,
13390 -- provide additional warning which might explain the error.
13392 Set_Is_Immediately_Visible
(Cur
, Vis
);
13394 ("& hides outer unit with the same name??",
13395 N
, Defining_Unit_Name
(N
));
13398 Abandon_Instantiation
(Act
);
13405 if Present
(Cur
) then
13406 Set_Is_Immediately_Visible
(Cur
, Vis
);
13408 end Preanalyze_Actuals
;
13410 -------------------
13411 -- Remove_Parent --
13412 -------------------
13414 procedure Remove_Parent
(In_Body
: Boolean := False) is
13415 S
: Entity_Id
:= Current_Scope
;
13416 -- S is the scope containing the instantiation just completed. The scope
13417 -- stack contains the parent instances of the instantiation, followed by
13426 -- After child instantiation is complete, remove from scope stack the
13427 -- extra copy of the current scope, and then remove parent instances.
13429 if not In_Body
then
13432 while Current_Scope
/= S
loop
13433 P
:= Current_Scope
;
13434 End_Package_Scope
(Current_Scope
);
13436 if In_Open_Scopes
(P
) then
13437 E
:= First_Entity
(P
);
13438 while Present
(E
) loop
13439 Set_Is_Immediately_Visible
(E
, True);
13443 -- If instantiation is declared in a block, it is the enclosing
13444 -- scope that might be a parent instance. Note that only one
13445 -- block can be involved, because the parent instances have
13446 -- been installed within it.
13448 if Ekind
(P
) = E_Block
then
13449 Cur_P
:= Scope
(P
);
13454 if Is_Generic_Instance
(Cur_P
) and then P
/= Current_Scope
then
13455 -- We are within an instance of some sibling. Retain
13456 -- visibility of parent, for proper subsequent cleanup, and
13457 -- reinstall private declarations as well.
13459 Set_In_Private_Part
(P
);
13460 Install_Private_Declarations
(P
);
13463 -- If the ultimate parent is a top-level unit recorded in
13464 -- Instance_Parent_Unit, then reset its visibility to what it was
13465 -- before instantiation. (It's not clear what the purpose is of
13466 -- testing whether Scope (P) is In_Open_Scopes, but that test was
13467 -- present before the ultimate parent test was added.???)
13469 elsif not In_Open_Scopes
(Scope
(P
))
13470 or else (P
= Instance_Parent_Unit
13471 and then not Parent_Unit_Visible
)
13473 Set_Is_Immediately_Visible
(P
, False);
13475 -- If the current scope is itself an instantiation of a generic
13476 -- nested within P, and we are in the private part of body of this
13477 -- instantiation, restore the full views of P, that were removed
13478 -- in End_Package_Scope above. This obscure case can occur when a
13479 -- subunit of a generic contains an instance of a child unit of
13480 -- its generic parent unit.
13482 elsif S
= Current_Scope
and then Is_Generic_Instance
(S
) then
13484 Par
: constant Entity_Id
:=
13485 Generic_Parent
(Package_Specification
(S
));
13488 and then P
= Scope
(Par
)
13489 and then (In_Package_Body
(S
) or else In_Private_Part
(S
))
13491 Set_In_Private_Part
(P
);
13492 Install_Private_Declarations
(P
);
13498 -- Reset visibility of entities in the enclosing scope
13500 Set_Is_Hidden_Open_Scope
(Current_Scope
, False);
13502 Hidden
:= First_Elmt
(Hidden_Entities
);
13503 while Present
(Hidden
) loop
13504 Set_Is_Immediately_Visible
(Node
(Hidden
), True);
13505 Next_Elmt
(Hidden
);
13509 -- Each body is analyzed separately, and there is no context that
13510 -- needs preserving from one body instance to the next, so remove all
13511 -- parent scopes that have been installed.
13513 while Present
(S
) loop
13514 End_Package_Scope
(S
);
13515 Set_Is_Immediately_Visible
(S
, False);
13516 S
:= Current_Scope
;
13517 exit when S
= Standard_Standard
;
13526 procedure Restore_Env
is
13527 Saved
: Instance_Env
renames Instance_Envs
.Table
(Instance_Envs
.Last
);
13530 if No
(Current_Instantiated_Parent
.Act_Id
) then
13531 -- Restore environment after subprogram inlining
13533 Restore_Private_Views
(Empty
);
13536 Current_Instantiated_Parent
:= Saved
.Instantiated_Parent
;
13537 Exchanged_Views
:= Saved
.Exchanged_Views
;
13538 Hidden_Entities
:= Saved
.Hidden_Entities
;
13539 Current_Sem_Unit
:= Saved
.Current_Sem_Unit
;
13540 Parent_Unit_Visible
:= Saved
.Parent_Unit_Visible
;
13541 Instance_Parent_Unit
:= Saved
.Instance_Parent_Unit
;
13543 Restore_Opt_Config_Switches
(Saved
.Switches
);
13545 Instance_Envs
.Decrement_Last
;
13548 ---------------------------
13549 -- Restore_Private_Views --
13550 ---------------------------
13552 procedure Restore_Private_Views
13553 (Pack_Id
: Entity_Id
;
13554 Is_Package
: Boolean := True)
13559 Dep_Elmt
: Elmt_Id
;
13562 procedure Restore_Nested_Formal
(Formal
: Entity_Id
);
13563 -- Hide the generic formals of formal packages declared with box which
13564 -- were reachable in the current instantiation.
13566 ---------------------------
13567 -- Restore_Nested_Formal --
13568 ---------------------------
13570 procedure Restore_Nested_Formal
(Formal
: Entity_Id
) is
13574 if Present
(Renamed_Object
(Formal
))
13575 and then Denotes_Formal_Package
(Renamed_Object
(Formal
), True)
13579 elsif Present
(Associated_Formal_Package
(Formal
)) then
13580 Ent
:= First_Entity
(Formal
);
13581 while Present
(Ent
) loop
13582 exit when Ekind
(Ent
) = E_Package
13583 and then Renamed_Entity
(Ent
) = Renamed_Entity
(Formal
);
13585 Set_Is_Hidden
(Ent
);
13586 Set_Is_Potentially_Use_Visible
(Ent
, False);
13588 -- If package, then recurse
13590 if Ekind
(Ent
) = E_Package
then
13591 Restore_Nested_Formal
(Ent
);
13597 end Restore_Nested_Formal
;
13599 -- Start of processing for Restore_Private_Views
13602 M
:= First_Elmt
(Exchanged_Views
);
13603 while Present
(M
) loop
13606 -- Subtypes of types whose views have been exchanged, and that are
13607 -- defined within the instance, were not on the Private_Dependents
13608 -- list on entry to the instance, so they have to be exchanged
13609 -- explicitly now, in order to remain consistent with the view of the
13612 if Ekind_In
(Typ
, E_Private_Type
,
13613 E_Limited_Private_Type
,
13614 E_Record_Type_With_Private
)
13616 Dep_Elmt
:= First_Elmt
(Private_Dependents
(Typ
));
13617 while Present
(Dep_Elmt
) loop
13618 Dep_Typ
:= Node
(Dep_Elmt
);
13620 if Scope
(Dep_Typ
) = Pack_Id
13621 and then Present
(Full_View
(Dep_Typ
))
13623 Replace_Elmt
(Dep_Elmt
, Full_View
(Dep_Typ
));
13624 Exchange_Declarations
(Dep_Typ
);
13627 Next_Elmt
(Dep_Elmt
);
13631 Exchange_Declarations
(Node
(M
));
13635 if No
(Pack_Id
) then
13639 -- Make the generic formal parameters private, and make the formal types
13640 -- into subtypes of the actuals again.
13642 E
:= First_Entity
(Pack_Id
);
13643 while Present
(E
) loop
13644 Set_Is_Hidden
(E
, True);
13647 and then Nkind
(Parent
(E
)) = N_Subtype_Declaration
13649 -- If the actual for E is itself a generic actual type from
13650 -- an enclosing instance, E is still a generic actual type
13651 -- outside of the current instance. This matter when resolving
13652 -- an overloaded call that may be ambiguous in the enclosing
13653 -- instance, when two of its actuals coincide.
13655 if Is_Entity_Name
(Subtype_Indication
(Parent
(E
)))
13656 and then Is_Generic_Actual_Type
13657 (Entity
(Subtype_Indication
(Parent
(E
))))
13661 Set_Is_Generic_Actual_Type
(E
, False);
13664 -- An unusual case of aliasing: the actual may also be directly
13665 -- visible in the generic, and be private there, while it is fully
13666 -- visible in the context of the instance. The internal subtype
13667 -- is private in the instance but has full visibility like its
13668 -- parent in the enclosing scope. This enforces the invariant that
13669 -- the privacy status of all private dependents of a type coincide
13670 -- with that of the parent type. This can only happen when a
13671 -- generic child unit is instantiated within a sibling.
13673 if Is_Private_Type
(E
)
13674 and then not Is_Private_Type
(Etype
(E
))
13676 Exchange_Declarations
(E
);
13679 elsif Ekind
(E
) = E_Package
then
13681 -- The end of the renaming list is the renaming of the generic
13682 -- package itself. If the instance is a subprogram, all entities
13683 -- in the corresponding package are renamings. If this entity is
13684 -- a formal package, make its own formals private as well. The
13685 -- actual in this case is itself the renaming of an instantiation.
13686 -- If the entity is not a package renaming, it is the entity
13687 -- created to validate formal package actuals: ignore it.
13689 -- If the actual is itself a formal package for the enclosing
13690 -- generic, or the actual for such a formal package, it remains
13691 -- visible on exit from the instance, and therefore nothing needs
13692 -- to be done either, except to keep it accessible.
13694 if Is_Package
and then Renamed_Object
(E
) = Pack_Id
then
13697 elsif Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
then
13701 Denotes_Formal_Package
(Renamed_Object
(E
), True, Pack_Id
)
13703 Set_Is_Hidden
(E
, False);
13707 Act_P
: constant Entity_Id
:= Renamed_Object
(E
);
13711 Id
:= First_Entity
(Act_P
);
13713 and then Id
/= First_Private_Entity
(Act_P
)
13715 exit when Ekind
(Id
) = E_Package
13716 and then Renamed_Object
(Id
) = Act_P
;
13718 Set_Is_Hidden
(Id
, True);
13719 Set_Is_Potentially_Use_Visible
(Id
, In_Use
(Act_P
));
13721 if Ekind
(Id
) = E_Package
then
13722 Restore_Nested_Formal
(Id
);
13733 end Restore_Private_Views
;
13740 (Gen_Unit
: Entity_Id
;
13741 Act_Unit
: Entity_Id
)
13745 Set_Instance_Env
(Gen_Unit
, Act_Unit
);
13748 ----------------------------
13749 -- Save_Global_References --
13750 ----------------------------
13752 procedure Save_Global_References
(Templ
: Node_Id
) is
13754 -- ??? it is horrible to use global variables in highly recursive code
13757 -- The entity of the current associated node
13759 Gen_Scope
: Entity_Id
;
13760 -- The scope of the generic for which references are being saved
13763 -- The current associated node
13765 function Is_Global
(E
: Entity_Id
) return Boolean;
13766 -- Check whether entity is defined outside of generic unit. Examine the
13767 -- scope of an entity, and the scope of the scope, etc, until we find
13768 -- either Standard, in which case the entity is global, or the generic
13769 -- unit itself, which indicates that the entity is local. If the entity
13770 -- is the generic unit itself, as in the case of a recursive call, or
13771 -- the enclosing generic unit, if different from the current scope, then
13772 -- it is local as well, because it will be replaced at the point of
13773 -- instantiation. On the other hand, if it is a reference to a child
13774 -- unit of a common ancestor, which appears in an instantiation, it is
13775 -- global because it is used to denote a specific compilation unit at
13776 -- the time the instantiations will be analyzed.
13778 procedure Reset_Entity
(N
: Node_Id
);
13779 -- Save semantic information on global entity so that it is not resolved
13780 -- again at instantiation time.
13782 procedure Save_Entity_Descendants
(N
: Node_Id
);
13783 -- Apply Save_Global_References to the two syntactic descendants of
13784 -- non-terminal nodes that carry an Associated_Node and are processed
13785 -- through Reset_Entity. Once the global entity (if any) has been
13786 -- captured together with its type, only two syntactic descendants need
13787 -- to be traversed to complete the processing of the tree rooted at N.
13788 -- This applies to Selected_Components, Expanded_Names, and to Operator
13789 -- nodes. N can also be a character literal, identifier, or operator
13790 -- symbol node, but the call has no effect in these cases.
13792 procedure Save_Global_Defaults
(N1
: Node_Id
; N2
: Node_Id
);
13793 -- Default actuals in nested instances must be handled specially
13794 -- because there is no link to them from the original tree. When an
13795 -- actual subprogram is given by a default, we add an explicit generic
13796 -- association for it in the instantiation node. When we save the
13797 -- global references on the name of the instance, we recover the list
13798 -- of generic associations, and add an explicit one to the original
13799 -- generic tree, through which a global actual can be preserved.
13800 -- Similarly, if a child unit is instantiated within a sibling, in the
13801 -- context of the parent, we must preserve the identifier of the parent
13802 -- so that it can be properly resolved in a subsequent instantiation.
13804 procedure Save_Global_Descendant
(D
: Union_Id
);
13805 -- Apply Save_References recursively to the descendents of node D
13807 procedure Save_References
(N
: Node_Id
);
13808 -- This is the recursive procedure that does the work, once the
13809 -- enclosing generic scope has been established.
13815 function Is_Global
(E
: Entity_Id
) return Boolean is
13818 function Is_Instance_Node
(Decl
: Node_Id
) return Boolean;
13819 -- Determine whether the parent node of a reference to a child unit
13820 -- denotes an instantiation or a formal package, in which case the
13821 -- reference to the child unit is global, even if it appears within
13822 -- the current scope (e.g. when the instance appears within the body
13823 -- of an ancestor).
13825 ----------------------
13826 -- Is_Instance_Node --
13827 ----------------------
13829 function Is_Instance_Node
(Decl
: Node_Id
) return Boolean is
13831 return Nkind
(Decl
) in N_Generic_Instantiation
13833 Nkind
(Original_Node
(Decl
)) = N_Formal_Package_Declaration
;
13834 end Is_Instance_Node
;
13836 -- Start of processing for Is_Global
13839 if E
= Gen_Scope
then
13842 elsif E
= Standard_Standard
then
13845 elsif Is_Child_Unit
(E
)
13846 and then (Is_Instance_Node
(Parent
(N2
))
13847 or else (Nkind
(Parent
(N2
)) = N_Expanded_Name
13848 and then N2
= Selector_Name
(Parent
(N2
))
13850 Is_Instance_Node
(Parent
(Parent
(N2
)))))
13856 while Se
/= Gen_Scope
loop
13857 if Se
= Standard_Standard
then
13872 procedure Reset_Entity
(N
: Node_Id
) is
13873 procedure Set_Global_Type
(N
: Node_Id
; N2
: Node_Id
);
13874 -- If the type of N2 is global to the generic unit, save the type in
13875 -- the generic node. Just as we perform name capture for explicit
13876 -- references within the generic, we must capture the global types
13877 -- of local entities because they may participate in resolution in
13880 function Top_Ancestor
(E
: Entity_Id
) return Entity_Id
;
13881 -- Find the ultimate ancestor of the current unit. If it is not a
13882 -- generic unit, then the name of the current unit in the prefix of
13883 -- an expanded name must be replaced with its generic homonym to
13884 -- ensure that it will be properly resolved in an instance.
13886 ---------------------
13887 -- Set_Global_Type --
13888 ---------------------
13890 procedure Set_Global_Type
(N
: Node_Id
; N2
: Node_Id
) is
13891 Typ
: constant Entity_Id
:= Etype
(N2
);
13894 Set_Etype
(N
, Typ
);
13896 -- If the entity of N is not the associated node, this is a
13897 -- nested generic and it has an associated node as well, whose
13898 -- type is already the full view (see below). Indicate that the
13899 -- original node has a private view.
13901 if Entity
(N
) /= N2
and then Has_Private_View
(Entity
(N
)) then
13902 Set_Has_Private_View
(N
);
13905 -- If not a private type, nothing else to do
13907 if not Is_Private_Type
(Typ
) then
13908 if Is_Array_Type
(Typ
)
13909 and then Is_Private_Type
(Component_Type
(Typ
))
13911 Set_Has_Private_View
(N
);
13914 -- If it is a derivation of a private type in a context where no
13915 -- full view is needed, nothing to do either.
13917 elsif No
(Full_View
(Typ
)) and then Typ
/= Etype
(Typ
) then
13920 -- Otherwise mark the type for flipping and use the full view when
13924 Set_Has_Private_View
(N
);
13926 if Present
(Full_View
(Typ
)) then
13927 Set_Etype
(N2
, Full_View
(Typ
));
13930 end Set_Global_Type
;
13936 function Top_Ancestor
(E
: Entity_Id
) return Entity_Id
is
13941 while Is_Child_Unit
(Par
) loop
13942 Par
:= Scope
(Par
);
13948 -- Start of processing for Reset_Entity
13951 N2
:= Get_Associated_Node
(N
);
13954 if Present
(E
) then
13956 -- If the node is an entry call to an entry in an enclosing task,
13957 -- it is rewritten as a selected component. No global entity to
13958 -- preserve in this case, since the expansion will be redone in
13961 if not Nkind_In
(E
, N_Defining_Character_Literal
,
13962 N_Defining_Identifier
,
13963 N_Defining_Operator_Symbol
)
13965 Set_Associated_Node
(N
, Empty
);
13966 Set_Etype
(N
, Empty
);
13970 -- If the entity is an itype created as a subtype of an access
13971 -- type with a null exclusion restore source entity for proper
13972 -- visibility. The itype will be created anew in the instance.
13975 and then Ekind
(E
) = E_Access_Subtype
13976 and then Is_Entity_Name
(N
)
13977 and then Chars
(Etype
(E
)) = Chars
(N
)
13980 Set_Entity
(N2
, E
);
13984 if Is_Global
(E
) then
13986 -- If the entity is a package renaming that is the prefix of
13987 -- an expanded name, it has been rewritten as the renamed
13988 -- package, which is necessary semantically but complicates
13989 -- ASIS tree traversal, so we recover the original entity to
13990 -- expose the renaming. Take into account that the context may
13991 -- be a nested generic, that the original node may itself have
13992 -- an associated node that had better be an entity, and that
13993 -- the current node is still a selected component.
13995 if Ekind
(E
) = E_Package
13996 and then Nkind
(N
) = N_Selected_Component
13997 and then Nkind
(Parent
(N
)) = N_Expanded_Name
13998 and then Present
(Original_Node
(N2
))
13999 and then Is_Entity_Name
(Original_Node
(N2
))
14000 and then Present
(Entity
(Original_Node
(N2
)))
14002 if Is_Global
(Entity
(Original_Node
(N2
))) then
14003 N2
:= Original_Node
(N2
);
14004 Set_Associated_Node
(N
, N2
);
14005 Set_Global_Type
(N
, N2
);
14007 -- Renaming is local, and will be resolved in instance
14010 Set_Associated_Node
(N
, Empty
);
14011 Set_Etype
(N
, Empty
);
14015 Set_Global_Type
(N
, N2
);
14018 elsif Nkind
(N
) = N_Op_Concat
14019 and then Is_Generic_Type
(Etype
(N2
))
14020 and then (Base_Type
(Etype
(Right_Opnd
(N2
))) = Etype
(N2
)
14022 Base_Type
(Etype
(Left_Opnd
(N2
))) = Etype
(N2
))
14023 and then Is_Intrinsic_Subprogram
(E
)
14027 -- Entity is local. Mark generic node as unresolved. Note that now
14028 -- it does not have an entity.
14031 Set_Associated_Node
(N
, Empty
);
14032 Set_Etype
(N
, Empty
);
14035 if Nkind
(Parent
(N
)) in N_Generic_Instantiation
14036 and then N
= Name
(Parent
(N
))
14038 Save_Global_Defaults
(Parent
(N
), Parent
(N2
));
14041 elsif Nkind
(Parent
(N
)) = N_Selected_Component
14042 and then Nkind
(Parent
(N2
)) = N_Expanded_Name
14044 if Is_Global
(Entity
(Parent
(N2
))) then
14045 Change_Selected_Component_To_Expanded_Name
(Parent
(N
));
14046 Set_Associated_Node
(Parent
(N
), Parent
(N2
));
14047 Set_Global_Type
(Parent
(N
), Parent
(N2
));
14048 Save_Entity_Descendants
(N
);
14050 -- If this is a reference to the current generic entity, replace
14051 -- by the name of the generic homonym of the current package. This
14052 -- is because in an instantiation Par.P.Q will not resolve to the
14053 -- name of the instance, whose enclosing scope is not necessarily
14054 -- Par. We use the generic homonym rather that the name of the
14055 -- generic itself because it may be hidden by a local declaration.
14057 elsif In_Open_Scopes
(Entity
(Parent
(N2
)))
14059 Is_Generic_Unit
(Top_Ancestor
(Entity
(Prefix
(Parent
(N2
)))))
14061 if Ekind
(Entity
(Parent
(N2
))) = E_Generic_Package
then
14062 Rewrite
(Parent
(N
),
14063 Make_Identifier
(Sloc
(N
),
14065 Chars
(Generic_Homonym
(Entity
(Parent
(N2
))))));
14067 Rewrite
(Parent
(N
),
14068 Make_Identifier
(Sloc
(N
),
14069 Chars
=> Chars
(Selector_Name
(Parent
(N2
)))));
14073 if Nkind
(Parent
(Parent
(N
))) in N_Generic_Instantiation
14074 and then Parent
(N
) = Name
(Parent
(Parent
(N
)))
14076 Save_Global_Defaults
14077 (Parent
(Parent
(N
)), Parent
(Parent
(N2
)));
14080 -- A selected component may denote a static constant that has been
14081 -- folded. If the static constant is global to the generic, capture
14082 -- its value. Otherwise the folding will happen in any instantiation.
14084 elsif Nkind
(Parent
(N
)) = N_Selected_Component
14085 and then Nkind_In
(Parent
(N2
), N_Integer_Literal
, N_Real_Literal
)
14087 if Present
(Entity
(Original_Node
(Parent
(N2
))))
14088 and then Is_Global
(Entity
(Original_Node
(Parent
(N2
))))
14090 Rewrite
(Parent
(N
), New_Copy
(Parent
(N2
)));
14091 Set_Analyzed
(Parent
(N
), False);
14094 -- A selected component may be transformed into a parameterless
14095 -- function call. If the called entity is global, rewrite the node
14096 -- appropriately, i.e. as an extended name for the global entity.
14098 elsif Nkind
(Parent
(N
)) = N_Selected_Component
14099 and then Nkind
(Parent
(N2
)) = N_Function_Call
14100 and then N
= Selector_Name
(Parent
(N
))
14102 if No
(Parameter_Associations
(Parent
(N2
))) then
14103 if Is_Global
(Entity
(Name
(Parent
(N2
)))) then
14104 Change_Selected_Component_To_Expanded_Name
(Parent
(N
));
14105 Set_Associated_Node
(Parent
(N
), Name
(Parent
(N2
)));
14106 Set_Global_Type
(Parent
(N
), Name
(Parent
(N2
)));
14107 Save_Entity_Descendants
(N
);
14110 Set_Is_Prefixed_Call
(Parent
(N
));
14111 Set_Associated_Node
(N
, Empty
);
14112 Set_Etype
(N
, Empty
);
14115 -- In Ada 2005, X.F may be a call to a primitive operation,
14116 -- rewritten as F (X). This rewriting will be done again in an
14117 -- instance, so keep the original node. Global entities will be
14118 -- captured as for other constructs. Indicate that this must
14119 -- resolve as a call, to prevent accidental overloading in the
14120 -- instance, if both a component and a primitive operation appear
14124 Set_Is_Prefixed_Call
(Parent
(N
));
14127 -- Entity is local. Reset in generic unit, so that node is resolved
14128 -- anew at the point of instantiation.
14131 Set_Associated_Node
(N
, Empty
);
14132 Set_Etype
(N
, Empty
);
14136 -----------------------------
14137 -- Save_Entity_Descendants --
14138 -----------------------------
14140 procedure Save_Entity_Descendants
(N
: Node_Id
) is
14143 when N_Binary_Op
=>
14144 Save_Global_Descendant
(Union_Id
(Left_Opnd
(N
)));
14145 Save_Global_Descendant
(Union_Id
(Right_Opnd
(N
)));
14148 Save_Global_Descendant
(Union_Id
(Right_Opnd
(N
)));
14150 when N_Expanded_Name |
14151 N_Selected_Component
=>
14152 Save_Global_Descendant
(Union_Id
(Prefix
(N
)));
14153 Save_Global_Descendant
(Union_Id
(Selector_Name
(N
)));
14155 when N_Identifier |
14156 N_Character_Literal |
14157 N_Operator_Symbol
=>
14161 raise Program_Error
;
14163 end Save_Entity_Descendants
;
14165 --------------------------
14166 -- Save_Global_Defaults --
14167 --------------------------
14169 procedure Save_Global_Defaults
(N1
: Node_Id
; N2
: Node_Id
) is
14170 Loc
: constant Source_Ptr
:= Sloc
(N1
);
14171 Assoc2
: constant List_Id
:= Generic_Associations
(N2
);
14172 Gen_Id
: constant Entity_Id
:= Get_Generic_Entity
(N2
);
14179 Actual
: Entity_Id
;
14182 Assoc1
:= Generic_Associations
(N1
);
14184 if Present
(Assoc1
) then
14185 Act1
:= First
(Assoc1
);
14188 Set_Generic_Associations
(N1
, New_List
);
14189 Assoc1
:= Generic_Associations
(N1
);
14192 if Present
(Assoc2
) then
14193 Act2
:= First
(Assoc2
);
14198 while Present
(Act1
) and then Present
(Act2
) loop
14203 -- Find the associations added for default subprograms
14205 if Present
(Act2
) then
14206 while Nkind
(Act2
) /= N_Generic_Association
14207 or else No
(Entity
(Selector_Name
(Act2
)))
14208 or else not Is_Overloadable
(Entity
(Selector_Name
(Act2
)))
14213 -- Add a similar association if the default is global. The
14214 -- renaming declaration for the actual has been analyzed, and
14215 -- its alias is the program it renames. Link the actual in the
14216 -- original generic tree with the node in the analyzed tree.
14218 while Present
(Act2
) loop
14219 Subp
:= Entity
(Selector_Name
(Act2
));
14220 Def
:= Explicit_Generic_Actual_Parameter
(Act2
);
14222 -- Following test is defence against rubbish errors
14224 if No
(Alias
(Subp
)) then
14228 -- Retrieve the resolved actual from the renaming declaration
14229 -- created for the instantiated formal.
14231 Actual
:= Entity
(Name
(Parent
(Parent
(Subp
))));
14232 Set_Entity
(Def
, Actual
);
14233 Set_Etype
(Def
, Etype
(Actual
));
14235 if Is_Global
(Actual
) then
14237 Make_Generic_Association
(Loc
,
14239 New_Occurrence_Of
(Subp
, Loc
),
14240 Explicit_Generic_Actual_Parameter
=>
14241 New_Occurrence_Of
(Actual
, Loc
));
14243 Set_Associated_Node
14244 (Explicit_Generic_Actual_Parameter
(Ndec
), Def
);
14246 Append
(Ndec
, Assoc1
);
14248 -- If there are other defaults, add a dummy association in case
14249 -- there are other defaulted formals with the same name.
14251 elsif Present
(Next
(Act2
)) then
14253 Make_Generic_Association
(Loc
,
14255 New_Occurrence_Of
(Subp
, Loc
),
14256 Explicit_Generic_Actual_Parameter
=> Empty
);
14258 Append
(Ndec
, Assoc1
);
14265 if Nkind
(Name
(N1
)) = N_Identifier
14266 and then Is_Child_Unit
(Gen_Id
)
14267 and then Is_Global
(Gen_Id
)
14268 and then Is_Generic_Unit
(Scope
(Gen_Id
))
14269 and then In_Open_Scopes
(Scope
(Gen_Id
))
14271 -- This is an instantiation of a child unit within a sibling, so
14272 -- that the generic parent is in scope. An eventual instance must
14273 -- occur within the scope of an instance of the parent. Make name
14274 -- in instance into an expanded name, to preserve the identifier
14275 -- of the parent, so it can be resolved subsequently.
14277 Rewrite
(Name
(N2
),
14278 Make_Expanded_Name
(Loc
,
14279 Chars
=> Chars
(Gen_Id
),
14280 Prefix
=> New_Occurrence_Of
(Scope
(Gen_Id
), Loc
),
14281 Selector_Name
=> New_Occurrence_Of
(Gen_Id
, Loc
)));
14282 Set_Entity
(Name
(N2
), Gen_Id
);
14284 Rewrite
(Name
(N1
),
14285 Make_Expanded_Name
(Loc
,
14286 Chars
=> Chars
(Gen_Id
),
14287 Prefix
=> New_Occurrence_Of
(Scope
(Gen_Id
), Loc
),
14288 Selector_Name
=> New_Occurrence_Of
(Gen_Id
, Loc
)));
14290 Set_Associated_Node
(Name
(N1
), Name
(N2
));
14291 Set_Associated_Node
(Prefix
(Name
(N1
)), Empty
);
14292 Set_Associated_Node
14293 (Selector_Name
(Name
(N1
)), Selector_Name
(Name
(N2
)));
14294 Set_Etype
(Name
(N1
), Etype
(Gen_Id
));
14296 end Save_Global_Defaults
;
14298 ----------------------------
14299 -- Save_Global_Descendant --
14300 ----------------------------
14302 procedure Save_Global_Descendant
(D
: Union_Id
) is
14306 if D
in Node_Range
then
14307 if D
= Union_Id
(Empty
) then
14310 elsif Nkind
(Node_Id
(D
)) /= N_Compilation_Unit
then
14311 Save_References
(Node_Id
(D
));
14314 elsif D
in List_Range
then
14315 if D
= Union_Id
(No_List
) or else Is_Empty_List
(List_Id
(D
)) then
14319 N1
:= First
(List_Id
(D
));
14320 while Present
(N1
) loop
14321 Save_References
(N1
);
14326 -- Element list or other non-node field, nothing to do
14331 end Save_Global_Descendant
;
14333 ---------------------
14334 -- Save_References --
14335 ---------------------
14337 -- This is the recursive procedure that does the work once the enclosing
14338 -- generic scope has been established. We have to treat specially a
14339 -- number of node rewritings that are required by semantic processing
14340 -- and which change the kind of nodes in the generic copy: typically
14341 -- constant-folding, replacing an operator node by a string literal, or
14342 -- a selected component by an expanded name. In each of those cases, the
14343 -- transformation is propagated to the generic unit.
14345 procedure Save_References
(N
: Node_Id
) is
14346 Loc
: constant Source_Ptr
:= Sloc
(N
);
14348 function Requires_Delayed_Save
(Nod
: Node_Id
) return Boolean;
14349 -- Determine whether arbitrary node Nod requires delayed capture of
14350 -- global references within its aspect specifications.
14352 procedure Save_References_In_Aggregate
(N
: Node_Id
);
14353 -- Save all global references in [extension] aggregate node N
14355 procedure Save_References_In_Char_Lit_Or_Op_Symbol
(N
: Node_Id
);
14356 -- Save all global references in a character literal or operator
14357 -- symbol denoted by N.
14359 procedure Save_References_In_Descendants
(N
: Node_Id
);
14360 -- Save all global references in all descendants of node N
14362 procedure Save_References_In_Identifier
(N
: Node_Id
);
14363 -- Save all global references in identifier node N
14365 procedure Save_References_In_Operator
(N
: Node_Id
);
14366 -- Save all global references in operator node N
14368 procedure Save_References_In_Pragma
(Prag
: Node_Id
);
14369 -- Save all global references found within the expression of pragma
14372 ---------------------------
14373 -- Requires_Delayed_Save --
14374 ---------------------------
14376 function Requires_Delayed_Save
(Nod
: Node_Id
) return Boolean is
14378 -- Generic packages and subprograms require delayed capture of
14379 -- global references within their aspects due to the timing of
14380 -- annotation analysis.
14382 if Nkind_In
(Nod
, N_Generic_Package_Declaration
,
14383 N_Generic_Subprogram_Declaration
,
14385 N_Package_Body_Stub
,
14387 N_Subprogram_Body_Stub
)
14389 -- Since the capture of global references is done on the
14390 -- unanalyzed generic template, there is no information around
14391 -- to infer the context. Use the Associated_Entity linkages to
14392 -- peek into the analyzed generic copy and determine what the
14393 -- template corresponds to.
14395 if Nod
= Templ
then
14397 Is_Generic_Declaration_Or_Body
14398 (Unit_Declaration_Node
14399 (Associated_Entity
(Defining_Entity
(Nod
))));
14401 -- Otherwise the generic unit being processed is not the top
14402 -- level template. It is safe to capture of global references
14403 -- within the generic unit because at this point the top level
14404 -- copy is fully analyzed.
14410 -- Otherwise capture the global references without interference
14415 end Requires_Delayed_Save
;
14417 ----------------------------------
14418 -- Save_References_In_Aggregate --
14419 ----------------------------------
14421 procedure Save_References_In_Aggregate
(N
: Node_Id
) is
14423 Qual
: Node_Id
:= Empty
;
14424 Typ
: Entity_Id
:= Empty
;
14426 use Atree
.Unchecked_Access
;
14427 -- This code section is part of implementing an untyped tree
14428 -- traversal, so it needs direct access to node fields.
14431 N2
:= Get_Associated_Node
(N
);
14433 if Present
(N2
) then
14436 -- In an instance within a generic, use the name of the actual
14437 -- and not the original generic parameter. If the actual is
14438 -- global in the current generic it must be preserved for its
14441 if Nkind
(Parent
(Typ
)) = N_Subtype_Declaration
14442 and then Present
(Generic_Parent_Type
(Parent
(Typ
)))
14444 Typ
:= Base_Type
(Typ
);
14445 Set_Etype
(N2
, Typ
);
14449 if No
(N2
) or else No
(Typ
) or else not Is_Global
(Typ
) then
14450 Set_Associated_Node
(N
, Empty
);
14452 -- If the aggregate is an actual in a call, it has been
14453 -- resolved in the current context, to some local type. The
14454 -- enclosing call may have been disambiguated by the aggregate,
14455 -- and this disambiguation might fail at instantiation time
14456 -- because the type to which the aggregate did resolve is not
14457 -- preserved. In order to preserve some of this information,
14458 -- wrap the aggregate in a qualified expression, using the id
14459 -- of its type. For further disambiguation we qualify the type
14460 -- name with its scope (if visible) because both id's will have
14461 -- corresponding entities in an instance. This resolves most of
14462 -- the problems with missing type information on aggregates in
14466 and then Nkind
(N2
) = Nkind
(N
)
14467 and then Nkind
(Parent
(N2
)) in N_Subprogram_Call
14468 and then Present
(Typ
)
14469 and then Comes_From_Source
(Typ
)
14471 Nam
:= Make_Identifier
(Loc
, Chars
(Typ
));
14473 if Is_Immediately_Visible
(Scope
(Typ
)) then
14475 Make_Selected_Component
(Loc
,
14477 Make_Identifier
(Loc
, Chars
(Scope
(Typ
))),
14478 Selector_Name
=> Nam
);
14482 Make_Qualified_Expression
(Loc
,
14483 Subtype_Mark
=> Nam
,
14484 Expression
=> Relocate_Node
(N
));
14488 Save_Global_Descendant
(Field1
(N
));
14489 Save_Global_Descendant
(Field2
(N
));
14490 Save_Global_Descendant
(Field3
(N
));
14491 Save_Global_Descendant
(Field5
(N
));
14493 if Present
(Qual
) then
14496 end Save_References_In_Aggregate
;
14498 ----------------------------------------------
14499 -- Save_References_In_Char_Lit_Or_Op_Symbol --
14500 ----------------------------------------------
14502 procedure Save_References_In_Char_Lit_Or_Op_Symbol
(N
: Node_Id
) is
14504 if Nkind
(N
) = Nkind
(Get_Associated_Node
(N
)) then
14507 elsif Nkind
(N
) = N_Operator_Symbol
14508 and then Nkind
(Get_Associated_Node
(N
)) = N_String_Literal
14510 Change_Operator_Symbol_To_String_Literal
(N
);
14512 end Save_References_In_Char_Lit_Or_Op_Symbol
;
14514 ------------------------------------
14515 -- Save_References_In_Descendants --
14516 ------------------------------------
14518 procedure Save_References_In_Descendants
(N
: Node_Id
) is
14519 use Atree
.Unchecked_Access
;
14520 -- This code section is part of implementing an untyped tree
14521 -- traversal, so it needs direct access to node fields.
14524 Save_Global_Descendant
(Field1
(N
));
14525 Save_Global_Descendant
(Field2
(N
));
14526 Save_Global_Descendant
(Field3
(N
));
14527 Save_Global_Descendant
(Field4
(N
));
14528 Save_Global_Descendant
(Field5
(N
));
14529 end Save_References_In_Descendants
;
14531 -----------------------------------
14532 -- Save_References_In_Identifier --
14533 -----------------------------------
14535 procedure Save_References_In_Identifier
(N
: Node_Id
) is
14537 -- The node did not undergo a transformation
14539 if Nkind
(N
) = Nkind
(Get_Associated_Node
(N
)) then
14541 -- If this is a discriminant reference, always save it. It is
14542 -- used in the instance to find the corresponding discriminant
14543 -- positionally rather than by name.
14545 Set_Original_Discriminant
14546 (N
, Original_Discriminant
(Get_Associated_Node
(N
)));
14549 -- The analysis of the generic copy transformed the identifier
14550 -- into another construct. Propagate the changes to the template.
14553 N2
:= Get_Associated_Node
(N
);
14555 -- The identifier denotes a call to a parameterless function.
14556 -- Mark the node as resolved when the function is external.
14558 if Nkind
(N2
) = N_Function_Call
then
14559 E
:= Entity
(Name
(N2
));
14561 if Present
(E
) and then Is_Global
(E
) then
14562 Set_Etype
(N
, Etype
(N2
));
14564 Set_Associated_Node
(N
, Empty
);
14565 Set_Etype
(N
, Empty
);
14568 -- The identifier denotes a named number that was constant
14569 -- folded. Preserve the original name for ASIS and undo the
14570 -- constant folding which will be repeated in the instance.
14572 elsif Nkind_In
(N2
, N_Integer_Literal
, N_Real_Literal
)
14573 and then Is_Entity_Name
(Original_Node
(N2
))
14575 Set_Associated_Node
(N
, Original_Node
(N2
));
14578 -- The identifier resolved to a string literal. Propagate this
14579 -- information to the generic template.
14581 elsif Nkind
(N2
) = N_String_Literal
then
14582 Rewrite
(N
, New_Copy
(N2
));
14584 -- The identifier is rewritten as a dereference if it is the
14585 -- prefix of an implicit dereference. Preserve the original
14586 -- tree as the analysis of the instance will expand the node
14587 -- again, but preserve the resolved entity if it is global.
14589 elsif Nkind
(N2
) = N_Explicit_Dereference
then
14590 if Is_Entity_Name
(Prefix
(N2
))
14591 and then Present
(Entity
(Prefix
(N2
)))
14592 and then Is_Global
(Entity
(Prefix
(N2
)))
14594 Set_Associated_Node
(N
, Prefix
(N2
));
14596 elsif Nkind
(Prefix
(N2
)) = N_Function_Call
14597 and then Present
(Entity
(Name
(Prefix
(N2
))))
14598 and then Is_Global
(Entity
(Name
(Prefix
(N2
))))
14601 Make_Explicit_Dereference
(Loc
,
14603 Make_Function_Call
(Loc
,
14606 (Entity
(Name
(Prefix
(N2
))), Loc
))));
14609 Set_Associated_Node
(N
, Empty
);
14610 Set_Etype
(N
, Empty
);
14613 -- The subtype mark of a nominally unconstrained object is
14614 -- rewritten as a subtype indication using the bounds of the
14615 -- expression. Recover the original subtype mark.
14617 elsif Nkind
(N2
) = N_Subtype_Indication
14618 and then Is_Entity_Name
(Original_Node
(N2
))
14620 Set_Associated_Node
(N
, Original_Node
(N2
));
14624 end Save_References_In_Identifier
;
14626 ---------------------------------
14627 -- Save_References_In_Operator --
14628 ---------------------------------
14630 procedure Save_References_In_Operator
(N
: Node_Id
) is
14632 -- The node did not undergo a transformation
14634 if Nkind
(N
) = Nkind
(Get_Associated_Node
(N
)) then
14635 if Nkind
(N
) = N_Op_Concat
then
14636 Set_Is_Component_Left_Opnd
(N
,
14637 Is_Component_Left_Opnd
(Get_Associated_Node
(N
)));
14639 Set_Is_Component_Right_Opnd
(N
,
14640 Is_Component_Right_Opnd
(Get_Associated_Node
(N
)));
14645 -- The analysis of the generic copy transformed the operator into
14646 -- some other construct. Propagate the changes to the template.
14649 N2
:= Get_Associated_Node
(N
);
14651 -- The operator resoved to a function call
14653 if Nkind
(N2
) = N_Function_Call
then
14654 E
:= Entity
(Name
(N2
));
14656 if Present
(E
) and then Is_Global
(E
) then
14657 Set_Etype
(N
, Etype
(N2
));
14659 Set_Associated_Node
(N
, Empty
);
14660 Set_Etype
(N
, Empty
);
14663 -- The operator was folded into a literal
14665 elsif Nkind_In
(N2
, N_Integer_Literal
,
14669 if Present
(Original_Node
(N2
))
14670 and then Nkind
(Original_Node
(N2
)) = Nkind
(N
)
14672 -- Operation was constant-folded. Whenever possible,
14673 -- recover semantic information from unfolded node,
14676 Set_Associated_Node
(N
, Original_Node
(N2
));
14678 if Nkind
(N
) = N_Op_Concat
then
14679 Set_Is_Component_Left_Opnd
(N
,
14680 Is_Component_Left_Opnd
(Get_Associated_Node
(N
)));
14681 Set_Is_Component_Right_Opnd
(N
,
14682 Is_Component_Right_Opnd
(Get_Associated_Node
(N
)));
14687 -- Propagate the constant folding back to the template
14690 Rewrite
(N
, New_Copy
(N2
));
14691 Set_Analyzed
(N
, False);
14694 -- The operator was folded into an enumeration literal. Retain
14695 -- the entity to avoid spurious ambiguities if it is overloaded
14696 -- at the point of instantiation or inlining.
14698 elsif Nkind
(N2
) = N_Identifier
14699 and then Ekind
(Entity
(N2
)) = E_Enumeration_Literal
14701 Rewrite
(N
, New_Copy
(N2
));
14702 Set_Analyzed
(N
, False);
14706 -- Complete the operands check if node has not been constant
14709 if Nkind
(N
) in N_Op
then
14710 Save_Entity_Descendants
(N
);
14712 end Save_References_In_Operator
;
14714 -------------------------------
14715 -- Save_References_In_Pragma --
14716 -------------------------------
14718 procedure Save_References_In_Pragma
(Prag
: Node_Id
) is
14720 Do_Save
: Boolean := True;
14722 use Atree
.Unchecked_Access
;
14723 -- This code section is part of implementing an untyped tree
14724 -- traversal, so it needs direct access to node fields.
14727 -- Do not save global references in pragmas generated from aspects
14728 -- because the pragmas will be regenerated at instantiation time.
14730 if From_Aspect_Specification
(Prag
) then
14733 -- The capture of global references within contract-related source
14734 -- pragmas associated with generic packages, subprograms or their
14735 -- respective bodies must be delayed due to timing of annotation
14736 -- analysis. Global references are still captured in routine
14737 -- Save_Global_References_In_Contract.
14739 elsif Is_Generic_Contract_Pragma
(Prag
) and then Prag
/= Templ
then
14740 if Is_Package_Contract_Annotation
(Prag
) then
14741 Context
:= Find_Related_Package_Or_Body
(Prag
);
14744 pragma Assert
(Is_Subprogram_Contract_Annotation
(Prag
));
14745 Context
:= Find_Related_Subprogram_Or_Body
(Prag
);
14748 -- The use of Original_Node accounts for the case when the
14749 -- related context is generic template.
14751 if Requires_Delayed_Save
(Original_Node
(Context
)) then
14756 -- For all other cases, save all global references within the
14757 -- descendants, but skip the following semantic fields:
14759 -- Field1 - Next_Pragma
14760 -- Field3 - Corresponding_Aspect
14761 -- Field5 - Next_Rep_Item
14764 Save_Global_Descendant
(Field2
(Prag
));
14765 Save_Global_Descendant
(Field4
(Prag
));
14767 end Save_References_In_Pragma
;
14769 -- Start of processing for Save_References
14777 elsif Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
) then
14778 Save_References_In_Aggregate
(N
);
14780 -- Character literals, operator symbols
14782 elsif Nkind_In
(N
, N_Character_Literal
, N_Operator_Symbol
) then
14783 Save_References_In_Char_Lit_Or_Op_Symbol
(N
);
14785 -- Defining identifiers
14787 elsif Nkind
(N
) in N_Entity
then
14792 elsif Nkind
(N
) = N_Identifier
then
14793 Save_References_In_Identifier
(N
);
14797 elsif Nkind
(N
) in N_Op
then
14798 Save_References_In_Operator
(N
);
14802 elsif Nkind
(N
) = N_Pragma
then
14803 Save_References_In_Pragma
(N
);
14806 Save_References_In_Descendants
(N
);
14809 -- Save all global references found within the aspect specifications
14810 -- of the related node.
14812 if Permits_Aspect_Specifications
(N
) and then Has_Aspects
(N
) then
14814 -- The capture of global references within aspects associated with
14815 -- generic packages, subprograms or their bodies must be delayed
14816 -- due to timing of annotation analysis. Global references are
14817 -- still captured in routine Save_Global_References_In_Contract.
14819 if Requires_Delayed_Save
(N
) then
14822 -- Otherwise save all global references within the aspects
14825 Save_Global_References_In_Aspects
(N
);
14828 end Save_References
;
14830 -- Start of processing for Save_Global_References
14833 Gen_Scope
:= Current_Scope
;
14835 -- If the generic unit is a child unit, references to entities in the
14836 -- parent are treated as local, because they will be resolved anew in
14837 -- the context of the instance of the parent.
14839 while Is_Child_Unit
(Gen_Scope
)
14840 and then Ekind
(Scope
(Gen_Scope
)) = E_Generic_Package
14842 Gen_Scope
:= Scope
(Gen_Scope
);
14845 Save_References
(Templ
);
14846 end Save_Global_References
;
14848 ---------------------------------------
14849 -- Save_Global_References_In_Aspects --
14850 ---------------------------------------
14852 procedure Save_Global_References_In_Aspects
(N
: Node_Id
) is
14857 Asp
:= First
(Aspect_Specifications
(N
));
14858 while Present
(Asp
) loop
14859 Expr
:= Expression
(Asp
);
14861 if Present
(Expr
) then
14862 Save_Global_References
(Expr
);
14867 end Save_Global_References_In_Aspects
;
14869 ----------------------------------------
14870 -- Save_Global_References_In_Contract --
14871 ----------------------------------------
14873 procedure Save_Global_References_In_Contract
14875 Gen_Id
: Entity_Id
)
14877 procedure Save_Global_References_In_List
(First_Prag
: Node_Id
);
14878 -- Save all global references in contract-related source pragmas found
14879 -- in the list starting with pragma First_Prag.
14881 ------------------------------------
14882 -- Save_Global_References_In_List --
14883 ------------------------------------
14885 procedure Save_Global_References_In_List
(First_Prag
: Node_Id
) is
14889 Prag
:= First_Prag
;
14890 while Present
(Prag
) loop
14891 if Is_Generic_Contract_Pragma
(Prag
) then
14892 Save_Global_References
(Prag
);
14895 Prag
:= Next_Pragma
(Prag
);
14897 end Save_Global_References_In_List
;
14901 Items
: constant Node_Id
:= Contract
(Defining_Entity
(Templ
));
14903 -- Start of processing for Save_Global_References_In_Contract
14906 -- The entity of the analyzed generic copy must be on the scope stack
14907 -- to ensure proper detection of global references.
14909 Push_Scope
(Gen_Id
);
14911 if Permits_Aspect_Specifications
(Templ
)
14912 and then Has_Aspects
(Templ
)
14914 Save_Global_References_In_Aspects
(Templ
);
14917 if Present
(Items
) then
14918 Save_Global_References_In_List
(Pre_Post_Conditions
(Items
));
14919 Save_Global_References_In_List
(Contract_Test_Cases
(Items
));
14920 Save_Global_References_In_List
(Classifications
(Items
));
14924 end Save_Global_References_In_Contract
;
14926 --------------------------------------
14927 -- Set_Copied_Sloc_For_Inlined_Body --
14928 --------------------------------------
14930 procedure Set_Copied_Sloc_For_Inlined_Body
(N
: Node_Id
; E
: Entity_Id
) is
14932 Create_Instantiation_Source
(N
, E
, True, S_Adjustment
);
14933 end Set_Copied_Sloc_For_Inlined_Body
;
14935 ---------------------
14936 -- Set_Instance_Of --
14937 ---------------------
14939 procedure Set_Instance_Of
(A
: Entity_Id
; B
: Entity_Id
) is
14941 Generic_Renamings
.Table
(Generic_Renamings
.Last
) := (A
, B
, Assoc_Null
);
14942 Generic_Renamings_HTable
.Set
(Generic_Renamings
.Last
);
14943 Generic_Renamings
.Increment_Last
;
14944 end Set_Instance_Of
;
14946 --------------------
14947 -- Set_Next_Assoc --
14948 --------------------
14950 procedure Set_Next_Assoc
(E
: Assoc_Ptr
; Next
: Assoc_Ptr
) is
14952 Generic_Renamings
.Table
(E
).Next_In_HTable
:= Next
;
14953 end Set_Next_Assoc
;
14955 -------------------
14956 -- Start_Generic --
14957 -------------------
14959 procedure Start_Generic
is
14961 -- ??? More things could be factored out in this routine.
14962 -- Should probably be done at a later stage.
14964 Generic_Flags
.Append
(Inside_A_Generic
);
14965 Inside_A_Generic
:= True;
14967 Expander_Mode_Save_And_Set
(False);
14970 ----------------------
14971 -- Set_Instance_Env --
14972 ----------------------
14974 procedure Set_Instance_Env
14975 (Gen_Unit
: Entity_Id
;
14976 Act_Unit
: Entity_Id
)
14978 Assertion_Status
: constant Boolean := Assertions_Enabled
;
14979 Save_SPARK_Mode
: constant SPARK_Mode_Type
:= SPARK_Mode
;
14980 Save_SPARK_Mode_Pragma
: constant Node_Id
:= SPARK_Mode_Pragma
;
14983 -- Regardless of the current mode, predefined units are analyzed in the
14984 -- most current Ada mode, and earlier version Ada checks do not apply
14985 -- to predefined units. Nothing needs to be done for non-internal units.
14986 -- These are always analyzed in the current mode.
14988 if Is_Internal_File_Name
14989 (Fname
=> Unit_File_Name
(Get_Source_Unit
(Gen_Unit
)),
14990 Renamings_Included
=> True)
14992 Set_Opt_Config_Switches
(True, Current_Sem_Unit
= Main_Unit
);
14994 -- In Ada2012 we may want to enable assertions in an instance of a
14995 -- predefined unit, in which case we need to preserve the current
14996 -- setting for the Assertions_Enabled flag. This will become more
14997 -- critical when pre/postconditions are added to predefined units,
14998 -- as is already the case for some numeric libraries.
15000 if Ada_Version
>= Ada_2012
then
15001 Assertions_Enabled
:= Assertion_Status
;
15004 -- SPARK_Mode for an instance is the one applicable at the point of
15007 SPARK_Mode
:= Save_SPARK_Mode
;
15008 SPARK_Mode_Pragma
:= Save_SPARK_Mode_Pragma
;
15010 -- Make sure dynamic elaboration checks are off in SPARK Mode
15012 if SPARK_Mode
= On
then
15013 Dynamic_Elaboration_Checks
:= False;
15017 Current_Instantiated_Parent
:=
15018 (Gen_Id
=> Gen_Unit
,
15019 Act_Id
=> Act_Unit
,
15020 Next_In_HTable
=> Assoc_Null
);
15021 end Set_Instance_Env
;
15027 procedure Switch_View
(T
: Entity_Id
) is
15028 BT
: constant Entity_Id
:= Base_Type
(T
);
15029 Priv_Elmt
: Elmt_Id
:= No_Elmt
;
15030 Priv_Sub
: Entity_Id
;
15033 -- T may be private but its base type may have been exchanged through
15034 -- some other occurrence, in which case there is nothing to switch
15035 -- besides T itself. Note that a private dependent subtype of a private
15036 -- type might not have been switched even if the base type has been,
15037 -- because of the last branch of Check_Private_View (see comment there).
15039 if not Is_Private_Type
(BT
) then
15040 Prepend_Elmt
(Full_View
(T
), Exchanged_Views
);
15041 Exchange_Declarations
(T
);
15045 Priv_Elmt
:= First_Elmt
(Private_Dependents
(BT
));
15047 if Present
(Full_View
(BT
)) then
15048 Prepend_Elmt
(Full_View
(BT
), Exchanged_Views
);
15049 Exchange_Declarations
(BT
);
15052 while Present
(Priv_Elmt
) loop
15053 Priv_Sub
:= (Node
(Priv_Elmt
));
15055 -- We avoid flipping the subtype if the Etype of its full view is
15056 -- private because this would result in a malformed subtype. This
15057 -- occurs when the Etype of the subtype full view is the full view of
15058 -- the base type (and since the base types were just switched, the
15059 -- subtype is pointing to the wrong view). This is currently the case
15060 -- for tagged record types, access types (maybe more?) and needs to
15061 -- be resolved. ???
15063 if Present
(Full_View
(Priv_Sub
))
15064 and then not Is_Private_Type
(Etype
(Full_View
(Priv_Sub
)))
15066 Prepend_Elmt
(Full_View
(Priv_Sub
), Exchanged_Views
);
15067 Exchange_Declarations
(Priv_Sub
);
15070 Next_Elmt
(Priv_Elmt
);
15078 function True_Parent
(N
: Node_Id
) return Node_Id
is
15080 if Nkind
(Parent
(N
)) = N_Subunit
then
15081 return Parent
(Corresponding_Stub
(Parent
(N
)));
15087 -----------------------------
15088 -- Valid_Default_Attribute --
15089 -----------------------------
15091 procedure Valid_Default_Attribute
(Nam
: Entity_Id
; Def
: Node_Id
) is
15092 Attr_Id
: constant Attribute_Id
:=
15093 Get_Attribute_Id
(Attribute_Name
(Def
));
15094 T
: constant Entity_Id
:= Entity
(Prefix
(Def
));
15095 Is_Fun
: constant Boolean := (Ekind
(Nam
) = E_Function
);
15101 if No
(T
) or else T
= Any_Id
then
15106 F
:= First_Formal
(Nam
);
15107 while Present
(F
) loop
15108 Num_F
:= Num_F
+ 1;
15113 when Attribute_Adjacent | Attribute_Ceiling | Attribute_Copy_Sign |
15114 Attribute_Floor | Attribute_Fraction | Attribute_Machine |
15115 Attribute_Model | Attribute_Remainder | Attribute_Rounding |
15116 Attribute_Unbiased_Rounding
=>
15119 and then Is_Floating_Point_Type
(T
);
15121 when Attribute_Image | Attribute_Pred | Attribute_Succ |
15122 Attribute_Value | Attribute_Wide_Image |
15123 Attribute_Wide_Value
=>
15124 OK
:= (Is_Fun
and then Num_F
= 1 and then Is_Scalar_Type
(T
));
15126 when Attribute_Max | Attribute_Min
=>
15127 OK
:= (Is_Fun
and then Num_F
= 2 and then Is_Scalar_Type
(T
));
15129 when Attribute_Input
=>
15130 OK
:= (Is_Fun
and then Num_F
= 1);
15132 when Attribute_Output | Attribute_Read | Attribute_Write
=>
15133 OK
:= (not Is_Fun
and then Num_F
= 2);
15141 ("attribute reference has wrong profile for subprogram", Def
);
15143 end Valid_Default_Attribute
;