1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2023, 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 Contracts
; use Contracts
;
29 with Einfo
; use Einfo
;
30 with Einfo
.Entities
; use Einfo
.Entities
;
31 with Einfo
.Utils
; use Einfo
.Utils
;
32 with Elists
; use Elists
;
33 with Errout
; use Errout
;
34 with Expander
; use Expander
;
35 with Fname
; use Fname
;
36 with Fname
.UF
; use Fname
.UF
;
37 with Freeze
; use Freeze
;
38 with Ghost
; use Ghost
;
39 with Itypes
; use Itypes
;
41 with Lib
.Load
; use Lib
.Load
;
42 with Lib
.Xref
; use Lib
.Xref
;
43 with Nlists
; use Nlists
;
44 with Namet
; use Namet
;
45 with Nmake
; use Nmake
;
47 with Rident
; use Rident
;
48 with Restrict
; use Restrict
;
49 with Rtsfind
; use Rtsfind
;
51 with Sem_Aux
; use Sem_Aux
;
52 with Sem_Cat
; use Sem_Cat
;
53 with Sem_Ch3
; use Sem_Ch3
;
54 with Sem_Ch6
; use Sem_Ch6
;
55 with Sem_Ch7
; use Sem_Ch7
;
56 with Sem_Ch8
; use Sem_Ch8
;
57 with Sem_Ch10
; use Sem_Ch10
;
58 with Sem_Ch13
; use Sem_Ch13
;
59 with Sem_Dim
; use Sem_Dim
;
60 with Sem_Disp
; use Sem_Disp
;
61 with Sem_Elab
; use Sem_Elab
;
62 with Sem_Elim
; use Sem_Elim
;
63 with Sem_Eval
; use Sem_Eval
;
64 with Sem_Prag
; use Sem_Prag
;
65 with Sem_Res
; use Sem_Res
;
66 with Sem_Type
; use Sem_Type
;
67 with Sem_Util
; use Sem_Util
;
68 with Sem_Warn
; use Sem_Warn
;
69 with Stand
; use Stand
;
70 with Sinfo
; use Sinfo
;
71 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
72 with Sinfo
.Utils
; use Sinfo
.Utils
;
73 with Sinfo
.CN
; use Sinfo
.CN
;
74 with Sinput
; use Sinput
;
75 with Sinput
.L
; use Sinput
.L
;
76 with Snames
; use Snames
;
77 with Stringt
; use Stringt
;
78 with Uname
; use Uname
;
80 with Tbuild
; use Tbuild
;
81 with Uintp
; use Uintp
;
82 with Urealp
; use Urealp
;
83 with Warnsw
; use Warnsw
;
87 package body Sem_Ch12
is
89 ----------------------------------------------------------
90 -- Implementation of Generic Analysis and Instantiation --
91 ----------------------------------------------------------
93 -- GNAT implements generics by macro expansion. No attempt is made to share
94 -- generic instantiations (for now). Analysis of a generic definition does
95 -- not perform any expansion action, but the expander must be called on the
96 -- tree for each instantiation, because the expansion may of course depend
97 -- on the generic actuals. All of this is best achieved as follows:
99 -- a) Semantic analysis of a generic unit is performed on a copy of the
100 -- tree for the generic unit. All tree modifications that follow analysis
101 -- do not affect the original tree. Links are kept between the original
102 -- tree and the copy, in order to recognize non-local references within
103 -- the generic, and propagate them to each instance (recall that name
104 -- resolution is done on the generic declaration: generics are not really
105 -- macros). This is summarized in the following diagram:
107 -- .-----------. .----------.
108 -- | semantic |<--------------| generic |
110 -- | |==============>| |
111 -- |___________| global |__________|
122 -- b) Each instantiation copies the original tree, and inserts into it a
123 -- series of declarations that describe the mapping between generic formals
124 -- and actuals. For example, a generic In OUT parameter is an object
125 -- renaming of the corresponding actual, etc. Generic IN parameters are
126 -- constant declarations.
128 -- c) In order to give the right visibility for these renamings, we use
129 -- a different scheme for package and subprogram instantiations. For
130 -- packages, the list of renamings is inserted into the package
131 -- specification, before the visible declarations of the package. The
132 -- renamings are analyzed before any of the text of the instance, and are
133 -- thus visible at the right place. Furthermore, outside of the instance,
134 -- the generic parameters are visible and denote their corresponding
137 -- For subprograms, we create a container package to hold the renamings
138 -- and the subprogram instance itself. Analysis of the package makes the
139 -- renaming declarations visible to the subprogram. After analyzing the
140 -- package, the defining entity for the subprogram is touched-up so that
141 -- it appears declared in the current scope, and not inside the container
144 -- If the instantiation is a compilation unit, the container package is
145 -- given the same name as the subprogram instance. This ensures that
146 -- the elaboration procedure called by the binder, using the compilation
147 -- unit name, calls in fact the elaboration procedure for the package.
149 -- Not surprisingly, private types complicate this approach. By saving in
150 -- the original generic object the non-local references, we guarantee that
151 -- the proper entities are referenced at the point of instantiation.
152 -- However, for private types, this by itself does not insure that the
153 -- proper VIEW of the entity is used (the full type may be visible at the
154 -- point of generic definition, but not at instantiation, or vice-versa).
155 -- In order to reference the proper view, we special-case any reference
156 -- to private types in the generic object, by saving both views, one in
157 -- the generic and one in the semantic copy. At time of instantiation, we
158 -- check whether the two views are consistent, and exchange declarations if
159 -- necessary, in order to restore the correct visibility. Similarly, if
160 -- the instance view is private when the generic view was not, we perform
161 -- the exchange. After completing the instantiation, we restore the
162 -- current visibility. The flag Has_Private_View marks identifiers in the
163 -- the generic unit that require checking.
165 -- Visibility within nested generic units requires special handling.
166 -- Consider the following scheme:
168 -- type Global is ... -- outside of generic unit.
172 -- type Semi_Global is ... -- global to inner.
175 -- procedure inner (X1 : Global; X2 : Semi_Global);
177 -- procedure in2 is new inner (...); -- 4
180 -- package New_Outer is new Outer (...); -- 2
181 -- procedure New_Inner is new New_Outer.Inner (...); -- 3
183 -- The semantic analysis of Outer captures all occurrences of Global.
184 -- The semantic analysis of Inner (at 1) captures both occurrences of
185 -- Global and Semi_Global.
187 -- At point 2 (instantiation of Outer), we also produce a generic copy
188 -- of Inner, even though Inner is, at that point, not being instantiated.
189 -- (This is just part of the semantic analysis of New_Outer).
191 -- Critically, references to Global within Inner must be preserved, while
192 -- references to Semi_Global should not preserved, because they must now
193 -- resolve to an entity within New_Outer. To distinguish between these, we
194 -- use a global variable, Current_Instantiated_Parent, which is set when
195 -- performing a generic copy during instantiation (at 2). This variable is
196 -- used when performing a generic copy that is not an instantiation, but
197 -- that is nested within one, as the occurrence of 1 within 2. The analysis
198 -- of a nested generic only preserves references that are global to the
199 -- enclosing Current_Instantiated_Parent. We use the Scope_Depth value to
200 -- determine whether a reference is external to the given parent.
202 -- The instantiation at point 3 requires no special treatment. The method
203 -- works as well for further nestings of generic units, but of course the
204 -- variable Current_Instantiated_Parent must be stacked because nested
205 -- instantiations can occur, e.g. the occurrence of 4 within 2.
207 -- The instantiation of package and subprogram bodies is handled in a
208 -- similar manner, except that it is delayed until after semantic
209 -- analysis is complete. In this fashion complex cross-dependencies
210 -- between several package declarations and bodies containing generics
211 -- can be compiled which otherwise would diagnose spurious circularities.
213 -- For example, it is possible to compile two packages A and B that
214 -- have the following structure:
216 -- package A is package B is
217 -- generic ... generic ...
218 -- package G_A is package G_B is
221 -- package body A is package body B is
222 -- package N_B is new G_B (..) package N_A is new G_A (..)
224 -- The table Pending_Instantiations in package Inline is used to keep
225 -- track of body instantiations that are delayed in this manner. Inline
226 -- handles the actual calls to do the body instantiations. This activity
227 -- is part of Inline, since the processing occurs at the same point, and
228 -- for essentially the same reason, as the handling of inlined routines.
230 ----------------------------------------------
231 -- Detection of Instantiation Circularities --
232 ----------------------------------------------
234 -- If we have a chain of instantiations that is circular, this is static
235 -- error which must be detected at compile time. The detection of these
236 -- circularities is carried out at the point that we insert a generic
237 -- instance spec or body. If there is a circularity, then the analysis of
238 -- the offending spec or body will eventually result in trying to load the
239 -- same unit again, and we detect this problem as we analyze the package
240 -- instantiation for the second time.
242 -- At least in some cases after we have detected the circularity, we get
243 -- into trouble if we try to keep going. The following flag is set if a
244 -- circularity is detected, and used to abandon compilation after the
245 -- messages have been posted.
247 Circularity_Detected
: Boolean := False;
248 -- It should really be reset upon encountering a new main unit, but in
249 -- practice we do not use multiple main units so this is not critical.
251 -----------------------------------------
252 -- Implementation of Generic Contracts --
253 -----------------------------------------
255 -- A "contract" is a collection of aspects and pragmas that either verify a
256 -- property of a construct at runtime or classify the data flow to and from
257 -- the construct in some fashion.
259 -- Generic packages, subprograms and their respective bodies may be subject
260 -- to the following contract-related aspects or pragmas collectively known
263 -- package subprogram [body]
264 -- Abstract_State Always_Terminates
265 -- Initial_Condition Contract_Cases
266 -- Initializes Depends
268 -- Extensions_Visible
271 -- Refined_State Post_Class
279 -- Subprogram_Variant
282 -- Most package contract annotations utilize forward references to classify
283 -- data declared within the package [body]. Subprogram annotations then use
284 -- the classifications to further refine them. These inter dependencies are
285 -- problematic with respect to the implementation of generics because their
286 -- analysis, capture of global references and instantiation does not mesh
287 -- well with the existing mechanism.
289 -- 1) Analysis of generic contracts is carried out the same way non-generic
290 -- contracts are analyzed:
292 -- 1.1) General rule - a contract is analyzed after all related aspects
293 -- and pragmas are analyzed. This is done by routines
295 -- Analyze_Package_Body_Contract
296 -- Analyze_Package_Contract
297 -- Analyze_Subprogram_Body_Contract
298 -- Analyze_Subprogram_Contract
300 -- 1.2) Compilation unit - the contract is analyzed after Pragmas_After
303 -- 1.3) Compilation unit body - the contract is analyzed at the end of
304 -- the body declaration list.
306 -- 1.4) Package - the contract is analyzed at the end of the private or
307 -- visible declarations, prior to analyzing the contracts of any nested
308 -- packages or subprograms.
310 -- 1.5) Package body - the contract is analyzed at the end of the body
311 -- declaration list, prior to analyzing the contracts of any nested
312 -- packages or subprograms.
314 -- 1.6) Subprogram - if the subprogram is declared inside a block, a
315 -- package or a subprogram, then its contract is analyzed at the end of
316 -- the enclosing declarations, otherwise the subprogram is a compilation
319 -- 1.7) Subprogram body - if the subprogram body is declared inside a
320 -- block, a package body or a subprogram body, then its contract is
321 -- analyzed at the end of the enclosing declarations, otherwise the
322 -- subprogram is a compilation unit 1.3).
324 -- 2) Capture of global references within contracts is done after capturing
325 -- global references within the generic template. There are two reasons for
326 -- this delay - pragma annotations are not part of the generic template in
327 -- the case of a generic subprogram declaration, and analysis of contracts
330 -- Contract-related source pragmas within generic templates are prepared
331 -- for delayed capture of global references by routine
333 -- Create_Generic_Contract
335 -- The routine associates these pragmas with the contract of the template.
336 -- In the case of a generic subprogram declaration, the routine creates
337 -- generic templates for the pragmas declared after the subprogram because
338 -- they are not part of the template.
340 -- generic -- template starts
341 -- procedure Gen_Proc (Input : Integer); -- template ends
342 -- pragma Precondition (Input > 0); -- requires own template
344 -- 2.1) The capture of global references with aspect specifications and
345 -- source pragmas that apply to a generic unit must be suppressed when
346 -- the generic template is being processed because the contracts have not
347 -- been analyzed yet. Any attempts to capture global references at that
348 -- point will destroy the Associated_Node linkages and leave the template
349 -- undecorated. This delay is controlled by routine
351 -- Requires_Delayed_Save
353 -- 2.2) The real capture of global references within a contract is done
354 -- after the contract has been analyzed, by routine
356 -- Save_Global_References_In_Contract
358 -- 3) The instantiation of a generic contract occurs as part of the
359 -- instantiation of the contract owner. Generic subprogram declarations
360 -- require additional processing when the contract is specified by pragmas
361 -- because the pragmas are not part of the generic template. This is done
364 -- Instantiate_Subprogram_Contract
366 --------------------------------------------------
367 -- Formal packages and partial parameterization --
368 --------------------------------------------------
370 -- When compiling a generic, a formal package is a local instantiation. If
371 -- declared with a box, its generic formals are visible in the enclosing
372 -- generic. If declared with a partial list of actuals, those actuals that
373 -- are defaulted (covered by an Others clause, or given an explicit box
374 -- initialization) are also visible in the enclosing generic, while those
375 -- that have a corresponding actual are not.
377 -- In our source model of instantiation, the same visibility must be
378 -- present in the spec and body of an instance: the names of the formals
379 -- that are defaulted must be made visible within the instance, and made
380 -- invisible (hidden) after the instantiation is complete, so that they
381 -- are not accessible outside of the instance.
383 -- In a generic, a formal package is treated like a special instantiation.
384 -- Our Ada 95 compiler handled formals with and without box in different
385 -- ways. With partial parameterization, we use a single model for both.
386 -- We create a package declaration that consists of the specification of
387 -- the generic package, and a set of declarations that map the actuals
388 -- into local renamings, just as we do for bona fide instantiations. For
389 -- defaulted parameters and formals with a box, we copy directly the
390 -- declarations of the formals into this local package. The result is a
391 -- package whose visible declarations may include generic formals. This
392 -- package is only used for type checking and visibility analysis, and
393 -- never reaches the back end, so it can freely violate the placement
394 -- rules for generic formal declarations.
396 -- The list of declarations (renamings and copies of formals) is built
397 -- by Analyze_Associations, just as for regular instantiations.
399 -- At the point of instantiation, conformance checking must be applied only
400 -- to those parameters that were specified in the formals. We perform this
401 -- checking by creating another internal instantiation, this one including
402 -- only the renamings and the formals (the rest of the package spec is not
403 -- relevant to conformance checking). We can then traverse two lists: the
404 -- list of actuals in the instance that corresponds to the formal package,
405 -- and the list of actuals produced for this bogus instantiation. We apply
406 -- the conformance rules to those actuals that are not defaulted, i.e.
407 -- which still appear as generic formals.
409 -- When we compile an instance body we must make the right parameters
410 -- visible again. The predicate Is_Generic_Formal indicates which of the
411 -- formals should have its Is_Hidden flag reset.
413 -----------------------
414 -- Local subprograms --
415 -----------------------
417 procedure Abandon_Instantiation
(N
: Node_Id
);
418 pragma No_Return
(Abandon_Instantiation
);
419 -- Posts an error message "instantiation abandoned" at the indicated node
420 -- and then raises the exception Instantiation_Error to do it.
422 procedure Analyze_Formal_Array_Type
423 (T
: in out Entity_Id
;
425 -- A formal array type is treated like an array type declaration, and
426 -- invokes Array_Type_Declaration (sem_ch3) whose first parameter is
427 -- in-out, because in the case of an anonymous type the entity is
428 -- actually created in the procedure.
430 -- The following procedures treat other kinds of formal parameters
432 procedure Analyze_Formal_Derived_Interface_Type
437 procedure Analyze_Formal_Derived_Type
442 procedure Analyze_Formal_Interface_Type
447 -- The following subprograms create abbreviated declarations for formal
448 -- scalar types. We introduce an anonymous base of the proper class for
449 -- each of them, and define the formals as constrained first subtypes of
450 -- their bases. The bounds are expressions that are non-static in the
453 procedure Analyze_Formal_Decimal_Fixed_Point_Type
454 (T
: Entity_Id
; Def
: Node_Id
);
455 procedure Analyze_Formal_Discrete_Type
(T
: Entity_Id
; Def
: Node_Id
);
456 procedure Analyze_Formal_Floating_Type
(T
: Entity_Id
; Def
: Node_Id
);
457 procedure Analyze_Formal_Signed_Integer_Type
(T
: Entity_Id
; Def
: Node_Id
);
458 procedure Analyze_Formal_Modular_Type
(T
: Entity_Id
; Def
: Node_Id
);
459 procedure Analyze_Formal_Ordinary_Fixed_Point_Type
460 (T
: Entity_Id
; Def
: Node_Id
);
462 procedure Analyze_Formal_Private_Type
466 -- Creates a new private type, which does not require completion
468 procedure Analyze_Formal_Incomplete_Type
(T
: Entity_Id
; Def
: Node_Id
);
469 -- Ada 2012: Creates a new incomplete type whose actual does not freeze
471 procedure Analyze_Generic_Formal_Part
(N
: Node_Id
);
472 -- Analyze generic formal part
474 procedure Analyze_Generic_Access_Type
(T
: Entity_Id
; Def
: Node_Id
);
475 -- Create a new access type with the given designated type
477 function Analyze_Associations
480 F_Copy
: List_Id
) return List_Id
;
481 -- At instantiation time, build the list of associations between formals
482 -- and actuals. Each association becomes a renaming declaration for the
483 -- formal entity. F_Copy is the analyzed list of formals in the generic
484 -- copy. It is used to apply legality checks to the actuals. I_Node is the
485 -- instantiation node itself.
487 procedure Analyze_Subprogram_Instantiation
491 procedure Build_Instance_Compilation_Unit_Nodes
495 -- This procedure is used in the case where the generic instance of a
496 -- subprogram body or package body is a library unit. In this case, the
497 -- original library unit node for the generic instantiation must be
498 -- replaced by the resulting generic body, and a link made to a new
499 -- compilation unit node for the generic declaration. The argument N is
500 -- the original generic instantiation. Act_Body and Act_Decl are the body
501 -- and declaration of the instance (either package body and declaration
502 -- nodes or subprogram body and declaration nodes depending on the case).
503 -- On return, the node N has been rewritten with the actual body.
505 function Build_Subprogram_Decl_Wrapper
506 (Formal_Subp
: Entity_Id
) return Node_Id
;
507 -- Ada 2022 allows formal subprograms to carry pre/postconditions.
508 -- At the point of instantiation these contracts apply to uses of
509 -- the actual subprogram. This is implemented by creating wrapper
510 -- subprograms instead of the renamings previously used to link
511 -- formal subprograms and the corresponding actuals. If the actual
512 -- is not an entity (e.g. an attribute reference) a renaming is
513 -- created to handle the expansion of the attribute.
515 function Build_Subprogram_Body_Wrapper
516 (Formal_Subp
: Entity_Id
;
517 Actual_Name
: Node_Id
) return Node_Id
;
518 -- The body of the wrapper is a call to the actual, with the generated
519 -- pre/postconditon checks added.
521 procedure Check_Abbreviated_Instance
523 Parent_Installed
: in out Boolean);
524 -- If the name of the generic unit in an abbreviated instantiation is an
525 -- expanded name, then the prefix may be an instance and the selector may
526 -- designate a child unit. If the parent is installed as a result of this
527 -- call, then Parent_Installed is set True, otherwise Parent_Installed is
528 -- unchanged by the call.
530 -- This routine needs to be called for declaration nodes of formal objects,
531 -- types and subprograms to check whether they are the copy, present in the
532 -- visible part of the abbreviated instantiation of formal packages, of the
533 -- declaration node of their corresponding formal parameter in the template
534 -- of the formal package, as specified by RM 12.7(10/2), so as to establish
535 -- the proper context for their analysis.
537 procedure Check_Access_Definition
(N
: Node_Id
);
538 -- Subsidiary routine to null exclusion processing. Perform an assertion
539 -- check on Ada version and the presence of an access definition in N.
541 procedure Check_Formal_Packages
(P_Id
: Entity_Id
);
542 -- Apply the following to all formal packages in generic associations.
543 -- Restore the visibility of the formals of the instance that are not
544 -- defaulted (see RM 12.7 (10)). Remove the anonymous package declaration
545 -- created for formal instances that are not defaulted.
547 procedure Check_Formal_Package_Instance
548 (Formal_Pack
: Entity_Id
;
549 Actual_Pack
: Entity_Id
);
550 -- Verify that the actuals of the actual instance match the actuals of
551 -- the template for a formal package that is not declared with a box.
553 procedure Check_Forward_Instantiation
(Decl
: Node_Id
);
554 -- If the generic is a local entity and the corresponding body has not
555 -- been seen yet, flag enclosing packages to indicate that it will be
556 -- elaborated after the generic body. Subprograms declared in the same
557 -- package cannot be inlined by the front end because front-end inlining
558 -- requires a strict linear order of elaboration.
560 function Check_Hidden_Primitives
(Assoc_List
: List_Id
) return Elist_Id
;
561 -- Check if some association between formals and actuals requires to make
562 -- visible primitives of a tagged type, and make those primitives visible.
563 -- Return the list of primitives whose visibility is modified (to restore
564 -- their visibility later through Restore_Hidden_Primitives). If no
565 -- candidate is found then return No_Elist.
567 procedure Check_Hidden_Child_Unit
569 Gen_Unit
: Entity_Id
;
570 Act_Decl_Id
: Entity_Id
);
571 -- If the generic unit is an implicit child instance within a parent
572 -- instance, we need to make an explicit test that it is not hidden by
573 -- a child instance of the same name and parent.
575 procedure Check_Generic_Actuals
576 (Instance
: Entity_Id
;
577 Is_Formal_Box
: Boolean);
578 -- Similar to previous one. Check the actuals in the instantiation,
579 -- whose views can change between the point of instantiation and the point
580 -- of instantiation of the body. In addition, mark the generic renamings
581 -- as generic actuals, so that they are not compatible with other actuals.
582 -- Recurse on an actual that is a formal package whose declaration has
585 function Component_Type_For_Private_View
(T
: Entity_Id
) return Entity_Id
;
586 -- Return the component type of array type T, with the following addition:
587 -- if this component type itself is an array type which has not been first
588 -- declared as private, then recurse on it. This makes it possible to deal
589 -- with arrays of arrays the same way as multi-dimensional arrays in the
590 -- mechanism handling private views.
592 function Contains_Instance_Of
595 N
: Node_Id
) return Boolean;
596 -- Inner is instantiated within the generic Outer. Check whether Inner
597 -- directly or indirectly contains an instance of Outer or of one of its
598 -- parents, in the case of a subunit. Each generic unit holds a list of
599 -- the entities instantiated within (at any depth). This procedure
600 -- determines whether the set of such lists contains a cycle, i.e. an
601 -- illegal circular instantiation.
603 function Denotes_Formal_Package
605 On_Exit
: Boolean := False;
606 Instance
: Entity_Id
:= Empty
) return Boolean;
607 -- Returns True if E is a formal package of an enclosing generic, or
608 -- the actual for such a formal in an enclosing instantiation. If such
609 -- a package is used as a formal in an nested generic, or as an actual
610 -- in a nested instantiation, the visibility of ITS formals should not
611 -- be modified. When called from within Restore_Private_Views, the flag
612 -- On_Exit is true, to indicate that the search for a possible enclosing
613 -- instance should ignore the current one. In that case Instance denotes
614 -- the declaration for which this is an actual. This declaration may be
615 -- an instantiation in the source, or the internal instantiation that
616 -- corresponds to the actual for a formal package.
618 function Earlier
(N1
, N2
: Node_Id
) return Boolean;
619 -- Yields True if N1 and N2 appear in the same compilation unit,
620 -- ignoring subunits, and if N1 is to the left of N2 in a left-to-right
621 -- traversal of the tree for the unit. Used to determine the placement
622 -- of freeze nodes for instance bodies that may depend on other instances.
624 function Find_Actual_Type
626 Gen_Type
: Entity_Id
) return Entity_Id
;
627 -- When validating the actual types of a child instance, check whether
628 -- the formal is a formal type of the parent unit, and retrieve the current
629 -- actual for it. Typ is the entity in the analyzed formal type declaration
630 -- (component or index type of an array type, or designated type of an
631 -- access formal) and Gen_Type is the enclosing analyzed formal array
632 -- or access type. The desired actual may be a formal of a parent, or may
633 -- be declared in a formal package of a parent. In both cases it is a
634 -- generic actual type because it appears within a visible instance.
635 -- Finally, it may be declared in a parent unit without being a formal
636 -- of that unit, in which case it must be retrieved by visibility.
637 -- Ambiguities may still arise if two homonyms are declared in two formal
638 -- packages, and the prefix of the formal type may be needed to resolve
639 -- the ambiguity in the instance ???
641 procedure Freeze_Package_Instance
646 -- If the instantiation happens textually before the body of the generic,
647 -- the instantiation of the body must be analyzed after the generic body,
648 -- and not at the point of instantiation. Such early instantiations can
649 -- happen if the generic and the instance appear in a package declaration
650 -- because the generic body can only appear in the corresponding package
651 -- body. Early instantiations can also appear if generic, instance and
652 -- body are all in the declarative part of a subprogram or entry. Entities
653 -- of packages that are early instantiations are delayed, and their freeze
654 -- node appears after the generic body. This rather complex machinery is
655 -- needed when nested instantiations are present, because the source does
656 -- not carry any indication of where the corresponding instance bodies must
657 -- be installed and frozen.
659 procedure Freeze_Subprogram_Instance
662 Pack_Id
: Entity_Id
);
663 -- The generic body may appear textually after the instance, including
664 -- in the proper body of a stub, or within a different package instance.
665 -- Given that the instance can only be elaborated after the generic, we
666 -- place freeze nodes for the instance and/or for packages that may enclose
667 -- the instance and the generic, so that the back-end can establish the
668 -- proper order of elaboration.
670 function Get_Associated_Entity
(Id
: Entity_Id
) return Entity_Id
;
671 -- Similar to Get_Associated_Node below, but for entities
673 function Get_Associated_Node
(N
: Node_Id
) return Node_Id
;
674 -- In order to propagate semantic information back from the analyzed copy
675 -- to the original generic, we maintain links between selected nodes in the
676 -- generic and their corresponding copies. At the end of generic analysis,
677 -- the routine Save_Global_References traverses the generic tree, examines
678 -- the semantic information, and preserves the links to those nodes that
679 -- contain global information. At instantiation, the information from the
680 -- associated node is placed on the new copy, so that name resolution is
683 -- Three kinds of source nodes have associated nodes:
685 -- a) those that can reference (denote) entities, that is identifiers,
686 -- character literals, expanded_names, operator symbols, operators,
687 -- and attribute reference nodes. These nodes have an Entity field
688 -- and are the set of nodes that are in N_Has_Entity.
690 -- b) aggregates (N_Aggregate and N_Extension_Aggregate)
692 -- c) selected components (N_Selected_Component)
694 -- For the first class, the associated node preserves the entity if it is
695 -- global. If the generic contains nested instantiations, the associated
696 -- node itself has been recopied, and a chain of them must be followed.
698 -- For aggregates, the associated node allows retrieval of the type, which
699 -- may otherwise not appear in the generic. The view of this type may be
700 -- different between generic and instantiation, and the full view can be
701 -- installed before the instantiation is analyzed. For aggregates of type
702 -- extensions, the same view exchange may have to be performed for some of
703 -- the ancestor types, if their view is private at the point of
706 -- Nodes that are selected components in the parse tree may be rewritten
707 -- as expanded names after resolution, and must be treated as potential
708 -- entity holders, which is why they also have an Associated_Node.
710 -- Nodes that do not come from source, such as freeze nodes, do not appear
711 -- in the generic tree, and need not have an associated node.
713 -- The associated node is stored in the Associated_Node field. Note that
714 -- this field overlaps Entity, which is fine, because the whole point is
715 -- that we don't need or want the normal Entity field in this situation.
717 function Has_Been_Exchanged
(E
: Entity_Id
) return Boolean;
718 -- Traverse the Exchanged_Views list to see if a type was private
719 -- and has already been flipped during this phase of instantiation.
721 function Has_Contracts
(Decl
: Node_Id
) return Boolean;
722 -- Determine whether a formal subprogram has a Pre- or Postcondition,
723 -- in which case a subprogram wrapper has to be built for the actual.
725 procedure Hide_Current_Scope
;
726 -- When instantiating a generic child unit, the parent context must be
727 -- present, but the instance and all entities that may be generated
728 -- must be inserted in the current scope. We leave the current scope
729 -- on the stack, but make its entities invisible to avoid visibility
730 -- problems. This is reversed at the end of the instantiation. This is
731 -- not done for the instantiation of the bodies, which only require the
732 -- instances of the generic parents to be in scope.
734 function In_Main_Context
(E
: Entity_Id
) return Boolean;
735 -- Check whether an instantiation is in the context of the main unit.
736 -- Used to determine whether its body should be elaborated to allow
737 -- front-end inlining.
739 procedure Inherit_Context
(Gen_Decl
: Node_Id
; Inst
: Node_Id
);
740 -- Add the context clause of the unit containing a generic unit to a
741 -- compilation unit that is, or contains, an instantiation.
744 -- Establish environment for subsequent instantiation. Separated from
745 -- Save_Env because data-structures for visibility handling must be
746 -- initialized before call to Check_Generic_Child_Unit.
748 procedure Inline_Instance_Body
750 Gen_Unit
: Entity_Id
;
752 -- If front-end inlining is requested, instantiate the package body,
753 -- and preserve the visibility of its compilation unit, to insure
754 -- that successive instantiations succeed.
756 procedure Insert_Freeze_Node_For_Instance
759 -- N denotes a package or a subprogram instantiation and F_Node is the
760 -- associated freeze node. Insert the freeze node before the first source
761 -- body which follows immediately after N. If no such body is found, the
762 -- freeze node is inserted at the end of the declarative region which
763 -- contains N, unless the instantiation is done in a package spec that is
764 -- not at library level, in which case it is inserted at the outer level.
765 -- This can also be invoked to insert the freeze node of a package that
766 -- encloses an instantiation, in which case N may denote an arbitrary node.
768 procedure Install_Formal_Packages
(Par
: Entity_Id
);
769 -- Install the visible part of any formal of the parent that is a formal
770 -- package. Note that for the case of a formal package with a box, this
771 -- includes the formal part of the formal package (12.7(10/2)).
773 procedure Install_Hidden_Primitives
774 (Prims_List
: in out Elist_Id
;
777 -- Remove suffix 'P' from hidden primitives of Act_T to match the
778 -- visibility of primitives of Gen_T. The list of primitives to which
779 -- the suffix is removed is added to Prims_List to restore them later.
781 procedure Install_Parent
(P
: Entity_Id
; In_Body
: Boolean := False);
782 -- When compiling an instance of a child unit the parent (which is
783 -- itself an instance) is an enclosing scope that must be made
784 -- immediately visible. This procedure is also used to install the non-
785 -- generic parent of a generic child unit when compiling its body, so
786 -- that full views of types in the parent are made visible.
788 -- The functions Instantiate_XXX perform various legality checks and build
789 -- the declarations for instantiated generic parameters. In all of these
790 -- Formal is the entity in the generic unit, Actual is the entity of
791 -- expression in the generic associations, and Analyzed_Formal is the
792 -- formal in the generic copy, which contains the semantic information to
793 -- be used to validate the actual.
795 function Instantiate_Object
798 Analyzed_Formal
: Node_Id
) return List_Id
;
800 function Instantiate_Type
803 Analyzed_Formal
: Node_Id
;
804 Actual_Decls
: List_Id
) return List_Id
;
806 function Instantiate_Formal_Subprogram
809 Analyzed_Formal
: Node_Id
) return Node_Id
;
811 function Instantiate_Formal_Package
814 Analyzed_Formal
: Node_Id
) return List_Id
;
815 -- If the formal package is declared with a box, special visibility rules
816 -- apply to its formals: they are in the visible part of the package. This
817 -- is true in the declarative region of the formal package, that is to say
818 -- in the enclosing generic or instantiation. For an instantiation, the
819 -- parameters of the formal package are made visible in an explicit step.
820 -- Furthermore, if the actual has a visible USE clause, these formals must
821 -- be made potentially use-visible as well. On exit from the enclosing
822 -- instantiation, the reverse must be done.
824 -- For a formal package declared without a box, there are conformance rules
825 -- that apply to the actuals in the generic declaration and the actuals of
826 -- the actual package in the enclosing instantiation. The simplest way to
827 -- apply these rules is to repeat the instantiation of the formal package
828 -- in the context of the enclosing instance, and compare the generic
829 -- associations of this instantiation with those of the actual package.
830 -- This internal instantiation only needs to contain the renamings of the
831 -- formals: the visible and private declarations themselves need not be
834 -- In Ada 2005, the formal package may be only partially parameterized.
835 -- In that case the visibility step must make visible those actuals whose
836 -- corresponding formals were given with a box. A final complication
837 -- involves inherited operations from formal derived types, which must
838 -- be visible if the type is.
840 function Is_In_Main_Unit
(N
: Node_Id
) return Boolean;
841 -- Test if given node is in the main unit
843 procedure Load_Parent_Of_Generic
846 Body_Optional
: Boolean := False);
847 -- If the generic appears in a separate non-generic library unit, load the
848 -- corresponding body to retrieve the body of the generic. N is the node
849 -- for the generic instantiation, Spec is the generic package declaration.
851 -- Body_Optional is a flag that indicates that the body is being loaded to
852 -- ensure that temporaries are generated consistently when there are other
853 -- instances in the current declarative part that precede the one being
854 -- loaded. In that case a missing body is acceptable.
856 procedure Map_Formal_Package_Entities
(Form
: Entity_Id
; Act
: Entity_Id
);
857 -- Within the generic part, entities in the formal package are
858 -- visible. To validate subsequent type declarations, indicate
859 -- the correspondence between the entities in the analyzed formal,
860 -- and the entities in the actual package. There are three packages
861 -- involved in the instantiation of a formal package: the parent
862 -- generic P1 which appears in the generic declaration, the fake
863 -- instantiation P2 which appears in the analyzed generic, and whose
864 -- visible entities may be used in subsequent formals, and the actual
865 -- P3 in the instance. To validate subsequent formals, me indicate
866 -- that the entities in P2 are mapped into those of P3. The mapping of
867 -- entities has to be done recursively for nested packages.
869 procedure Move_Freeze_Nodes
873 -- Freeze nodes can be generated in the analysis of a generic unit, but
874 -- will not be seen by the back-end. It is necessary to move those nodes
875 -- to the enclosing scope if they freeze an outer entity. We place them
876 -- at the end of the enclosing generic package, which is semantically
879 procedure Preanalyze_Actuals
(N
: Node_Id
; Inst
: Entity_Id
:= Empty
);
880 -- Analyze actuals to perform name resolution. Full resolution is done
881 -- later, when the expected types are known, but names have to be captured
882 -- before installing parents of generics, that are not visible for the
883 -- actuals themselves.
885 -- If Inst is present, it is the entity of the package instance. This
886 -- entity is marked as having a limited_view actual when some actual is
887 -- a limited view. This is used to place the instance body properly.
889 procedure Provide_Completing_Bodies
(N
: Node_Id
);
890 -- Generate completing bodies for all subprograms found within package or
891 -- subprogram declaration N.
893 procedure Remove_Parent
(In_Body
: Boolean := False);
894 -- Reverse effect after instantiation of child is complete
896 function Requires_Conformance_Checking
(N
: Node_Id
) return Boolean;
897 -- Determine whether the formal package declaration N requires conformance
898 -- checking with actuals in instantiations.
900 procedure Restore_Hidden_Primitives
(Prims_List
: in out Elist_Id
);
901 -- Restore suffix 'P' to primitives of Prims_List and leave Prims_List
904 procedure Set_Instance_Env
905 (Gen_Unit
: Entity_Id
;
906 Act_Unit
: Entity_Id
);
907 -- Save current instance on saved environment, to be used to determine
908 -- the global status of entities in nested instances. Part of Save_Env.
909 -- called after verifying that the generic unit is legal for the instance,
910 -- The procedure also examines whether the generic unit is a predefined
911 -- unit, in order to set configuration switches accordingly. As a result
912 -- the procedure must be called after analyzing and freezing the actuals.
914 procedure Set_Instance_Of
(A
: Entity_Id
; B
: Entity_Id
);
915 -- Associate analyzed generic parameter with corresponding instance. Used
916 -- for semantic checks at instantiation time.
918 function True_Parent
(N
: Node_Id
) return Node_Id
;
919 -- For a subunit, return parent of corresponding stub, else return
922 procedure Valid_Default_Attribute
(Nam
: Entity_Id
; Def
: Node_Id
);
923 -- Verify that an attribute that appears as the default for a formal
924 -- subprogram is a function or procedure with the correct profile.
926 procedure Validate_Formal_Type_Default
(Decl
: Node_Id
);
927 -- Ada_2022 AI12-205: if a default subtype_mark is present, verify
928 -- that it is the name of a type in the same class as the formal.
929 -- The treatment parallels what is done in Instantiate_Type but differs
930 -- in a few ways so that this machinery cannot be reused as is: on one
931 -- hand there are no visibility issues for a default, because it is
932 -- analyzed in the same context as the formal type definition; on the
933 -- other hand the check needs to take into acount the use of a previous
934 -- formal type in the current formal type definition (see details in
937 -------------------------------------------
938 -- Data Structures for Generic Renamings --
939 -------------------------------------------
941 -- The map Generic_Renamings associates generic entities with their
942 -- corresponding actuals. Currently used to validate type instances. It
943 -- will eventually be used for all generic parameters to eliminate the
944 -- need for overload resolution in the instance.
946 type Assoc_Ptr
is new Int
;
948 Assoc_Null
: constant Assoc_Ptr
:= -1;
953 Next_In_HTable
: Assoc_Ptr
;
956 package Generic_Renamings
is new Table
.Table
957 (Table_Component_Type
=> Assoc
,
958 Table_Index_Type
=> Assoc_Ptr
,
959 Table_Low_Bound
=> 0,
961 Table_Increment
=> 100,
962 Table_Name
=> "Generic_Renamings");
964 -- Variable to hold enclosing instantiation. When the environment is
965 -- saved for a subprogram inlining, the corresponding Act_Id is empty.
967 Current_Instantiated_Parent
: Assoc
:= (Empty
, Empty
, Assoc_Null
);
969 -- Hash table for associations
971 HTable_Size
: constant := 37;
972 type HTable_Range
is range 0 .. HTable_Size
- 1;
974 procedure Set_Next_Assoc
(E
: Assoc_Ptr
; Next
: Assoc_Ptr
);
975 function Next_Assoc
(E
: Assoc_Ptr
) return Assoc_Ptr
;
976 function Get_Gen_Id
(E
: Assoc_Ptr
) return Entity_Id
;
977 function Hash
(F
: Entity_Id
) return HTable_Range
;
979 package Generic_Renamings_HTable
is new GNAT
.HTable
.Static_HTable
(
980 Header_Num
=> HTable_Range
,
982 Elmt_Ptr
=> Assoc_Ptr
,
983 Null_Ptr
=> Assoc_Null
,
984 Set_Next
=> Set_Next_Assoc
,
987 Get_Key
=> Get_Gen_Id
,
991 Exchanged_Views
: Elist_Id
;
992 -- This list holds the private views that have been exchanged during
993 -- instantiation to restore the visibility of the generic declaration.
994 -- (see comments above). After instantiation, the current visibility is
995 -- reestablished by means of a traversal of this list.
997 Hidden_Entities
: Elist_Id
;
998 -- This list holds the entities of the current scope that are removed
999 -- from immediate visibility when instantiating a child unit. Their
1000 -- visibility is restored in Remove_Parent.
1002 -- Because instantiations can be recursive, the following must be saved
1003 -- on entry and restored on exit from an instantiation (spec or body).
1004 -- This is done by the two procedures Save_Env and Restore_Env. For
1005 -- package and subprogram instantiations (but not for the body instances)
1006 -- the action of Save_Env is done in two steps: Init_Env is called before
1007 -- Check_Generic_Child_Unit, because setting the parent instances requires
1008 -- that the visibility data structures be properly initialized. Once the
1009 -- generic is unit is validated, Set_Instance_Env completes Save_Env.
1011 Parent_Unit_Visible
: Boolean := False;
1012 -- Parent_Unit_Visible is used when the generic is a child unit, and
1013 -- indicates whether the ultimate parent of the generic is visible in the
1014 -- instantiation environment. It is used to reset the visibility of the
1015 -- parent at the end of the instantiation (see Remove_Parent).
1017 Instance_Parent_Unit
: Entity_Id
:= Empty
;
1018 -- This records the ultimate parent unit of an instance of a generic
1019 -- child unit and is used in conjunction with Parent_Unit_Visible to
1020 -- indicate the unit to which the Parent_Unit_Visible flag corresponds.
1022 type Instance_Env
is record
1023 Instantiated_Parent
: Assoc
;
1024 Exchanged_Views
: Elist_Id
;
1025 Hidden_Entities
: Elist_Id
;
1026 Current_Sem_Unit
: Unit_Number_Type
;
1027 Parent_Unit_Visible
: Boolean := False;
1028 Instance_Parent_Unit
: Entity_Id
:= Empty
;
1029 Switches
: Config_Switches_Type
;
1032 package Instance_Envs
is new Table
.Table
(
1033 Table_Component_Type
=> Instance_Env
,
1034 Table_Index_Type
=> Int
,
1035 Table_Low_Bound
=> 0,
1036 Table_Initial
=> 32,
1037 Table_Increment
=> 100,
1038 Table_Name
=> "Instance_Envs");
1040 procedure Restore_Private_Views
1041 (Pack_Id
: Entity_Id
;
1042 Is_Package
: Boolean := True);
1043 -- Restore the private views of external types, and unmark the generic
1044 -- renamings of actuals, so that they become compatible subtypes again.
1045 -- For subprograms, Pack_Id is the package constructed to hold the
1048 procedure Switch_View
(T
: Entity_Id
);
1049 -- Switch the partial and full views of a type and its private
1050 -- dependents (i.e. its subtypes and derived types).
1052 ------------------------------------
1053 -- Structures for Error Reporting --
1054 ------------------------------------
1056 Instantiation_Node
: Node_Id
;
1057 -- Used by subprograms that validate instantiation of formal parameters
1058 -- where there might be no actual on which to place the error message.
1059 -- Also used to locate the instantiation node for generic subunits.
1061 Instantiation_Error
: exception;
1062 -- When there is a semantic error in the generic parameter matching,
1063 -- there is no point in continuing the instantiation, because the
1064 -- number of cascaded errors is unpredictable. This exception aborts
1065 -- the instantiation process altogether.
1067 S_Adjustment
: Sloc_Adjustment
;
1068 -- Offset created for each node in an instantiation, in order to keep
1069 -- track of the source position of the instantiation in each of its nodes.
1070 -- A subsequent semantic error or warning on a construct of the instance
1071 -- points to both places: the original generic node, and the point of
1072 -- instantiation. See Sinput and Sinput.L for additional details.
1074 ------------------------------------------------------------
1075 -- Data structure for keeping track when inside a Generic --
1076 ------------------------------------------------------------
1078 -- The following table is used to save values of the Inside_A_Generic
1079 -- flag (see spec of Sem) when they are saved by Start_Generic.
1081 package Generic_Flags
is new Table
.Table
(
1082 Table_Component_Type
=> Boolean,
1083 Table_Index_Type
=> Int
,
1084 Table_Low_Bound
=> 0,
1085 Table_Initial
=> 32,
1086 Table_Increment
=> 200,
1087 Table_Name
=> "Generic_Flags");
1089 ---------------------------
1090 -- Abandon_Instantiation --
1091 ---------------------------
1093 procedure Abandon_Instantiation
(N
: Node_Id
) is
1095 Error_Msg_N
("\instantiation abandoned!", N
);
1096 raise Instantiation_Error
;
1097 end Abandon_Instantiation
;
1099 ----------------------------------
1100 -- Adjust_Inherited_Pragma_Sloc --
1101 ----------------------------------
1103 procedure Adjust_Inherited_Pragma_Sloc
(N
: Node_Id
) is
1105 Adjust_Instantiation_Sloc
(N
, S_Adjustment
);
1106 end Adjust_Inherited_Pragma_Sloc
;
1108 --------------------------
1109 -- Analyze_Associations --
1110 --------------------------
1112 function Analyze_Associations
1115 F_Copy
: List_Id
) return List_Id
1117 Actuals_To_Freeze
: constant Elist_Id
:= New_Elmt_List
;
1118 Assoc_List
: constant List_Id
:= New_List
;
1119 Default_Actuals
: constant List_Id
:= New_List
;
1120 Gen_Unit
: constant Entity_Id
:=
1121 Defining_Entity
(Parent
(F_Copy
));
1125 Analyzed_Formal
: Node_Id
;
1126 First_Named
: Node_Id
:= Empty
;
1128 Match
: Node_Id
:= Empty
;
1130 Saved_Formal
: Node_Id
;
1132 Default_Formals
: constant List_Id
:= New_List
;
1133 -- If an Others_Choice is present, some of the formals may be defaulted.
1134 -- To simplify the treatment of visibility in an instance, we introduce
1135 -- individual defaults for each such formal. These defaults are
1136 -- appended to the list of associations and replace the Others_Choice.
1138 Found_Assoc
: Node_Id
;
1139 -- Association for the current formal being match. Empty if there are
1140 -- no remaining actuals, or if there is no named association with the
1141 -- name of the formal.
1143 Is_Named_Assoc
: Boolean;
1144 Num_Matched
: Nat
:= 0;
1145 Num_Actuals
: Nat
:= 0;
1147 Others_Present
: Boolean := False;
1148 Others_Choice
: Node_Id
:= Empty
;
1149 -- In Ada 2005, indicates partial parameterization of a formal
1150 -- package. As usual an other association must be last in the list.
1152 procedure Build_Subprogram_Wrappers
;
1153 -- Ada 2022: AI12-0272 introduces pre/postconditions for formal
1154 -- subprograms. The implementation of making the formal into a renaming
1155 -- of the actual does not work, given that subprogram renaming cannot
1156 -- carry aspect specifications. Instead we must create subprogram
1157 -- wrappers whose body is a call to the actual, and whose declaration
1158 -- carries the aspects of the formal.
1160 procedure Check_Fixed_Point_Actual
(Actual
: Node_Id
);
1161 -- Warn if an actual fixed-point type has user-defined arithmetic
1162 -- operations, but there is no corresponding formal in the generic,
1163 -- in which case the predefined operations will be used. This merits
1164 -- a warning because of the special semantics of fixed point ops.
1166 procedure Check_Overloaded_Formal_Subprogram
(Formal
: Node_Id
);
1167 -- Apply RM 12.3(9): if a formal subprogram is overloaded, the instance
1168 -- cannot have a named association for it. AI05-0025 extends this rule
1169 -- to formals of formal packages by AI05-0025, and it also applies to
1170 -- box-initialized formals.
1172 function Has_Fully_Defined_Profile
(Subp
: Entity_Id
) return Boolean;
1173 -- Determine whether the parameter types and the return type of Subp
1174 -- are fully defined at the point of instantiation.
1176 function Matching_Actual
1178 A_F
: Entity_Id
) return Node_Id
;
1179 -- Find actual that corresponds to a given formal parameter. If the
1180 -- actuals are positional, return the next one, if any. If the actuals
1181 -- are named, scan the parameter associations to find the right one.
1182 -- A_F is the corresponding entity in the analyzed generic, which is
1183 -- placed on the selector name.
1185 -- In Ada 2005, a named association may be given with a box, in which
1186 -- case Matching_Actual sets Found_Assoc to the generic association,
1187 -- but return Empty for the actual itself. In this case the code below
1188 -- creates a corresponding declaration for the formal.
1190 function Partial_Parameterization
return Boolean;
1191 -- Ada 2005: if no match is found for a given formal, check if the
1192 -- association for it includes a box, or whether the associations
1193 -- include an Others clause.
1195 procedure Process_Default
(Formal
: Node_Id
);
1196 -- Add a copy of the declaration of a generic formal to the list of
1197 -- associations, and add an explicit box association for its entity
1198 -- if there is none yet, and the default comes from an Others_Choice.
1200 function Renames_Standard_Subprogram
(Subp
: Entity_Id
) return Boolean;
1201 -- Determine whether Subp renames one of the subprograms defined in the
1202 -- generated package Standard.
1204 procedure Set_Analyzed_Formal
;
1205 -- Find the node in the generic copy that corresponds to a given formal.
1206 -- The semantic information on this node is used to perform legality
1207 -- checks on the actuals. Because semantic analysis can introduce some
1208 -- anonymous entities or modify the declaration node itself, the
1209 -- correspondence between the two lists is not one-one. In addition to
1210 -- anonymous types, the presence a formal equality will introduce an
1211 -- implicit declaration for the corresponding inequality.
1213 -------------------------------
1214 -- Build_Subprogram_Wrappers --
1215 -------------------------------
1217 procedure Build_Subprogram_Wrappers
is
1218 function Adjust_Aspect_Sloc
(N
: Node_Id
) return Traverse_Result
;
1219 -- Adjust sloc so that errors located at N will be reported with
1220 -- information about the instance and not just about the generic.
1222 ------------------------
1223 -- Adjust_Aspect_Sloc --
1224 ------------------------
1226 function Adjust_Aspect_Sloc
(N
: Node_Id
) return Traverse_Result
is
1228 Adjust_Instantiation_Sloc
(N
, S_Adjustment
);
1230 end Adjust_Aspect_Sloc
;
1232 procedure Adjust_Aspect_Slocs
is new
1233 Traverse_Proc
(Adjust_Aspect_Sloc
);
1235 Formal
: constant Entity_Id
:=
1236 Defining_Unit_Name
(Specification
(Analyzed_Formal
));
1237 Aspect_Spec
: Node_Id
;
1238 Decl_Node
: Node_Id
;
1239 Actual_Name
: Node_Id
;
1241 -- Start of processing for Build_Subprogram_Wrappers
1244 -- Create declaration for wrapper subprogram
1245 -- The actual can be overloaded, in which case it will be
1246 -- resolved when the call in the wrapper body is analyzed.
1247 -- We attach the possible interpretations of the actual to
1248 -- the name to be used in the call in the wrapper body.
1250 if Is_Entity_Name
(Match
) then
1251 Actual_Name
:= New_Occurrence_Of
(Entity
(Match
), Sloc
(Match
));
1253 if Is_Overloaded
(Match
) then
1254 Save_Interps
(Match
, Actual_Name
);
1258 -- Use renaming declaration created when analyzing actual.
1259 -- This may be incomplete if there are several formal
1260 -- subprograms whose actual is an attribute ???
1263 Renaming_Decl
: constant Node_Id
:= Last
(Assoc_List
);
1266 Actual_Name
:= New_Occurrence_Of
1267 (Defining_Entity
(Renaming_Decl
), Sloc
(Match
));
1268 Set_Etype
(Actual_Name
, Get_Instance_Of
(Etype
(Formal
)));
1272 Decl_Node
:= Build_Subprogram_Decl_Wrapper
(Formal
);
1274 -- Transfer aspect specifications from formal subprogram to wrapper
1276 Set_Aspect_Specifications
(Decl_Node
,
1277 New_Copy_List_Tree
(Aspect_Specifications
(Analyzed_Formal
)));
1279 Aspect_Spec
:= First
(Aspect_Specifications
(Decl_Node
));
1280 while Present
(Aspect_Spec
) loop
1281 Adjust_Aspect_Slocs
(Aspect_Spec
);
1282 Set_Analyzed
(Aspect_Spec
, False);
1286 Append_To
(Assoc_List
, Decl_Node
);
1288 -- Create corresponding body, and append it to association list
1289 -- that appears at the head of the declarations in the instance.
1290 -- The subprogram may be called in the analysis of subsequent
1293 Append_To
(Assoc_List
,
1294 Build_Subprogram_Body_Wrapper
(Formal
, Actual_Name
));
1295 end Build_Subprogram_Wrappers
;
1297 ----------------------------------------
1298 -- Check_Overloaded_Formal_Subprogram --
1299 ----------------------------------------
1301 procedure Check_Overloaded_Formal_Subprogram
(Formal
: Node_Id
) is
1302 Temp_Formal
: Node_Id
;
1305 Temp_Formal
:= First
(Formals
);
1306 while Present
(Temp_Formal
) loop
1307 if Nkind
(Temp_Formal
) in N_Formal_Subprogram_Declaration
1308 and then Temp_Formal
/= Formal
1310 Chars
(Defining_Unit_Name
(Specification
(Formal
))) =
1311 Chars
(Defining_Unit_Name
(Specification
(Temp_Formal
)))
1313 if Present
(Found_Assoc
) then
1315 ("named association not allowed for overloaded formal",
1320 ("named association not allowed for overloaded formal",
1324 Abandon_Instantiation
(Instantiation_Node
);
1329 end Check_Overloaded_Formal_Subprogram
;
1331 -------------------------------
1332 -- Check_Fixed_Point_Actual --
1333 -------------------------------
1335 procedure Check_Fixed_Point_Actual
(Actual
: Node_Id
) is
1336 Typ
: constant Entity_Id
:= Entity
(Actual
);
1337 Prims
: constant Elist_Id
:= Collect_Primitive_Operations
(Typ
);
1343 -- Locate primitive operations of the type that are arithmetic
1346 Elem
:= First_Elmt
(Prims
);
1347 while Present
(Elem
) loop
1348 if Nkind
(Node
(Elem
)) = N_Defining_Operator_Symbol
then
1350 -- Check whether the generic unit has a formal subprogram of
1351 -- the same name. This does not check types but is good enough
1352 -- to justify a warning.
1354 Formal
:= First_Non_Pragma
(Formals
);
1355 Op
:= Alias
(Node
(Elem
));
1357 while Present
(Formal
) loop
1358 if Nkind
(Formal
) = N_Formal_Concrete_Subprogram_Declaration
1359 and then Chars
(Defining_Entity
(Formal
)) =
1364 elsif Nkind
(Formal
) = N_Formal_Package_Declaration
then
1370 -- Locate corresponding actual, and check whether it
1371 -- includes a fixed-point type.
1373 Assoc
:= First
(Assoc_List
);
1374 while Present
(Assoc
) loop
1376 Nkind
(Assoc
) = N_Package_Renaming_Declaration
1377 and then Chars
(Defining_Unit_Name
(Assoc
)) =
1378 Chars
(Defining_Identifier
(Formal
));
1383 if Present
(Assoc
) then
1385 -- If formal package declares a fixed-point type,
1386 -- and the user-defined operator is derived from
1387 -- a generic instance package, the fixed-point type
1388 -- does not use the corresponding predefined op.
1390 Ent
:= First_Entity
(Entity
(Name
(Assoc
)));
1391 while Present
(Ent
) loop
1392 if Is_Fixed_Point_Type
(Ent
)
1393 and then Present
(Op
)
1394 and then Is_Generic_Instance
(Scope
(Op
))
1409 Error_Msg_Sloc
:= Sloc
(Node
(Elem
));
1411 ("?instance uses predefined operation, not primitive "
1412 & "operation&#", Actual
, Node
(Elem
));
1418 end Check_Fixed_Point_Actual
;
1420 -------------------------------
1421 -- Has_Fully_Defined_Profile --
1422 -------------------------------
1424 function Has_Fully_Defined_Profile
(Subp
: Entity_Id
) return Boolean is
1425 function Is_Fully_Defined_Type
(Typ
: Entity_Id
) return Boolean;
1426 -- Determine whethet type Typ is fully defined
1428 ---------------------------
1429 -- Is_Fully_Defined_Type --
1430 ---------------------------
1432 function Is_Fully_Defined_Type
(Typ
: Entity_Id
) return Boolean is
1434 -- A private type without a full view is not fully defined
1436 if Is_Private_Type
(Typ
)
1437 and then No
(Full_View
(Typ
))
1441 -- An incomplete type is never fully defined
1443 elsif Is_Incomplete_Type
(Typ
) then
1446 -- All other types are fully defined
1451 end Is_Fully_Defined_Type
;
1453 -- Local declarations
1457 -- Start of processing for Has_Fully_Defined_Profile
1460 -- Check the parameters
1462 Param
:= First_Formal
(Subp
);
1463 while Present
(Param
) loop
1464 if not Is_Fully_Defined_Type
(Etype
(Param
)) then
1468 Next_Formal
(Param
);
1471 -- Check the return type
1473 return Is_Fully_Defined_Type
(Etype
(Subp
));
1474 end Has_Fully_Defined_Profile
;
1476 ---------------------
1477 -- Matching_Actual --
1478 ---------------------
1480 function Matching_Actual
1482 A_F
: Entity_Id
) return Node_Id
1488 Is_Named_Assoc
:= False;
1490 -- End of list of purely positional parameters
1492 if No
(Actual
) or else Nkind
(Actual
) = N_Others_Choice
then
1493 Found_Assoc
:= Empty
;
1496 -- Case of positional parameter corresponding to current formal
1498 elsif No
(Selector_Name
(Actual
)) then
1499 Found_Assoc
:= Actual
;
1500 Act
:= Explicit_Generic_Actual_Parameter
(Actual
);
1501 Num_Matched
:= Num_Matched
+ 1;
1504 -- Otherwise scan list of named actuals to find the one with the
1505 -- desired name. All remaining actuals have explicit names.
1508 Is_Named_Assoc
:= True;
1509 Found_Assoc
:= Empty
;
1513 while Present
(Actual
) loop
1514 if Nkind
(Actual
) = N_Others_Choice
then
1515 Found_Assoc
:= Empty
;
1518 elsif Chars
(Selector_Name
(Actual
)) = Chars
(F
) then
1519 Set_Entity
(Selector_Name
(Actual
), A_F
);
1520 Set_Etype
(Selector_Name
(Actual
), Etype
(A_F
));
1521 Generate_Reference
(A_F
, Selector_Name
(Actual
));
1523 Found_Assoc
:= Actual
;
1524 Act
:= Explicit_Generic_Actual_Parameter
(Actual
);
1525 Num_Matched
:= Num_Matched
+ 1;
1533 -- Reset for subsequent searches. In most cases the named
1534 -- associations are in order. If they are not, we reorder them
1535 -- to avoid scanning twice the same actual. This is not just a
1536 -- question of efficiency: there may be multiple defaults with
1537 -- boxes that have the same name. In a nested instantiation we
1538 -- insert actuals for those defaults, and cannot rely on their
1539 -- names to disambiguate them.
1541 if Actual
= First_Named
then
1544 elsif Present
(Actual
) then
1545 Insert_Before
(First_Named
, Remove_Next
(Prev
));
1548 Actual
:= First_Named
;
1551 if Is_Entity_Name
(Act
) and then Present
(Entity
(Act
)) then
1552 Set_Used_As_Generic_Actual
(Entity
(Act
));
1556 end Matching_Actual
;
1558 ------------------------------
1559 -- Partial_Parameterization --
1560 ------------------------------
1562 function Partial_Parameterization
return Boolean is
1564 return Others_Present
1565 or else (Present
(Found_Assoc
) and then Box_Present
(Found_Assoc
));
1566 end Partial_Parameterization
;
1568 ---------------------
1569 -- Process_Default --
1570 ---------------------
1572 procedure Process_Default
(Formal
: Node_Id
) is
1573 Loc
: constant Source_Ptr
:= Sloc
(I_Node
);
1574 F_Id
: constant Entity_Id
:= Defining_Entity
(Formal
);
1580 -- Append copy of formal declaration to associations, and create new
1581 -- defining identifier for it.
1583 Decl
:= New_Copy_Tree
(Formal
);
1584 Id
:= Make_Defining_Identifier
(Sloc
(F_Id
), Chars
(F_Id
));
1586 if Nkind
(Formal
) in N_Formal_Subprogram_Declaration
then
1587 Set_Defining_Unit_Name
(Specification
(Decl
), Id
);
1590 Set_Defining_Identifier
(Decl
, Id
);
1593 Append
(Decl
, Assoc_List
);
1595 if No
(Found_Assoc
) then
1597 Make_Generic_Association
(Loc
,
1599 New_Occurrence_Of
(Id
, Loc
),
1600 Explicit_Generic_Actual_Parameter
=> Empty
);
1601 Set_Box_Present
(Default
);
1602 Append
(Default
, Default_Formals
);
1604 end Process_Default
;
1606 ---------------------------------
1607 -- Renames_Standard_Subprogram --
1608 ---------------------------------
1610 function Renames_Standard_Subprogram
(Subp
: Entity_Id
) return Boolean is
1615 while Present
(Id
) loop
1616 if Scope
(Id
) = Standard_Standard
then
1624 end Renames_Standard_Subprogram
;
1626 -------------------------
1627 -- Set_Analyzed_Formal --
1628 -------------------------
1630 procedure Set_Analyzed_Formal
is
1634 while Present
(Analyzed_Formal
) loop
1635 Kind
:= Nkind
(Analyzed_Formal
);
1637 case Nkind
(Formal
) is
1638 when N_Formal_Subprogram_Declaration
=>
1639 exit when Kind
in N_Formal_Subprogram_Declaration
1642 (Defining_Unit_Name
(Specification
(Formal
))) =
1644 (Defining_Unit_Name
(Specification
(Analyzed_Formal
)));
1646 when N_Formal_Package_Declaration
=>
1647 exit when Kind
in N_Formal_Package_Declaration
1648 | N_Generic_Package_Declaration
1649 | N_Package_Declaration
;
1651 when N_Use_Package_Clause
1658 -- Skip freeze nodes, and nodes inserted to replace
1659 -- unrecognized pragmas.
1662 Kind
not in N_Formal_Subprogram_Declaration
1663 and then Kind
not in N_Subprogram_Declaration
1667 and then Chars
(Defining_Identifier
(Formal
)) =
1668 Chars
(Defining_Identifier
(Analyzed_Formal
));
1671 Next
(Analyzed_Formal
);
1673 end Set_Analyzed_Formal
;
1675 -- Start of processing for Analyze_Associations
1678 Actuals
:= Generic_Associations
(I_Node
);
1680 if Present
(Actuals
) then
1682 -- Check for an Others choice, indicating a partial parameterization
1683 -- for a formal package.
1685 Actual
:= First
(Actuals
);
1686 while Present
(Actual
) loop
1687 if Nkind
(Actual
) = N_Others_Choice
then
1688 Others_Present
:= True;
1689 Others_Choice
:= Actual
;
1691 if Present
(Next
(Actual
)) then
1692 Error_Msg_N
("OTHERS must be last association", Actual
);
1695 -- This subprogram is used both for formal packages and for
1696 -- instantiations. For the latter, associations must all be
1699 if Nkind
(I_Node
) /= N_Formal_Package_Declaration
1700 and then Comes_From_Source
(I_Node
)
1703 ("OTHERS association not allowed in an instance",
1707 -- In any case, nothing to do after the others association
1711 elsif Box_Present
(Actual
)
1712 and then Comes_From_Source
(I_Node
)
1713 and then Nkind
(I_Node
) /= N_Formal_Package_Declaration
1716 ("box association not allowed in an instance", Actual
);
1722 -- If named associations are present, save first named association
1723 -- (it may of course be Empty) to facilitate subsequent name search.
1725 First_Named
:= First
(Actuals
);
1726 while Present
(First_Named
)
1727 and then Nkind
(First_Named
) /= N_Others_Choice
1728 and then No
(Selector_Name
(First_Named
))
1730 Num_Actuals
:= Num_Actuals
+ 1;
1735 Named
:= First_Named
;
1736 while Present
(Named
) loop
1737 if Nkind
(Named
) /= N_Others_Choice
1738 and then No
(Selector_Name
(Named
))
1740 Error_Msg_N
("invalid positional actual after named one", Named
);
1741 Abandon_Instantiation
(Named
);
1744 -- A named association may lack an actual parameter, if it was
1745 -- introduced for a default subprogram that turns out to be local
1746 -- to the outer instantiation. If it has a box association it must
1747 -- correspond to some formal in the generic.
1749 if Nkind
(Named
) /= N_Others_Choice
1750 and then (Present
(Explicit_Generic_Actual_Parameter
(Named
))
1751 or else Box_Present
(Named
))
1753 Num_Actuals
:= Num_Actuals
+ 1;
1759 if Present
(Formals
) then
1760 Formal
:= First_Non_Pragma
(Formals
);
1761 Analyzed_Formal
:= First_Non_Pragma
(F_Copy
);
1763 if Present
(Actuals
) then
1764 Actual
:= First
(Actuals
);
1766 -- All formals should have default values
1772 while Present
(Formal
) loop
1773 Set_Analyzed_Formal
;
1774 Saved_Formal
:= Next_Non_Pragma
(Formal
);
1776 case Nkind
(Formal
) is
1777 when N_Formal_Object_Declaration
=>
1780 (Defining_Identifier
(Formal
),
1781 Defining_Identifier
(Analyzed_Formal
));
1783 if No
(Match
) and then Partial_Parameterization
then
1784 Process_Default
(Formal
);
1788 (Instantiate_Object
(Formal
, Match
, Analyzed_Formal
),
1791 -- For a defaulted in_parameter, create an entry in the
1792 -- the list of defaulted actuals, for GNATprove use. Do
1793 -- not included these defaults for an instance nested
1794 -- within a generic, because the defaults are also used
1795 -- in the analysis of the enclosing generic, and only
1796 -- defaulted subprograms are relevant there.
1798 if No
(Match
) and then not Inside_A_Generic
then
1799 Append_To
(Default_Actuals
,
1800 Make_Generic_Association
(Sloc
(I_Node
),
1803 (Defining_Identifier
(Formal
), Sloc
(I_Node
)),
1804 Explicit_Generic_Actual_Parameter
=>
1805 New_Copy_Tree
(Default_Expression
(Formal
))));
1809 -- If the object is a call to an expression function, this
1810 -- is a freezing point for it.
1812 if Is_Entity_Name
(Match
)
1813 and then Present
(Entity
(Match
))
1815 (Original_Node
(Unit_Declaration_Node
(Entity
(Match
))))
1816 = N_Expression_Function
1818 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
1821 when N_Formal_Type_Declaration
=>
1824 (Defining_Identifier
(Formal
),
1825 Defining_Identifier
(Analyzed_Formal
));
1828 if Partial_Parameterization
then
1829 Process_Default
(Formal
);
1831 elsif Present
(Default_Subtype_Mark
(Formal
)) then
1832 Match
:= New_Copy
(Default_Subtype_Mark
(Formal
));
1835 (Formal
, Match
, Analyzed_Formal
, Assoc_List
),
1837 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
1840 Error_Msg_Sloc
:= Sloc
(Gen_Unit
);
1843 Instantiation_Node
, Defining_Identifier
(Formal
));
1845 ("\in instantiation of & declared#",
1846 Instantiation_Node
, Gen_Unit
);
1847 Abandon_Instantiation
(Instantiation_Node
);
1854 (Formal
, Match
, Analyzed_Formal
, Assoc_List
),
1857 -- Warn when an actual is a fixed-point with user-
1858 -- defined promitives. The warning is superfluous
1859 -- if the formal is private, because there can be
1860 -- no arithmetic operations in the generic so there
1861 -- no danger of confusion.
1863 if Is_Fixed_Point_Type
(Entity
(Match
))
1864 and then not Is_Private_Type
1865 (Defining_Identifier
(Analyzed_Formal
))
1867 Check_Fixed_Point_Actual
(Match
);
1870 -- An instantiation is a freeze point for the actuals,
1871 -- unless this is a rewritten formal package, or the
1872 -- formal is an Ada 2012 formal incomplete type.
1874 if Nkind
(I_Node
) = N_Formal_Package_Declaration
1876 (Ada_Version
>= Ada_2012
1878 Ekind
(Defining_Identifier
(Analyzed_Formal
)) =
1884 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
1888 -- A remote access-to-class-wide type is not a legal actual
1889 -- for a generic formal of an access type (E.2.2(17/2)).
1890 -- In GNAT an exception to this rule is introduced when
1891 -- the formal is marked as remote using implementation
1892 -- defined aspect/pragma Remote_Access_Type. In that case
1893 -- the actual must be remote as well.
1895 -- If the current instantiation is the construction of a
1896 -- local copy for a formal package the actuals may be
1897 -- defaulted, and there is no matching actual to check.
1899 if Nkind
(Analyzed_Formal
) = N_Formal_Type_Declaration
1901 Nkind
(Formal_Type_Definition
(Analyzed_Formal
)) =
1902 N_Access_To_Object_Definition
1903 and then Present
(Match
)
1906 Formal_Ent
: constant Entity_Id
:=
1907 Defining_Identifier
(Analyzed_Formal
);
1909 if Is_Remote_Access_To_Class_Wide_Type
(Entity
(Match
))
1910 = Is_Remote_Types
(Formal_Ent
)
1912 -- Remoteness of formal and actual match
1916 elsif Is_Remote_Types
(Formal_Ent
) then
1918 -- Remote formal, non-remote actual
1921 ("actual for& must be remote", Match
, Formal_Ent
);
1924 -- Non-remote formal, remote actual
1927 ("actual for& may not be remote",
1933 when N_Formal_Subprogram_Declaration
=>
1936 (Defining_Unit_Name
(Specification
(Formal
)),
1937 Defining_Unit_Name
(Specification
(Analyzed_Formal
)));
1939 -- If the formal subprogram has the same name as another
1940 -- formal subprogram of the generic, then a named
1941 -- association is illegal (12.3(9)). Exclude named
1942 -- associations that are generated for a nested instance.
1945 and then Is_Named_Assoc
1946 and then Comes_From_Source
(Found_Assoc
)
1948 Check_Overloaded_Formal_Subprogram
(Formal
);
1951 -- If there is no corresponding actual, this may be case
1952 -- of partial parameterization, or else the formal has a
1953 -- default or a box.
1955 if No
(Match
) and then Partial_Parameterization
then
1956 Process_Default
(Formal
);
1958 if Nkind
(I_Node
) = N_Formal_Package_Declaration
then
1959 Check_Overloaded_Formal_Subprogram
(Formal
);
1963 Append_To
(Assoc_List
,
1964 Instantiate_Formal_Subprogram
1965 (Formal
, Match
, Analyzed_Formal
));
1967 -- If formal subprogram has contracts, create wrappers
1968 -- for it. This is an expansion activity that cannot
1969 -- take place e.g. within an enclosing generic unit.
1971 if Has_Contracts
(Analyzed_Formal
)
1972 and then (Expander_Active
or GNATprove_Mode
)
1974 Build_Subprogram_Wrappers
;
1977 -- An instantiation is a freeze point for the actuals,
1978 -- unless this is a rewritten formal package.
1980 if Nkind
(I_Node
) /= N_Formal_Package_Declaration
1981 and then Nkind
(Match
) = N_Identifier
1982 and then Is_Subprogram
(Entity
(Match
))
1984 -- The actual subprogram may rename a routine defined
1985 -- in Standard. Avoid freezing such renamings because
1986 -- subprograms coming from Standard cannot be frozen.
1989 not Renames_Standard_Subprogram
(Entity
(Match
))
1991 -- If the actual subprogram comes from a different
1992 -- unit, it is already frozen, either by a body in
1993 -- that unit or by the end of the declarative part
1994 -- of the unit. This check avoids the freezing of
1995 -- subprograms defined in Standard which are used
1996 -- as generic actuals.
1998 and then In_Same_Code_Unit
(Entity
(Match
), I_Node
)
1999 and then Has_Fully_Defined_Profile
(Entity
(Match
))
2001 -- Mark the subprogram as having a delayed freeze
2002 -- since this may be an out-of-order action.
2004 Set_Has_Delayed_Freeze
(Entity
(Match
));
2005 Append_Elmt
(Entity
(Match
), Actuals_To_Freeze
);
2009 -- If this is a nested generic, preserve default for later
2010 -- instantiations. We do this as well for GNATprove use,
2011 -- so that the list of generic associations is complete.
2013 if No
(Match
) and then Box_Present
(Formal
) then
2015 Subp
: constant Entity_Id
:=
2017 (Specification
(Last
(Assoc_List
)));
2020 Append_To
(Default_Actuals
,
2021 Make_Generic_Association
(Sloc
(I_Node
),
2023 New_Occurrence_Of
(Subp
, Sloc
(I_Node
)),
2024 Explicit_Generic_Actual_Parameter
=>
2025 New_Occurrence_Of
(Subp
, Sloc
(I_Node
))));
2029 when N_Formal_Package_Declaration
=>
2030 -- The name of the formal package may be hidden by the
2031 -- formal parameter itself.
2033 if Error_Posted
(Analyzed_Formal
) then
2034 Abandon_Instantiation
(Instantiation_Node
);
2039 (Defining_Identifier
(Formal
),
2041 (Original_Node
(Analyzed_Formal
)));
2045 if Partial_Parameterization
then
2046 Process_Default
(Formal
);
2049 Error_Msg_Sloc
:= Sloc
(Gen_Unit
);
2052 Instantiation_Node
, Defining_Identifier
(Formal
));
2054 ("\in instantiation of & declared#",
2055 Instantiation_Node
, Gen_Unit
);
2057 Abandon_Instantiation
(Instantiation_Node
);
2063 (Instantiate_Formal_Package
2064 (Formal
, Match
, Analyzed_Formal
),
2067 -- Determine whether the actual package needs an explicit
2068 -- freeze node. This is only the case if the actual is
2069 -- declared in the same unit and has a body. Normally
2070 -- packages do not have explicit freeze nodes, and gigi
2071 -- only uses them to elaborate entities in a package
2074 Explicit_Freeze_Check
: declare
2075 Actual
: constant Entity_Id
:= Entity
(Match
);
2076 Gen_Par
: Entity_Id
;
2078 Needs_Freezing
: Boolean;
2081 procedure Check_Generic_Parent
;
2082 -- The actual may be an instantiation of a unit
2083 -- declared in a previous instantiation. If that
2084 -- one is also in the current compilation, it must
2085 -- itself be frozen before the actual. The actual
2086 -- may be an instantiation of a generic child unit,
2087 -- in which case the same applies to the instance
2088 -- of the parent which must be frozen before the
2090 -- Should this itself be recursive ???
2092 --------------------------
2093 -- Check_Generic_Parent --
2094 --------------------------
2096 procedure Check_Generic_Parent
is
2097 Inst
: constant Node_Id
:=
2098 Get_Unit_Instantiation_Node
(Actual
);
2104 if Nkind
(Parent
(Actual
)) = N_Package_Specification
2106 Par
:= Scope
(Generic_Parent
(Parent
(Actual
)));
2108 if Is_Generic_Instance
(Par
) then
2111 -- If the actual is a child generic unit, check
2112 -- whether the instantiation of the parent is
2113 -- also local and must also be frozen now. We
2114 -- must retrieve the instance node to locate the
2115 -- parent instance if any.
2117 elsif Ekind
(Par
) = E_Generic_Package
2118 and then Is_Child_Unit
(Gen_Par
)
2119 and then Ekind
(Scope
(Gen_Par
)) =
2122 if Nkind
(Inst
) = N_Package_Instantiation
2123 and then Nkind
(Name
(Inst
)) =
2126 -- Retrieve entity of parent instance
2128 Par
:= Entity
(Prefix
(Name
(Inst
)));
2137 and then Is_Generic_Instance
(Par
)
2138 and then Scope
(Par
) = Current_Scope
2140 (No
(Freeze_Node
(Par
))
2142 not Is_List_Member
(Freeze_Node
(Par
)))
2144 Set_Has_Delayed_Freeze
(Par
);
2145 Append_Elmt
(Par
, Actuals_To_Freeze
);
2147 end Check_Generic_Parent
;
2149 -- Start of processing for Explicit_Freeze_Check
2152 if Present
(Renamed_Entity
(Actual
)) then
2154 Generic_Parent
(Specification
2155 (Unit_Declaration_Node
2156 (Renamed_Entity
(Actual
))));
2159 Generic_Parent
(Specification
2160 (Unit_Declaration_Node
(Actual
)));
2163 if not Expander_Active
2164 or else not Has_Completion
(Actual
)
2165 or else not In_Same_Source_Unit
(I_Node
, Actual
)
2166 or else Is_Frozen
(Actual
)
2168 (Present
(Renamed_Entity
(Actual
))
2170 not In_Same_Source_Unit
2171 (I_Node
, (Renamed_Entity
(Actual
))))
2176 -- Finally we want to exclude such freeze nodes
2177 -- from statement sequences, which freeze
2178 -- everything before them.
2179 -- Is this strictly necessary ???
2181 Needs_Freezing
:= True;
2183 P
:= Parent
(I_Node
);
2184 while Nkind
(P
) /= N_Compilation_Unit
loop
2185 if Nkind
(P
) = N_Handled_Sequence_Of_Statements
2187 Needs_Freezing
:= False;
2194 if Needs_Freezing
then
2195 Check_Generic_Parent
;
2197 -- If the actual is a renaming of a proper
2198 -- instance of the formal package, indicate
2199 -- that it is the instance that must be frozen.
2201 if Nkind
(Parent
(Actual
)) =
2202 N_Package_Renaming_Declaration
2204 Set_Has_Delayed_Freeze
2205 (Renamed_Entity
(Actual
));
2207 (Renamed_Entity
(Actual
),
2210 Set_Has_Delayed_Freeze
(Actual
);
2211 Append_Elmt
(Actual
, Actuals_To_Freeze
);
2215 end Explicit_Freeze_Check
;
2218 -- For use type and use package appearing in the generic part,
2219 -- we have already copied them, so we can just move them where
2220 -- they belong (we mustn't recopy them since this would mess up
2221 -- the Sloc values).
2223 when N_Use_Package_Clause
2226 if Nkind
(Original_Node
(I_Node
)) =
2227 N_Formal_Package_Declaration
2229 Append
(New_Copy_Tree
(Formal
), Assoc_List
);
2232 Append
(Formal
, Assoc_List
);
2236 raise Program_Error
;
2239 -- Check here the correct use of Ghost entities in generic
2240 -- instantiations, as now the generic has been resolved and
2241 -- we know which formal generic parameters are ghost (SPARK
2244 if Nkind
(Formal
) not in N_Use_Package_Clause
2247 Check_Ghost_Context_In_Generic_Association
2249 Formal
=> Defining_Entity
(Analyzed_Formal
));
2252 Formal
:= Saved_Formal
;
2253 Next_Non_Pragma
(Analyzed_Formal
);
2256 if Num_Actuals
> Num_Matched
then
2257 Error_Msg_Sloc
:= Sloc
(Gen_Unit
);
2259 if Present
(Selector_Name
(Actual
)) then
2261 ("unmatched actual &", Actual
, Selector_Name
(Actual
));
2263 ("\in instantiation of & declared#", Actual
, Gen_Unit
);
2266 ("unmatched actual in instantiation of & declared#",
2271 elsif Present
(Actuals
) then
2273 ("too many actuals in generic instantiation", Instantiation_Node
);
2276 -- An instantiation freezes all generic actuals. The only exceptions
2277 -- to this are incomplete types and subprograms which are not fully
2278 -- defined at the point of instantiation.
2281 Elmt
: Elmt_Id
:= First_Elmt
(Actuals_To_Freeze
);
2283 while Present
(Elmt
) loop
2284 Freeze_Before
(I_Node
, Node
(Elmt
));
2289 -- If there are default subprograms, normalize the tree by adding
2290 -- explicit associations for them. This is required if the instance
2291 -- appears within a generic.
2293 if not Is_Empty_List
(Default_Actuals
) then
2298 Default
:= First
(Default_Actuals
);
2299 while Present
(Default
) loop
2300 Mark_Rewrite_Insertion
(Default
);
2304 if No
(Actuals
) then
2305 Set_Generic_Associations
(I_Node
, Default_Actuals
);
2307 Append_List_To
(Actuals
, Default_Actuals
);
2312 -- If this is a formal package, normalize the parameter list by adding
2313 -- explicit box associations for the formals that are covered by an
2316 Append_List
(Default_Formals
, Formals
);
2319 end Analyze_Associations
;
2321 -------------------------------
2322 -- Analyze_Formal_Array_Type --
2323 -------------------------------
2325 procedure Analyze_Formal_Array_Type
2326 (T
: in out Entity_Id
;
2332 -- Treated like a non-generic array declaration, with additional
2337 if Nkind
(Def
) = N_Constrained_Array_Definition
then
2338 DSS
:= First
(Discrete_Subtype_Definitions
(Def
));
2339 while Present
(DSS
) loop
2340 if Nkind
(DSS
) in N_Subtype_Indication
2342 | N_Attribute_Reference
2344 Error_Msg_N
("only a subtype mark is allowed in a formal", DSS
);
2351 Array_Type_Declaration
(T
, Def
);
2352 Set_Is_Generic_Type
(Base_Type
(T
));
2354 if Ekind
(Component_Type
(T
)) = E_Incomplete_Type
2355 and then No
(Full_View
(Component_Type
(T
)))
2357 Error_Msg_N
("premature usage of incomplete type", Def
);
2359 -- Check that range constraint is not allowed on the component type
2360 -- of a generic formal array type (AARM 12.5.3(3))
2362 elsif Is_Internal
(Component_Type
(T
))
2363 and then Present
(Subtype_Indication
(Component_Definition
(Def
)))
2364 and then Nkind
(Original_Node
2365 (Subtype_Indication
(Component_Definition
(Def
)))) =
2366 N_Subtype_Indication
2369 ("in a formal, a subtype indication can only be "
2370 & "a subtype mark (RM 12.5.3(3))",
2371 Subtype_Indication
(Component_Definition
(Def
)));
2374 end Analyze_Formal_Array_Type
;
2376 ---------------------------------------------
2377 -- Analyze_Formal_Decimal_Fixed_Point_Type --
2378 ---------------------------------------------
2380 -- As for other generic types, we create a valid type representation with
2381 -- legal but arbitrary attributes, whose values are never considered
2382 -- static. For all scalar types we introduce an anonymous base type, with
2383 -- the same attributes. We choose the corresponding integer type to be
2384 -- Standard_Integer.
2385 -- Here and in other similar routines, the Sloc of the generated internal
2386 -- type must be the same as the sloc of the defining identifier of the
2387 -- formal type declaration, to provide proper source navigation.
2389 procedure Analyze_Formal_Decimal_Fixed_Point_Type
2393 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2395 Base
: constant Entity_Id
:=
2397 (E_Decimal_Fixed_Point_Type
,
2399 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2401 Int_Base
: constant Entity_Id
:= Standard_Integer
;
2402 Delta_Val
: constant Ureal
:= Ureal_1
;
2403 Digs_Val
: constant Uint
:= Uint_6
;
2405 function Make_Dummy_Bound
return Node_Id
;
2406 -- Return a properly typed universal real literal to use as a bound
2408 ----------------------
2409 -- Make_Dummy_Bound --
2410 ----------------------
2412 function Make_Dummy_Bound
return Node_Id
is
2413 Bound
: constant Node_Id
:= Make_Real_Literal
(Loc
, Ureal_1
);
2415 Set_Etype
(Bound
, Universal_Real
);
2417 end Make_Dummy_Bound
;
2419 -- Start of processing for Analyze_Formal_Decimal_Fixed_Point_Type
2424 Set_Etype
(Base
, Base
);
2425 Set_Size_Info
(Base
, Int_Base
);
2426 Set_RM_Size
(Base
, RM_Size
(Int_Base
));
2427 Set_First_Rep_Item
(Base
, First_Rep_Item
(Int_Base
));
2428 Set_Digits_Value
(Base
, Digs_Val
);
2429 Set_Delta_Value
(Base
, Delta_Val
);
2430 Set_Small_Value
(Base
, Delta_Val
);
2431 Set_Scalar_Range
(Base
,
2433 Low_Bound
=> Make_Dummy_Bound
,
2434 High_Bound
=> Make_Dummy_Bound
));
2436 Set_Is_Generic_Type
(Base
);
2437 Set_Parent
(Base
, Parent
(Def
));
2439 Mutate_Ekind
(T
, E_Decimal_Fixed_Point_Subtype
);
2440 Set_Etype
(T
, Base
);
2441 Set_Size_Info
(T
, Int_Base
);
2442 Set_RM_Size
(T
, RM_Size
(Int_Base
));
2443 Set_First_Rep_Item
(T
, First_Rep_Item
(Int_Base
));
2444 Set_Digits_Value
(T
, Digs_Val
);
2445 Set_Delta_Value
(T
, Delta_Val
);
2446 Set_Small_Value
(T
, Delta_Val
);
2447 Set_Scalar_Range
(T
, Scalar_Range
(Base
));
2448 Set_Is_Constrained
(T
);
2450 Check_Restriction
(No_Fixed_Point
, Def
);
2451 end Analyze_Formal_Decimal_Fixed_Point_Type
;
2453 -------------------------------------------
2454 -- Analyze_Formal_Derived_Interface_Type --
2455 -------------------------------------------
2457 procedure Analyze_Formal_Derived_Interface_Type
2462 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2465 -- Rewrite as a type declaration of a derived type. This ensures that
2466 -- the interface list and primitive operations are properly captured.
2469 Make_Full_Type_Declaration
(Loc
,
2470 Defining_Identifier
=> T
,
2471 Type_Definition
=> Def
));
2473 Set_Is_Generic_Type
(T
);
2474 end Analyze_Formal_Derived_Interface_Type
;
2476 ---------------------------------
2477 -- Analyze_Formal_Derived_Type --
2478 ---------------------------------
2480 procedure Analyze_Formal_Derived_Type
2485 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2486 Unk_Disc
: constant Boolean := Unknown_Discriminants_Present
(N
);
2490 Set_Is_Generic_Type
(T
);
2492 if Private_Present
(Def
) then
2494 Make_Private_Extension_Declaration
(Loc
,
2495 Defining_Identifier
=> T
,
2496 Discriminant_Specifications
=> Discriminant_Specifications
(N
),
2497 Unknown_Discriminants_Present
=> Unk_Disc
,
2498 Subtype_Indication
=> Subtype_Mark
(Def
),
2499 Interface_List
=> Interface_List
(Def
));
2501 Set_Abstract_Present
(New_N
, Abstract_Present
(Def
));
2502 Set_Limited_Present
(New_N
, Limited_Present
(Def
));
2503 Set_Synchronized_Present
(New_N
, Synchronized_Present
(Def
));
2507 Make_Full_Type_Declaration
(Loc
,
2508 Defining_Identifier
=> T
,
2509 Discriminant_Specifications
=>
2510 Discriminant_Specifications
(Parent
(T
)),
2512 Make_Derived_Type_Definition
(Loc
,
2513 Subtype_Indication
=> Subtype_Mark
(Def
)));
2515 Set_Abstract_Present
2516 (Type_Definition
(New_N
), Abstract_Present
(Def
));
2518 (Type_Definition
(New_N
), Limited_Present
(Def
));
2525 if not Is_Composite_Type
(T
) then
2527 ("unknown discriminants not allowed for elementary types", N
);
2529 Set_Has_Unknown_Discriminants
(T
);
2530 Set_Is_Constrained
(T
, False);
2534 -- If the parent type has a known size, so does the formal, which makes
2535 -- legal representation clauses that involve the formal.
2537 Set_Size_Known_At_Compile_Time
2538 (T
, Size_Known_At_Compile_Time
(Entity
(Subtype_Mark
(Def
))));
2539 end Analyze_Formal_Derived_Type
;
2541 ----------------------------------
2542 -- Analyze_Formal_Discrete_Type --
2543 ----------------------------------
2545 -- The operations defined for a discrete types are those of an enumeration
2546 -- type. The size is set to an arbitrary value, for use in analyzing the
2549 procedure Analyze_Formal_Discrete_Type
(T
: Entity_Id
; Def
: Node_Id
) is
2550 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2554 Base
: constant Entity_Id
:=
2556 (E_Floating_Point_Type
, Current_Scope
,
2557 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2561 Mutate_Ekind
(T
, E_Enumeration_Subtype
);
2562 Set_Etype
(T
, Base
);
2564 Reinit_Alignment
(T
);
2565 Set_Is_Generic_Type
(T
);
2566 Set_Is_Constrained
(T
);
2568 -- For semantic analysis, the bounds of the type must be set to some
2569 -- non-static value. The simplest is to create attribute nodes for those
2570 -- bounds, that refer to the type itself. These bounds are never
2571 -- analyzed but serve as place-holders.
2574 Make_Attribute_Reference
(Loc
,
2575 Attribute_Name
=> Name_First
,
2576 Prefix
=> New_Occurrence_Of
(T
, Loc
));
2580 Make_Attribute_Reference
(Loc
,
2581 Attribute_Name
=> Name_Last
,
2582 Prefix
=> New_Occurrence_Of
(T
, Loc
));
2585 Set_Scalar_Range
(T
,
2590 Mutate_Ekind
(Base
, E_Enumeration_Type
);
2591 Set_Etype
(Base
, Base
);
2592 Init_Size
(Base
, 8);
2593 Reinit_Alignment
(Base
);
2594 Set_Is_Generic_Type
(Base
);
2595 Set_Scalar_Range
(Base
, Scalar_Range
(T
));
2596 Set_Parent
(Base
, Parent
(Def
));
2597 end Analyze_Formal_Discrete_Type
;
2599 ----------------------------------
2600 -- Analyze_Formal_Floating_Type --
2601 ---------------------------------
2603 procedure Analyze_Formal_Floating_Type
(T
: Entity_Id
; Def
: Node_Id
) is
2604 Base
: constant Entity_Id
:=
2606 (E_Floating_Point_Type
, Current_Scope
,
2607 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2610 -- The various semantic attributes are taken from the predefined type
2611 -- Float, just so that all of them are initialized. Their values are
2612 -- never used because no constant folding or expansion takes place in
2613 -- the generic itself.
2616 Mutate_Ekind
(T
, E_Floating_Point_Subtype
);
2617 Set_Etype
(T
, Base
);
2618 Set_Size_Info
(T
, (Standard_Float
));
2619 Set_RM_Size
(T
, RM_Size
(Standard_Float
));
2620 Set_Digits_Value
(T
, Digits_Value
(Standard_Float
));
2621 Set_Scalar_Range
(T
, Scalar_Range
(Standard_Float
));
2622 Set_Is_Constrained
(T
);
2624 Set_Is_Generic_Type
(Base
);
2625 Set_Etype
(Base
, Base
);
2626 Set_Size_Info
(Base
, (Standard_Float
));
2627 Set_RM_Size
(Base
, RM_Size
(Standard_Float
));
2628 Set_Digits_Value
(Base
, Digits_Value
(Standard_Float
));
2629 Set_Scalar_Range
(Base
, Scalar_Range
(Standard_Float
));
2630 Set_Parent
(Base
, Parent
(Def
));
2632 Check_Restriction
(No_Floating_Point
, Def
);
2633 end Analyze_Formal_Floating_Type
;
2635 -----------------------------------
2636 -- Analyze_Formal_Interface_Type;--
2637 -----------------------------------
2639 procedure Analyze_Formal_Interface_Type
2644 Loc
: constant Source_Ptr
:= Sloc
(N
);
2649 Make_Full_Type_Declaration
(Loc
,
2650 Defining_Identifier
=> T
,
2651 Type_Definition
=> Def
);
2655 Set_Is_Generic_Type
(T
);
2656 end Analyze_Formal_Interface_Type
;
2658 ---------------------------------
2659 -- Analyze_Formal_Modular_Type --
2660 ---------------------------------
2662 procedure Analyze_Formal_Modular_Type
(T
: Entity_Id
; Def
: Node_Id
) is
2664 -- Apart from their entity kind, generic modular types are treated like
2665 -- signed integer types, and have the same attributes.
2667 Analyze_Formal_Signed_Integer_Type
(T
, Def
);
2668 Mutate_Ekind
(T
, E_Modular_Integer_Subtype
);
2669 Mutate_Ekind
(Etype
(T
), E_Modular_Integer_Type
);
2671 end Analyze_Formal_Modular_Type
;
2673 ---------------------------------------
2674 -- Analyze_Formal_Object_Declaration --
2675 ---------------------------------------
2677 procedure Analyze_Formal_Object_Declaration
(N
: Node_Id
) is
2678 E
: constant Node_Id
:= Default_Expression
(N
);
2679 Id
: constant Node_Id
:= Defining_Identifier
(N
);
2682 Parent_Installed
: Boolean := False;
2688 Check_Abbreviated_Instance
(Parent
(N
), Parent_Installed
);
2690 -- Determine the mode of the formal object
2692 if Out_Present
(N
) then
2693 K
:= E_Generic_In_Out_Parameter
;
2695 if not In_Present
(N
) then
2696 Error_Msg_N
("formal generic objects cannot have mode OUT", N
);
2700 K
:= E_Generic_In_Parameter
;
2703 if Present
(Subtype_Mark
(N
)) then
2704 Find_Type
(Subtype_Mark
(N
));
2705 T
:= Entity
(Subtype_Mark
(N
));
2707 -- Verify that there is no redundant null exclusion
2709 if Null_Exclusion_Present
(N
) then
2710 if not Is_Access_Type
(T
) then
2712 ("null exclusion can only apply to an access type", N
);
2714 elsif Can_Never_Be_Null
(T
) then
2716 ("`NOT NULL` not allowed (& already excludes null)", N
, T
);
2720 -- Ada 2005 (AI-423): Formal object with an access definition
2723 Check_Access_Definition
(N
);
2724 T
:= Access_Definition
2726 N
=> Access_Definition
(N
));
2729 if Ekind
(T
) = E_Incomplete_Type
then
2731 Error_Node
: Node_Id
;
2734 if Present
(Subtype_Mark
(N
)) then
2735 Error_Node
:= Subtype_Mark
(N
);
2737 Check_Access_Definition
(N
);
2738 Error_Node
:= Access_Definition
(N
);
2741 Error_Msg_N
("premature usage of incomplete type", Error_Node
);
2745 if K
= E_Generic_In_Parameter
then
2747 -- Ada 2005 (AI-287): Limited aggregates allowed in generic formals
2749 if Ada_Version
< Ada_2005
and then Is_Limited_Type
(T
) then
2751 ("generic formal of mode IN must not be of limited type", N
);
2752 Explain_Limited_Type
(T
, N
);
2755 if Is_Abstract_Type
(T
) then
2757 ("generic formal of mode IN must not be of abstract type", N
);
2761 Preanalyze_Spec_Expression
(E
, T
);
2763 -- The default for a ghost generic formal IN parameter of
2764 -- access-to-variable type should be a ghost object (SPARK
2767 if Is_Access_Variable
(T
) then
2768 Check_Ghost_Formal_Variable
2771 Is_Default
=> True);
2774 if Is_Limited_Type
(T
) and then not OK_For_Limited_Init
(T
, E
) then
2776 ("initialization not allowed for limited types", E
);
2777 Explain_Limited_Type
(T
, E
);
2781 Mutate_Ekind
(Id
, K
);
2784 -- Case of generic IN OUT parameter
2787 -- If the formal has an unconstrained type, construct its actual
2788 -- subtype, as is done for subprogram formals. In this fashion, all
2789 -- its uses can refer to specific bounds.
2791 Mutate_Ekind
(Id
, K
);
2794 if (Is_Array_Type
(T
) and then not Is_Constrained
(T
))
2795 or else (Ekind
(T
) = E_Record_Type
and then Has_Discriminants
(T
))
2798 Non_Freezing_Ref
: constant Node_Id
:=
2799 New_Occurrence_Of
(Id
, Sloc
(Id
));
2803 -- Make sure the actual subtype doesn't generate bogus freezing
2805 Set_Must_Not_Freeze
(Non_Freezing_Ref
);
2806 Decl
:= Build_Actual_Subtype
(T
, Non_Freezing_Ref
);
2807 Insert_Before_And_Analyze
(N
, Decl
);
2808 Set_Actual_Subtype
(Id
, Defining_Identifier
(Decl
));
2811 Set_Actual_Subtype
(Id
, T
);
2816 ("initialization not allowed for `IN OUT` formals", N
);
2820 if Has_Aspects
(N
) then
2821 Analyze_Aspect_Specifications
(N
, Id
);
2824 if Parent_Installed
then
2827 end Analyze_Formal_Object_Declaration
;
2829 ----------------------------------------------
2830 -- Analyze_Formal_Ordinary_Fixed_Point_Type --
2831 ----------------------------------------------
2833 procedure Analyze_Formal_Ordinary_Fixed_Point_Type
2837 Loc
: constant Source_Ptr
:= Sloc
(Def
);
2838 Base
: constant Entity_Id
:=
2840 (E_Ordinary_Fixed_Point_Type
, Current_Scope
,
2841 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
2844 -- The semantic attributes are set for completeness only, their values
2845 -- will never be used, since all properties of the type are non-static.
2848 Mutate_Ekind
(T
, E_Ordinary_Fixed_Point_Subtype
);
2849 Set_Etype
(T
, Base
);
2850 Set_Size_Info
(T
, Standard_Integer
);
2851 Set_RM_Size
(T
, RM_Size
(Standard_Integer
));
2852 Set_Small_Value
(T
, Ureal_1
);
2853 Set_Delta_Value
(T
, Ureal_1
);
2854 Set_Scalar_Range
(T
,
2856 Low_Bound
=> Make_Real_Literal
(Loc
, Ureal_1
),
2857 High_Bound
=> Make_Real_Literal
(Loc
, Ureal_1
)));
2858 Set_Is_Constrained
(T
);
2860 Set_Is_Generic_Type
(Base
);
2861 Set_Etype
(Base
, Base
);
2862 Set_Size_Info
(Base
, Standard_Integer
);
2863 Set_RM_Size
(Base
, RM_Size
(Standard_Integer
));
2864 Set_Small_Value
(Base
, Ureal_1
);
2865 Set_Delta_Value
(Base
, Ureal_1
);
2866 Set_Scalar_Range
(Base
, Scalar_Range
(T
));
2867 Set_Parent
(Base
, Parent
(Def
));
2869 Check_Restriction
(No_Fixed_Point
, Def
);
2870 end Analyze_Formal_Ordinary_Fixed_Point_Type
;
2872 ----------------------------------------
2873 -- Analyze_Formal_Package_Declaration --
2874 ----------------------------------------
2876 procedure Analyze_Formal_Package_Declaration
(N
: Node_Id
) is
2877 Gen_Id
: constant Node_Id
:= Name
(N
);
2878 Loc
: constant Source_Ptr
:= Sloc
(N
);
2879 Pack_Id
: constant Entity_Id
:= Defining_Identifier
(N
);
2882 Gen_Unit
: Entity_Id
;
2885 Vis_Prims_List
: Elist_Id
:= No_Elist
;
2886 -- List of primitives made temporarily visible in the instantiation
2887 -- to match the visibility of the formal type.
2889 function Build_Local_Package
return Node_Id
;
2890 -- The formal package is rewritten so that its parameters are replaced
2891 -- with corresponding declarations. For parameters with bona fide
2892 -- associations these declarations are created by Analyze_Associations
2893 -- as for a regular instantiation. For boxed parameters, we preserve
2894 -- the formal declarations and analyze them, in order to introduce
2895 -- entities of the right kind in the environment of the formal.
2897 -------------------------
2898 -- Build_Local_Package --
2899 -------------------------
2901 function Build_Local_Package
return Node_Id
is
2903 Pack_Decl
: Node_Id
;
2906 -- Within the formal, the name of the generic package is a renaming
2907 -- of the formal (as for a regular instantiation).
2910 Make_Package_Declaration
(Loc
,
2913 (Specification
(Original_Node
(Gen_Decl
)),
2914 Empty
, Instantiating
=> True));
2917 Make_Package_Renaming_Declaration
(Loc
,
2918 Defining_Unit_Name
=>
2919 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
)),
2920 Name
=> New_Occurrence_Of
(Formal
, Loc
));
2922 if Nkind
(Gen_Id
) = N_Identifier
2923 and then Chars
(Gen_Id
) = Chars
(Pack_Id
)
2926 ("& is hidden within declaration of instance", Gen_Id
, Gen_Unit
);
2929 -- If the formal is declared with a box, or with an others choice,
2930 -- create corresponding declarations for all entities in the formal
2931 -- part, so that names with the proper types are available in the
2932 -- specification of the formal package.
2934 -- On the other hand, if there are no associations, then all the
2935 -- formals must have defaults, and this will be checked by the
2936 -- call to Analyze_Associations.
2939 or else Nkind
(First
(Generic_Associations
(N
))) = N_Others_Choice
2942 Formal_Decl
: Node_Id
;
2945 -- TBA : for a formal package, need to recurse ???
2950 (Generic_Formal_Declarations
(Original_Node
(Gen_Decl
)));
2951 while Present
(Formal_Decl
) loop
2955 (Formal_Decl
, Empty
, Instantiating
=> True));
2960 -- If generic associations are present, use Analyze_Associations to
2961 -- create the proper renaming declarations.
2965 Act_Tree
: constant Node_Id
:=
2967 (Original_Node
(Gen_Decl
), Empty
,
2968 Instantiating
=> True);
2971 Generic_Renamings
.Set_Last
(0);
2972 Generic_Renamings_HTable
.Reset
;
2973 Instantiation_Node
:= N
;
2976 Analyze_Associations
2977 (I_Node
=> Original_Node
(N
),
2978 Formals
=> Generic_Formal_Declarations
(Act_Tree
),
2979 F_Copy
=> Generic_Formal_Declarations
(Gen_Decl
));
2981 Vis_Prims_List
:= Check_Hidden_Primitives
(Decls
);
2985 Append
(Renaming
, To
=> Decls
);
2987 -- Add generated declarations ahead of local declarations in
2990 if No
(Visible_Declarations
(Specification
(Pack_Decl
))) then
2991 Set_Visible_Declarations
(Specification
(Pack_Decl
), Decls
);
2994 (First
(Visible_Declarations
(Specification
(Pack_Decl
))),
2999 end Build_Local_Package
;
3003 Save_ISMP
: constant Boolean := Ignore_SPARK_Mode_Pragmas_In_Instance
;
3004 -- Save flag Ignore_SPARK_Mode_Pragmas_In_Instance for restore on exit
3006 Associations
: Boolean := True;
3008 Parent_Installed
: Boolean := False;
3009 Parent_Instance
: Entity_Id
;
3010 Renaming_In_Par
: Entity_Id
;
3012 -- Start of processing for Analyze_Formal_Package_Declaration
3015 Check_Text_IO_Special_Unit
(Gen_Id
);
3018 Check_Generic_Child_Unit
(Gen_Id
, Parent_Installed
);
3019 Gen_Unit
:= Entity
(Gen_Id
);
3021 -- Check for a formal package that is a package renaming
3023 if Present
(Renamed_Entity
(Gen_Unit
)) then
3025 -- Indicate that unit is used, before replacing it with renamed
3026 -- entity for use below.
3028 if In_Extended_Main_Source_Unit
(N
) then
3029 Set_Is_Instantiated
(Gen_Unit
);
3030 Generate_Reference
(Gen_Unit
, N
);
3033 Gen_Unit
:= Renamed_Entity
(Gen_Unit
);
3036 if Ekind
(Gen_Unit
) /= E_Generic_Package
then
3037 Error_Msg_N
("expect generic package name", Gen_Id
);
3041 elsif Gen_Unit
= Current_Scope
then
3043 ("generic package cannot be used as a formal package of itself",
3048 elsif In_Open_Scopes
(Gen_Unit
) then
3049 if Is_Compilation_Unit
(Gen_Unit
)
3050 and then Is_Child_Unit
(Current_Scope
)
3052 -- Special-case the error when the formal is a parent, and
3053 -- continue analysis to minimize cascaded errors.
3056 ("generic parent cannot be used as formal package of a child "
3061 ("generic package cannot be used as a formal package within "
3062 & "itself", Gen_Id
);
3068 -- Check that name of formal package does not hide name of generic,
3069 -- or its leading prefix. This check must be done separately because
3070 -- the name of the generic has already been analyzed.
3073 Gen_Name
: Entity_Id
;
3077 while Nkind
(Gen_Name
) = N_Expanded_Name
loop
3078 Gen_Name
:= Prefix
(Gen_Name
);
3081 if Chars
(Gen_Name
) = Chars
(Pack_Id
) then
3083 ("& is hidden within declaration of formal package",
3089 or else No
(Generic_Associations
(N
))
3090 or else Nkind
(First
(Generic_Associations
(N
))) = N_Others_Choice
3092 Associations
:= False;
3095 -- If there are no generic associations, the generic parameters appear
3096 -- as local entities and are instantiated like them. We copy the generic
3097 -- package declaration as if it were an instantiation, and analyze it
3098 -- like a regular package, except that we treat the formals as
3099 -- additional visible components.
3101 Gen_Decl
:= Unit_Declaration_Node
(Gen_Unit
);
3103 if In_Extended_Main_Source_Unit
(N
) then
3104 Set_Is_Instantiated
(Gen_Unit
);
3105 Generate_Reference
(Gen_Unit
, N
);
3108 Formal
:= New_Copy
(Pack_Id
);
3109 Create_Instantiation_Source
(N
, Gen_Unit
, S_Adjustment
);
3111 -- Make local generic without formals. The formals will be replaced with
3112 -- internal declarations.
3115 New_N
:= Build_Local_Package
;
3117 -- If there are errors in the parameter list, Analyze_Associations
3118 -- raises Instantiation_Error. Patch the declaration to prevent further
3119 -- exception propagation.
3122 when Instantiation_Error
=>
3123 Enter_Name
(Formal
);
3124 Mutate_Ekind
(Formal
, E_Variable
);
3125 Set_Etype
(Formal
, Any_Type
);
3126 Restore_Hidden_Primitives
(Vis_Prims_List
);
3128 if Parent_Installed
then
3136 Set_Defining_Unit_Name
(Specification
(New_N
), Formal
);
3137 Set_Generic_Parent
(Specification
(N
), Gen_Unit
);
3138 Set_Instance_Env
(Gen_Unit
, Formal
);
3139 Set_Is_Generic_Instance
(Formal
);
3141 Enter_Name
(Formal
);
3142 Mutate_Ekind
(Formal
, E_Package
);
3143 Set_Etype
(Formal
, Standard_Void_Type
);
3144 Set_Inner_Instances
(Formal
, New_Elmt_List
);
3146 -- It is unclear that any aspects can apply to a formal package
3147 -- declaration, given that they look like a hidden conformance
3148 -- requirement on the corresponding actual. However, Abstract_State
3149 -- must be treated specially because it generates declarations that
3150 -- must appear before other declarations in the specification and
3151 -- must be analyzed at once.
3153 if Present
(Aspect_Specifications
(Gen_Decl
)) then
3154 if No
(Aspect_Specifications
(N
)) then
3155 Set_Aspect_Specifications
(N
, New_List
);
3159 ASN
: Node_Id
:= First
(Aspect_Specifications
(Gen_Decl
));
3163 while Present
(ASN
) loop
3164 if Get_Aspect_Id
(ASN
) = Aspect_Abstract_State
then
3166 Copy_Generic_Node
(ASN
, Empty
, Instantiating
=> True);
3167 Set_Entity
(New_A
, Formal
);
3168 Set_Analyzed
(New_A
, False);
3169 Append
(New_A
, Aspect_Specifications
(N
));
3170 Analyze_Aspect_Specifications
(N
, Formal
);
3179 Push_Scope
(Formal
);
3181 -- Manually set the SPARK_Mode from the context because the package
3182 -- declaration is never analyzed.
3184 Set_SPARK_Pragma
(Formal
, SPARK_Mode_Pragma
);
3185 Set_SPARK_Aux_Pragma
(Formal
, SPARK_Mode_Pragma
);
3186 Set_SPARK_Pragma_Inherited
(Formal
);
3187 Set_SPARK_Aux_Pragma_Inherited
(Formal
);
3189 if Is_Child_Unit
(Gen_Unit
) and then Parent_Installed
then
3191 -- Similarly, we have to make the name of the formal visible in the
3192 -- parent instance, to resolve properly fully qualified names that
3193 -- may appear in the generic unit. The parent instance has been
3194 -- placed on the scope stack ahead of the current scope.
3196 Parent_Instance
:= Scope_Stack
.Table
(Scope_Stack
.Last
- 1).Entity
;
3199 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
));
3200 Mutate_Ekind
(Renaming_In_Par
, E_Package
);
3201 Set_Is_Not_Self_Hidden
(Renaming_In_Par
);
3202 Set_Etype
(Renaming_In_Par
, Standard_Void_Type
);
3203 Set_Scope
(Renaming_In_Par
, Parent_Instance
);
3204 Set_Parent
(Renaming_In_Par
, Parent
(Formal
));
3205 Set_Renamed_Entity
(Renaming_In_Par
, Formal
);
3206 Append_Entity
(Renaming_In_Par
, Parent_Instance
);
3209 -- A formal package declaration behaves as a package instantiation with
3210 -- respect to SPARK_Mode "off". If the annotation is "off" or altogether
3211 -- missing, set the global flag which signals Analyze_Pragma to ingnore
3212 -- all SPARK_Mode pragmas within the generic_package_name.
3214 if SPARK_Mode
/= On
then
3215 Ignore_SPARK_Mode_Pragmas_In_Instance
:= True;
3217 -- Mark the formal spec in case the body is instantiated at a later
3218 -- pass. This preserves the original context in effect for the body.
3220 Set_Ignore_SPARK_Mode_Pragmas
(Formal
);
3223 Analyze
(Specification
(N
));
3225 -- The formals for which associations are provided are not visible
3226 -- outside of the formal package. The others are still declared by a
3227 -- formal parameter declaration.
3229 -- If there are no associations, the only local entity to hide is the
3230 -- generated package renaming itself.
3236 E
:= First_Entity
(Formal
);
3237 while Present
(E
) loop
3238 if Associations
and then not Is_Generic_Formal
(E
) then
3242 if Ekind
(E
) = E_Package
and then Renamed_Entity
(E
) = Formal
then
3251 End_Package_Scope
(Formal
);
3252 Restore_Hidden_Primitives
(Vis_Prims_List
);
3254 if Parent_Installed
then
3260 -- Inside the generic unit, the formal package is a regular package, but
3261 -- no body is needed for it. Note that after instantiation, the defining
3262 -- unit name we need is in the new tree and not in the original (see
3263 -- Package_Instantiation). A generic formal package is an instance, and
3264 -- can be used as an actual for an inner instance.
3266 Set_Has_Completion
(Formal
, True);
3268 -- Add semantic information to the original defining identifier.
3270 Mutate_Ekind
(Pack_Id
, E_Package
);
3271 Set_Etype
(Pack_Id
, Standard_Void_Type
);
3272 Set_Scope
(Pack_Id
, Scope
(Formal
));
3273 Set_Has_Completion
(Pack_Id
, True);
3276 if Has_Aspects
(N
) then
3277 -- Unclear that any other aspects may appear here, analyze them
3278 -- for completion, given that the grammar allows their appearance.
3280 Analyze_Aspect_Specifications
(N
, Pack_Id
);
3283 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Save_ISMP
;
3284 end Analyze_Formal_Package_Declaration
;
3286 ---------------------------------
3287 -- Analyze_Formal_Private_Type --
3288 ---------------------------------
3290 procedure Analyze_Formal_Private_Type
3296 New_Private_Type
(N
, T
, Def
);
3298 -- Set the size to an arbitrary but legal value
3300 Set_Size_Info
(T
, Standard_Integer
);
3301 Set_RM_Size
(T
, RM_Size
(Standard_Integer
));
3302 end Analyze_Formal_Private_Type
;
3304 ------------------------------------
3305 -- Analyze_Formal_Incomplete_Type --
3306 ------------------------------------
3308 procedure Analyze_Formal_Incomplete_Type
3314 Mutate_Ekind
(T
, E_Incomplete_Type
);
3316 Set_Private_Dependents
(T
, New_Elmt_List
);
3318 if Tagged_Present
(Def
) then
3319 Set_Is_Tagged_Type
(T
);
3320 Make_Class_Wide_Type
(T
);
3321 Set_Direct_Primitive_Operations
(T
, New_Elmt_List
);
3323 end Analyze_Formal_Incomplete_Type
;
3325 ----------------------------------------
3326 -- Analyze_Formal_Signed_Integer_Type --
3327 ----------------------------------------
3329 procedure Analyze_Formal_Signed_Integer_Type
3333 Base
: constant Entity_Id
:=
3335 (E_Signed_Integer_Type
,
3337 Sloc
(Defining_Identifier
(Parent
(Def
))), 'G');
3342 Mutate_Ekind
(T
, E_Signed_Integer_Subtype
);
3343 Set_Etype
(T
, Base
);
3344 Set_Size_Info
(T
, Standard_Integer
);
3345 Set_RM_Size
(T
, RM_Size
(Standard_Integer
));
3346 Set_Scalar_Range
(T
, Scalar_Range
(Standard_Integer
));
3347 Set_Is_Constrained
(T
);
3349 Set_Is_Generic_Type
(Base
);
3350 Set_Size_Info
(Base
, Standard_Integer
);
3351 Set_RM_Size
(Base
, RM_Size
(Standard_Integer
));
3352 Set_Etype
(Base
, Base
);
3353 Set_Scalar_Range
(Base
, Scalar_Range
(Standard_Integer
));
3354 Set_Parent
(Base
, Parent
(Def
));
3355 end Analyze_Formal_Signed_Integer_Type
;
3357 -------------------------------------------
3358 -- Analyze_Formal_Subprogram_Declaration --
3359 -------------------------------------------
3361 procedure Analyze_Formal_Subprogram_Declaration
(N
: Node_Id
) is
3362 Spec
: constant Node_Id
:= Specification
(N
);
3363 Def
: constant Node_Id
:= Default_Name
(N
);
3364 Expr
: constant Node_Id
:= Expression
(N
);
3365 Nam
: constant Entity_Id
:= Defining_Unit_Name
(Spec
);
3367 Parent_Installed
: Boolean := False;
3375 if Nkind
(Nam
) = N_Defining_Program_Unit_Name
then
3376 Error_Msg_N
("name of formal subprogram must be a direct name", Nam
);
3380 Check_Abbreviated_Instance
(Parent
(N
), Parent_Installed
);
3382 Analyze_Subprogram_Declaration
(N
);
3383 Set_Is_Formal_Subprogram
(Nam
);
3384 Set_Has_Completion
(Nam
);
3386 if Nkind
(N
) = N_Formal_Abstract_Subprogram_Declaration
then
3387 Set_Is_Abstract_Subprogram
(Nam
);
3389 Set_Is_Dispatching_Operation
(Nam
);
3391 -- A formal abstract procedure cannot have a null default
3392 -- (RM 12.6(4.1/2)).
3394 if Nkind
(Spec
) = N_Procedure_Specification
3395 and then Null_Present
(Spec
)
3398 ("a formal abstract subprogram cannot default to null", Spec
);
3401 -- A formal abstract function cannot have an expression default
3402 -- (expression defaults are allowed for nonabstract formal functions
3403 -- when extensions are enabled).
3405 if Nkind
(Spec
) = N_Function_Specification
3406 and then Present
(Expr
)
3409 ("a formal abstract subprogram cannot default to an expression",
3414 Ctrl_Type
: constant Entity_Id
:= Find_Dispatching_Type
(Nam
);
3416 if No
(Ctrl_Type
) then
3418 ("abstract formal subprogram must have a controlling type",
3421 elsif Ada_Version
>= Ada_2012
3422 and then Is_Incomplete_Type
(Ctrl_Type
)
3425 ("controlling type of abstract formal subprogram cannot "
3426 & "be incomplete type", N
, Ctrl_Type
);
3429 Check_Controlling_Formals
(Ctrl_Type
, Nam
);
3434 -- Default name is resolved at the point of instantiation
3436 if Box_Present
(N
) then
3439 -- Default name is bound at the point of generic declaration
3441 elsif Present
(Def
) then
3442 if Nkind
(Def
) = N_Operator_Symbol
then
3443 Find_Direct_Name
(Def
);
3445 elsif Nkind
(Def
) /= N_Attribute_Reference
then
3449 -- For an attribute reference, analyze the prefix and verify
3450 -- that it has the proper profile for the subprogram.
3452 Analyze
(Prefix
(Def
));
3453 Valid_Default_Attribute
(Nam
, Def
);
3457 -- The default for a ghost generic formal procedure should be a ghost
3458 -- procedure (SPARK RM 6.9(13)).
3460 if Ekind
(Nam
) = E_Procedure
then
3462 Def_E
: Entity_Id
:= Empty
;
3464 if Nkind
(Def
) in N_Has_Entity
then
3465 Def_E
:= Entity
(Def
);
3468 Check_Ghost_Formal_Procedure_Or_Package
3472 Is_Default
=> True);
3476 -- Default name may be overloaded, in which case the interpretation
3477 -- with the correct profile must be selected, as for a renaming.
3478 -- If the definition is an indexed component, it must denote a
3479 -- member of an entry family. If it is a selected component, it
3480 -- can be a protected operation.
3482 if Etype
(Def
) = Any_Type
then
3485 elsif Nkind
(Def
) = N_Selected_Component
then
3486 if not Is_Overloadable
(Entity
(Selector_Name
(Def
))) then
3487 Error_Msg_N
("expect valid subprogram name as default", Def
);
3490 elsif Nkind
(Def
) = N_Indexed_Component
then
3491 if Is_Entity_Name
(Prefix
(Def
)) then
3492 if Ekind
(Entity
(Prefix
(Def
))) /= E_Entry_Family
then
3493 Error_Msg_N
("expect valid subprogram name as default", Def
);
3496 elsif Nkind
(Prefix
(Def
)) = N_Selected_Component
then
3497 if Ekind
(Entity
(Selector_Name
(Prefix
(Def
)))) /=
3500 Error_Msg_N
("expect valid subprogram name as default", Def
);
3504 Error_Msg_N
("expect valid subprogram name as default", Def
);
3508 elsif Nkind
(Def
) = N_Character_Literal
then
3510 -- Needs some type checks: subprogram should be parameterless???
3512 Resolve
(Def
, (Etype
(Nam
)));
3514 elsif not Is_Entity_Name
(Def
)
3515 or else not Is_Overloadable
(Entity
(Def
))
3517 Error_Msg_N
("expect valid subprogram name as default", Def
);
3520 elsif not Is_Overloaded
(Def
) then
3521 Subp
:= Entity
(Def
);
3524 Error_Msg_N
("premature usage of formal subprogram", Def
);
3526 elsif not Entity_Matches_Spec
(Subp
, Nam
) then
3527 Error_Msg_N
("no visible entity matches specification", Def
);
3530 -- More than one interpretation, so disambiguate as for a renaming
3535 I1
: Interp_Index
:= 0;
3541 Get_First_Interp
(Def
, I
, It
);
3542 while Present
(It
.Nam
) loop
3543 if Entity_Matches_Spec
(It
.Nam
, Nam
) then
3544 if Subp
/= Any_Id
then
3545 It1
:= Disambiguate
(Def
, I1
, I
, Etype
(Subp
));
3547 if It1
= No_Interp
then
3548 Error_Msg_N
("ambiguous default subprogram", Def
);
3561 Get_Next_Interp
(I
, It
);
3565 if Subp
/= Any_Id
then
3567 -- Subprogram found, generate reference to it
3569 Set_Entity
(Def
, Subp
);
3570 Generate_Reference
(Subp
, Def
);
3573 Error_Msg_N
("premature usage of formal subprogram", Def
);
3575 elsif Ekind
(Subp
) /= E_Operator
then
3576 Check_Mode_Conformant
(Subp
, Nam
);
3580 Error_Msg_N
("no visible subprogram matches specification", N
);
3584 -- When extensions are enabled, an expression can be given as default
3585 -- for a formal function. The expression must be of the function result
3586 -- type and can reference formal parameters of the function.
3588 elsif Present
(Expr
) then
3590 Install_Formals
(Nam
);
3591 Preanalyze_Spec_Expression
(Expr
, Etype
(Nam
));
3596 if Has_Aspects
(N
) then
3597 Analyze_Aspect_Specifications
(N
, Nam
);
3600 if Parent_Installed
then
3603 end Analyze_Formal_Subprogram_Declaration
;
3605 -------------------------------------
3606 -- Analyze_Formal_Type_Declaration --
3607 -------------------------------------
3609 procedure Analyze_Formal_Type_Declaration
(N
: Node_Id
) is
3610 Def
: constant Node_Id
:= Formal_Type_Definition
(N
);
3612 Parent_Installed
: Boolean := False;
3616 T
:= Defining_Identifier
(N
);
3618 if Present
(Discriminant_Specifications
(N
))
3619 and then Nkind
(Def
) /= N_Formal_Private_Type_Definition
3622 ("discriminants not allowed for this formal type", T
);
3625 Check_Abbreviated_Instance
(Parent
(N
), Parent_Installed
);
3627 -- Enter the new name, and branch to specific routine
3630 when N_Formal_Private_Type_Definition
=>
3631 Analyze_Formal_Private_Type
(N
, T
, Def
);
3633 when N_Formal_Derived_Type_Definition
=>
3634 Analyze_Formal_Derived_Type
(N
, T
, Def
);
3636 when N_Formal_Incomplete_Type_Definition
=>
3637 Analyze_Formal_Incomplete_Type
(T
, Def
);
3639 when N_Formal_Discrete_Type_Definition
=>
3640 Analyze_Formal_Discrete_Type
(T
, Def
);
3642 when N_Formal_Signed_Integer_Type_Definition
=>
3643 Analyze_Formal_Signed_Integer_Type
(T
, Def
);
3645 when N_Formal_Modular_Type_Definition
=>
3646 Analyze_Formal_Modular_Type
(T
, Def
);
3648 when N_Formal_Floating_Point_Definition
=>
3649 Analyze_Formal_Floating_Type
(T
, Def
);
3651 when N_Formal_Ordinary_Fixed_Point_Definition
=>
3652 Analyze_Formal_Ordinary_Fixed_Point_Type
(T
, Def
);
3654 when N_Formal_Decimal_Fixed_Point_Definition
=>
3655 Analyze_Formal_Decimal_Fixed_Point_Type
(T
, Def
);
3657 when N_Array_Type_Definition
=>
3658 Analyze_Formal_Array_Type
(T
, Def
);
3660 when N_Access_Function_Definition
3661 | N_Access_Procedure_Definition
3662 | N_Access_To_Object_Definition
3664 Analyze_Generic_Access_Type
(T
, Def
);
3666 -- Ada 2005: a interface declaration is encoded as an abstract
3667 -- record declaration or a abstract type derivation.
3669 when N_Record_Definition
=>
3670 Analyze_Formal_Interface_Type
(N
, T
, Def
);
3672 when N_Derived_Type_Definition
=>
3673 Analyze_Formal_Derived_Interface_Type
(N
, T
, Def
);
3679 raise Program_Error
;
3682 -- A formal type declaration declares a type and its first
3685 Set_Is_Generic_Type
(T
);
3686 Set_Is_First_Subtype
(T
);
3688 if Present
(Default_Subtype_Mark
(Original_Node
(N
))) then
3689 Validate_Formal_Type_Default
(N
);
3692 if Has_Aspects
(N
) then
3693 Analyze_Aspect_Specifications
(N
, T
);
3696 if Parent_Installed
then
3699 end Analyze_Formal_Type_Declaration
;
3701 ------------------------------------
3702 -- Analyze_Function_Instantiation --
3703 ------------------------------------
3705 procedure Analyze_Function_Instantiation
(N
: Node_Id
) is
3707 Analyze_Subprogram_Instantiation
(N
, E_Function
);
3708 end Analyze_Function_Instantiation
;
3710 ---------------------------------
3711 -- Analyze_Generic_Access_Type --
3712 ---------------------------------
3714 procedure Analyze_Generic_Access_Type
(T
: Entity_Id
; Def
: Node_Id
) is
3718 if Nkind
(Def
) = N_Access_To_Object_Definition
then
3719 Access_Type_Declaration
(T
, Def
);
3721 if Is_Incomplete_Or_Private_Type
(Designated_Type
(T
))
3722 and then No
(Full_View
(Designated_Type
(T
)))
3723 and then not Is_Generic_Type
(Designated_Type
(T
))
3725 Error_Msg_N
("premature usage of incomplete type", Def
);
3727 elsif not Is_Entity_Name
(Subtype_Indication
(Def
)) then
3729 ("only a subtype mark is allowed in a formal", Def
);
3733 Access_Subprogram_Declaration
(T
, Def
);
3735 end Analyze_Generic_Access_Type
;
3737 ---------------------------------
3738 -- Analyze_Generic_Formal_Part --
3739 ---------------------------------
3741 procedure Analyze_Generic_Formal_Part
(N
: Node_Id
) is
3742 Gen_Parm_Decl
: Node_Id
;
3745 -- The generic formals are processed in the scope of the generic unit,
3746 -- where they are immediately visible. The scope is installed by the
3749 Gen_Parm_Decl
:= First
(Generic_Formal_Declarations
(N
));
3750 while Present
(Gen_Parm_Decl
) loop
3751 Analyze
(Gen_Parm_Decl
);
3752 Next
(Gen_Parm_Decl
);
3755 Generate_Reference_To_Generic_Formals
(Current_Scope
);
3757 -- For Ada 2022, some formal parameters can carry aspects, which must
3758 -- be name-resolved at the end of the list of formal parameters (which
3759 -- has the semantics of a declaration list).
3761 Analyze_Contracts
(Generic_Formal_Declarations
(N
));
3762 end Analyze_Generic_Formal_Part
;
3764 ------------------------------------------
3765 -- Analyze_Generic_Package_Declaration --
3766 ------------------------------------------
3768 procedure Analyze_Generic_Package_Declaration
(N
: Node_Id
) is
3769 Decls
: constant List_Id
:= Visible_Declarations
(Specification
(N
));
3770 Loc
: constant Source_Ptr
:= Sloc
(N
);
3776 Save_Parent
: Node_Id
;
3779 -- A generic may grant access to its private enclosing context depending
3780 -- on the placement of its corresponding body. From elaboration point of
3781 -- view, the flow of execution may enter this private context, and then
3782 -- reach an external unit, thus producing a dependency on that external
3783 -- unit. For such a path to be properly discovered and encoded in the
3784 -- ALI file of the main unit, let the ABE mechanism process the body of
3785 -- the main unit, and encode all relevant invocation constructs and the
3786 -- relations between them.
3788 Mark_Save_Invocation_Graph_Of_Body
;
3790 -- We introduce a renaming of the enclosing package, to have a usable
3791 -- entity as the prefix of an expanded name for a local entity of the
3792 -- form Par.P.Q, where P is the generic package. This is because a local
3793 -- entity named P may hide it, so that the usual visibility rules in
3794 -- the instance will not resolve properly.
3797 Make_Package_Renaming_Declaration
(Loc
,
3798 Defining_Unit_Name
=>
3799 Make_Defining_Identifier
(Loc
,
3800 Chars
=> New_External_Name
(Chars
(Defining_Entity
(N
)), "GH")),
3802 Make_Identifier
(Loc
, Chars
(Defining_Entity
(N
))));
3804 -- The declaration is inserted before other declarations, but before
3805 -- pragmas that may be library-unit pragmas and must appear before other
3806 -- declarations. The pragma Compile_Time_Error is not in this class, and
3807 -- may contain an expression that includes such a qualified name, so the
3808 -- renaming declaration must appear before it.
3810 -- Are there other pragmas that require this special handling ???
3812 if Present
(Decls
) then
3813 Decl
:= First
(Decls
);
3814 while Present
(Decl
)
3815 and then Nkind
(Decl
) = N_Pragma
3816 and then Get_Pragma_Id
(Decl
) /= Pragma_Compile_Time_Error
3821 if Present
(Decl
) then
3822 Insert_Before
(Decl
, Renaming
);
3824 Append
(Renaming
, Visible_Declarations
(Specification
(N
)));
3828 Set_Visible_Declarations
(Specification
(N
), New_List
(Renaming
));
3831 -- Create copy of generic unit, and save for instantiation. If the unit
3832 -- is a child unit, do not copy the specifications for the parent, which
3833 -- are not part of the generic tree.
3835 Save_Parent
:= Parent_Spec
(N
);
3836 Set_Parent_Spec
(N
, Empty
);
3838 New_N
:= Copy_Generic_Node
(N
, Empty
, Instantiating
=> False);
3839 Set_Parent_Spec
(New_N
, Save_Parent
);
3842 -- Once the contents of the generic copy and the template are swapped,
3843 -- do the same for their respective aspect specifications.
3845 Exchange_Aspects
(N
, New_N
);
3847 -- Collect all contract-related source pragmas found within the template
3848 -- and attach them to the contract of the package spec. This contract is
3849 -- used in the capture of global references within annotations.
3851 Create_Generic_Contract
(N
);
3853 Id
:= Defining_Entity
(N
);
3854 Generate_Definition
(Id
);
3856 -- Expansion is not applied to generic units
3861 Mutate_Ekind
(Id
, E_Generic_Package
);
3862 Set_Is_Not_Self_Hidden
(Id
);
3863 Set_Etype
(Id
, Standard_Void_Type
);
3865 -- Set SPARK_Mode from context
3867 Set_SPARK_Pragma
(Id
, SPARK_Mode_Pragma
);
3868 Set_SPARK_Aux_Pragma
(Id
, SPARK_Mode_Pragma
);
3869 Set_SPARK_Pragma_Inherited
(Id
);
3870 Set_SPARK_Aux_Pragma_Inherited
(Id
);
3872 -- Preserve relevant elaboration-related attributes of the context which
3873 -- are no longer available or very expensive to recompute once analysis,
3874 -- resolution, and expansion are over.
3876 Mark_Elaboration_Attributes
3881 -- Analyze aspects now, so that generated pragmas appear in the
3882 -- declarations before building and analyzing the generic copy.
3884 if Has_Aspects
(N
) then
3885 Analyze_Aspect_Specifications
(N
, Id
);
3889 Enter_Generic_Scope
(Id
);
3890 Set_Inner_Instances
(Id
, New_Elmt_List
);
3892 Set_Categorization_From_Pragmas
(N
);
3893 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
3895 -- Link the declaration of the generic homonym in the generic copy to
3896 -- the package it renames, so that it is always resolved properly.
3898 Set_Generic_Homonym
(Id
, Defining_Unit_Name
(Renaming
));
3899 Set_Entity
(Associated_Node
(Name
(Renaming
)), Id
);
3901 -- For a library unit, we have reconstructed the entity for the unit,
3902 -- and must reset it in the library tables.
3904 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
3905 Set_Cunit_Entity
(Current_Sem_Unit
, Id
);
3908 Analyze_Generic_Formal_Part
(N
);
3910 -- After processing the generic formals, analysis proceeds as for a
3911 -- non-generic package.
3913 Analyze
(Specification
(N
));
3915 Validate_Categorization_Dependency
(N
, Id
);
3919 End_Package_Scope
(Id
);
3920 Exit_Generic_Scope
(Id
);
3922 -- If the generic appears within a package unit, the body of that unit
3923 -- has to be present for instantiation and inlining.
3925 if Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) = N_Package_Declaration
then
3926 Set_Body_Needed_For_Inlining
3927 (Defining_Entity
(Unit
(Cunit
(Current_Sem_Unit
))));
3930 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
3931 Move_Freeze_Nodes
(Id
, N
, Visible_Declarations
(Specification
(N
)));
3932 Move_Freeze_Nodes
(Id
, N
, Private_Declarations
(Specification
(N
)));
3933 Move_Freeze_Nodes
(Id
, N
, Generic_Formal_Declarations
(N
));
3936 Set_Body_Required
(Parent
(N
), Unit_Requires_Body
(Id
));
3937 Validate_RT_RAT_Component
(N
);
3939 -- If this is a spec without a body, check that generic parameters
3942 if not Body_Required
(Parent
(N
)) then
3943 Check_References
(Id
);
3947 -- If there is a specified storage pool in the context, create an
3948 -- aspect on the package declaration, so that it is used in any
3949 -- instance that does not override it.
3951 if Present
(Default_Pool
) then
3957 Make_Aspect_Specification
(Loc
,
3958 Identifier
=> Make_Identifier
(Loc
, Name_Default_Storage_Pool
),
3959 Expression
=> New_Copy
(Default_Pool
));
3961 if No
(Aspect_Specifications
(Specification
(N
))) then
3962 Set_Aspect_Specifications
(Specification
(N
), New_List
(ASN
));
3964 Append
(ASN
, Aspect_Specifications
(Specification
(N
)));
3968 end Analyze_Generic_Package_Declaration
;
3970 --------------------------------------------
3971 -- Analyze_Generic_Subprogram_Declaration --
3972 --------------------------------------------
3974 procedure Analyze_Generic_Subprogram_Declaration
(N
: Node_Id
) is
3978 Result_Type
: Entity_Id
;
3979 Save_Parent
: Node_Id
;
3984 -- A generic may grant access to its private enclosing context depending
3985 -- on the placement of its corresponding body. From elaboration point of
3986 -- view, the flow of execution may enter this private context, and then
3987 -- reach an external unit, thus producing a dependency on that external
3988 -- unit. For such a path to be properly discovered and encoded in the
3989 -- ALI file of the main unit, let the ABE mechanism process the body of
3990 -- the main unit, and encode all relevant invocation constructs and the
3991 -- relations between them.
3993 Mark_Save_Invocation_Graph_Of_Body
;
3995 -- Create copy of generic unit, and save for instantiation. If the unit
3996 -- is a child unit, do not copy the specifications for the parent, which
3997 -- are not part of the generic tree.
3999 Save_Parent
:= Parent_Spec
(N
);
4000 Set_Parent_Spec
(N
, Empty
);
4002 New_N
:= Copy_Generic_Node
(N
, Empty
, Instantiating
=> False);
4003 Set_Parent_Spec
(New_N
, Save_Parent
);
4006 -- Once the contents of the generic copy and the template are swapped,
4007 -- do the same for their respective aspect specifications.
4009 Exchange_Aspects
(N
, New_N
);
4011 -- Collect all contract-related source pragmas found within the template
4012 -- and attach them to the contract of the subprogram spec. This contract
4013 -- is used in the capture of global references within annotations.
4015 Create_Generic_Contract
(N
);
4017 Spec
:= Specification
(N
);
4018 Id
:= Defining_Entity
(Spec
);
4019 Generate_Definition
(Id
);
4021 if Nkind
(Id
) = N_Defining_Operator_Symbol
then
4023 ("operator symbol not allowed for generic subprogram", Id
);
4029 Set_Scope_Depth_Value
(Id
, Scope_Depth
(Current_Scope
) + 1);
4032 Enter_Generic_Scope
(Id
);
4033 Set_Inner_Instances
(Id
, New_Elmt_List
);
4034 Set_Is_Pure
(Id
, Is_Pure
(Current_Scope
));
4036 Analyze_Generic_Formal_Part
(N
);
4038 if Nkind
(Spec
) = N_Function_Specification
then
4039 Mutate_Ekind
(Id
, E_Generic_Function
);
4041 Mutate_Ekind
(Id
, E_Generic_Procedure
);
4044 -- Set SPARK_Mode from context
4046 Set_SPARK_Pragma
(Id
, SPARK_Mode_Pragma
);
4047 Set_SPARK_Pragma_Inherited
(Id
);
4049 -- Preserve relevant elaboration-related attributes of the context which
4050 -- are no longer available or very expensive to recompute once analysis,
4051 -- resolution, and expansion are over.
4053 Mark_Elaboration_Attributes
4058 Formals
:= Parameter_Specifications
(Spec
);
4060 if Present
(Formals
) then
4061 Process_Formals
(Formals
, Spec
);
4064 if Nkind
(Spec
) = N_Function_Specification
then
4065 if Nkind
(Result_Definition
(Spec
)) = N_Access_Definition
then
4066 Result_Type
:= Access_Definition
(Spec
, Result_Definition
(Spec
));
4067 Set_Etype
(Id
, Result_Type
);
4069 -- Check restriction imposed by AI05-073: a generic function
4070 -- cannot return an abstract type or an access to such.
4072 if Is_Abstract_Type
(Designated_Type
(Result_Type
)) then
4074 ("generic function cannot have an access result "
4075 & "that designates an abstract type", Spec
);
4079 Find_Type
(Result_Definition
(Spec
));
4080 Typ
:= Entity
(Result_Definition
(Spec
));
4082 if Is_Abstract_Type
(Typ
)
4083 and then Ada_Version
>= Ada_2012
4086 ("generic function cannot have abstract result type", Spec
);
4089 -- If a null exclusion is imposed on the result type, then create
4090 -- a null-excluding itype (an access subtype) and use it as the
4091 -- function's Etype.
4093 if Is_Access_Type
(Typ
)
4094 and then Null_Exclusion_Present
(Spec
)
4097 Create_Null_Excluding_Itype
4099 Related_Nod
=> Spec
,
4100 Scope_Id
=> Defining_Unit_Name
(Spec
)));
4102 Set_Etype
(Id
, Typ
);
4107 Set_Etype
(Id
, Standard_Void_Type
);
4110 Set_Is_Not_Self_Hidden
(Id
);
4112 -- Analyze the aspects of the generic copy to ensure that all generated
4113 -- pragmas (if any) perform their semantic effects.
4115 if Has_Aspects
(N
) then
4116 Analyze_Aspect_Specifications
(N
, Id
);
4119 -- For a library unit, we have reconstructed the entity for the unit,
4120 -- and must reset it in the library tables. We also make sure that
4121 -- Body_Required is set properly in the original compilation unit node.
4123 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
4124 Set_Cunit_Entity
(Current_Sem_Unit
, Id
);
4125 Set_Body_Required
(Parent
(N
), Unit_Requires_Body
(Id
));
4128 -- If the generic appears within a package unit, the body of that unit
4129 -- has to be present for instantiation and inlining.
4131 if Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) = N_Package_Declaration
4132 and then Unit_Requires_Body
(Id
)
4134 Set_Body_Needed_For_Inlining
4135 (Defining_Entity
(Unit
(Cunit
(Current_Sem_Unit
))));
4138 Set_Categorization_From_Pragmas
(N
);
4139 Validate_Categorization_Dependency
(N
, Id
);
4141 -- Capture all global references that occur within the profile of the
4142 -- generic subprogram. Aspects are not part of this processing because
4143 -- they must be delayed. If processed now, Save_Global_References will
4144 -- destroy the Associated_Node links and prevent the capture of global
4145 -- references when the contract of the generic subprogram is analyzed.
4147 Save_Global_References
(Original_Node
(N
));
4151 Exit_Generic_Scope
(Id
);
4152 Generate_Reference_To_Formals
(Id
);
4154 List_Inherited_Pre_Post_Aspects
(Id
);
4155 end Analyze_Generic_Subprogram_Declaration
;
4157 -----------------------------------
4158 -- Analyze_Package_Instantiation --
4159 -----------------------------------
4161 -- WARNING: This routine manages Ghost and SPARK regions. Return statements
4162 -- must be replaced by gotos which jump to the end of the routine in order
4163 -- to restore the Ghost and SPARK modes.
4165 procedure Analyze_Package_Instantiation
(N
: Node_Id
) is
4166 Has_Inline_Always
: Boolean := False;
4167 -- Set if the generic unit contains any subprograms with Inline_Always.
4168 -- Only relevant when back-end inlining is not enabled.
4170 function Might_Inline_Subp
(Gen_Unit
: Entity_Id
) return Boolean;
4171 -- Return True if inlining is active and Gen_Unit contains inlined
4172 -- subprograms. In this case, we may either instantiate the body when
4173 -- front-end inlining is enabled, or add a pending instantiation when
4174 -- back-end inlining is enabled. In the former case, this may cause
4175 -- superfluous instantiations, but in either case we need to perform
4176 -- the instantiation of the body in the context of the instance and
4177 -- not in that of the point of inlining.
4179 function Needs_Body_Instantiated
(Gen_Unit
: Entity_Id
) return Boolean;
4180 -- Return True if Gen_Unit needs to have its body instantiated in the
4181 -- context of N. This in particular excludes generic contexts.
4183 -----------------------
4184 -- Might_Inline_Subp --
4185 -----------------------
4187 function Might_Inline_Subp
(Gen_Unit
: Entity_Id
) return Boolean is
4191 if Inline_Processing_Required
then
4192 -- No need to recompute the answer if we know it is positive
4193 -- and back-end inlining is enabled.
4195 if Is_Inlined
(Gen_Unit
) and then Back_End_Inlining
then
4199 E
:= First_Entity
(Gen_Unit
);
4200 while Present
(E
) loop
4201 if Is_Subprogram
(E
) and then Is_Inlined
(E
) then
4202 -- Remember if there are any subprograms with Inline_Always
4204 if Has_Pragma_Inline_Always
(E
) then
4205 Has_Inline_Always
:= True;
4208 Set_Is_Inlined
(Gen_Unit
);
4217 end Might_Inline_Subp
;
4219 -------------------------------
4220 -- Needs_Body_Instantiated --
4221 -------------------------------
4223 function Needs_Body_Instantiated
(Gen_Unit
: Entity_Id
) return Boolean is
4225 -- No need to instantiate bodies in generic units
4227 if Is_Generic_Unit
(Cunit_Entity
(Main_Unit
)) then
4231 -- If the instantiation is in the main unit, then the body is needed
4233 if Is_In_Main_Unit
(N
) then
4237 -- In GNATprove mode, never instantiate bodies outside of the main
4238 -- unit, as it does not use frontend/backend inlining in the way that
4239 -- GNAT does, so does not benefit from such instantiations. On the
4240 -- contrary, such instantiations may bring artificial constraints,
4241 -- as for example such bodies may require preprocessing.
4243 if GNATprove_Mode
then
4247 -- If not, then again no need to instantiate bodies in generic units
4249 if Is_Generic_Unit
(Cunit_Entity
(Get_Code_Unit
(N
))) then
4253 -- Here we have a special handling for back-end inlining: if inline
4254 -- processing is required, then we unconditionally want to have the
4255 -- body instantiated. The reason is that Might_Inline_Subp does not
4256 -- catch all the cases (as it does not recurse into nested packages)
4257 -- so this avoids the need to patch things up afterwards. Moreover,
4258 -- these instantiations are only performed on demand when back-end
4259 -- inlining is enabled, so this causes very little extra work.
4261 if Inline_Processing_Required
and then Back_End_Inlining
then
4265 -- We want to have the bodies instantiated in non-main units if
4266 -- they might contribute inlined subprograms.
4268 return Might_Inline_Subp
(Gen_Unit
);
4269 end Needs_Body_Instantiated
;
4271 -- Local declarations
4273 Gen_Id
: constant Node_Id
:= Name
(N
);
4274 Inst_Id
: constant Entity_Id
:= Defining_Entity
(N
);
4275 Is_Actual_Pack
: constant Boolean := Is_Internal
(Inst_Id
);
4276 Loc
: constant Source_Ptr
:= Sloc
(N
);
4278 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
4279 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
4280 Saved_ISMP
: constant Boolean :=
4281 Ignore_SPARK_Mode_Pragmas_In_Instance
;
4282 Saved_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
4283 Saved_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
4284 -- Save the Ghost and SPARK mode-related data to restore on exit
4286 Saved_Style_Check
: constant Boolean := Style_Check
;
4287 -- Save style check mode for restore on exit
4290 Act_Decl_Name
: Node_Id
;
4291 Act_Decl_Id
: Entity_Id
;
4294 Env_Installed
: Boolean := False;
4297 Gen_Unit
: Entity_Id
;
4298 Inline_Now
: Boolean := False;
4299 Needs_Body
: Boolean;
4300 Parent_Installed
: Boolean := False;
4301 Renaming_List
: List_Id
;
4302 Unit_Renaming
: Node_Id
;
4304 Vis_Prims_List
: Elist_Id
:= No_Elist
;
4305 -- List of primitives made temporarily visible in the instantiation
4306 -- to match the visibility of the formal type
4308 -- Start of processing for Analyze_Package_Instantiation
4311 -- Preserve relevant elaboration-related attributes of the context which
4312 -- are no longer available or very expensive to recompute once analysis,
4313 -- resolution, and expansion are over.
4315 Mark_Elaboration_Attributes
4322 -- Very first thing: check for Text_IO special unit in case we are
4323 -- instantiating one of the children of [[Wide_]Wide_]Text_IO.
4325 Check_Text_IO_Special_Unit
(Name
(N
));
4327 -- Make node global for error reporting
4329 Instantiation_Node
:= N
;
4331 -- Case of instantiation of a generic package
4333 if Nkind
(N
) = N_Package_Instantiation
then
4334 Act_Decl_Id
:= New_Copy
(Defining_Entity
(N
));
4336 if Nkind
(Defining_Unit_Name
(N
)) = N_Defining_Program_Unit_Name
then
4338 Make_Defining_Program_Unit_Name
(Loc
,
4340 New_Copy_Tree
(Name
(Defining_Unit_Name
(N
))),
4341 Defining_Identifier
=> Act_Decl_Id
);
4343 Act_Decl_Name
:= Act_Decl_Id
;
4346 -- Case of instantiation of a formal package
4349 Act_Decl_Id
:= Defining_Identifier
(N
);
4350 Act_Decl_Name
:= Act_Decl_Id
;
4353 Generate_Definition
(Act_Decl_Id
);
4354 Mutate_Ekind
(Act_Decl_Id
, E_Package
);
4355 Set_Is_Not_Self_Hidden
(Act_Decl_Id
);
4357 -- Initialize list of incomplete actuals before analysis
4359 Set_Incomplete_Actuals
(Act_Decl_Id
, New_Elmt_List
);
4361 Preanalyze_Actuals
(N
, Act_Decl_Id
);
4363 -- Turn off style checking in instances. If the check is enabled on the
4364 -- generic unit, a warning in an instance would just be noise. If not
4365 -- enabled on the generic, then a warning in an instance is just wrong.
4366 -- This must be done after analyzing the actuals, which do come from
4367 -- source and are subject to style checking.
4369 Style_Check
:= False;
4372 Env_Installed
:= True;
4374 -- Reset renaming map for formal types. The mapping is established
4375 -- when analyzing the generic associations, but some mappings are
4376 -- inherited from formal packages of parent units, and these are
4377 -- constructed when the parents are installed.
4379 Generic_Renamings
.Set_Last
(0);
4380 Generic_Renamings_HTable
.Reset
;
4382 -- Except for an abbreviated instance created to check a formal package,
4383 -- install the parent if this is a generic child unit.
4385 if not Is_Abbreviated_Instance
(Inst_Id
) then
4386 Check_Generic_Child_Unit
(Gen_Id
, Parent_Installed
);
4389 Gen_Unit
:= Entity
(Gen_Id
);
4391 -- A package instantiation is Ghost when it is subject to pragma Ghost
4392 -- or the generic template is Ghost. Set the mode now to ensure that
4393 -- any nodes generated during analysis and expansion are marked as
4396 Mark_And_Set_Ghost_Instantiation
(N
, Gen_Unit
);
4398 -- Verify that it is the name of a generic package
4400 -- A visibility glitch: if the instance is a child unit and the generic
4401 -- is the generic unit of a parent instance (i.e. both the parent and
4402 -- the child units are instances of the same package) the name now
4403 -- denotes the renaming within the parent, not the intended generic
4404 -- unit. See if there is a homonym that is the desired generic. The
4405 -- renaming declaration must be visible inside the instance of the
4406 -- child, but not when analyzing the name in the instantiation itself.
4408 if Ekind
(Gen_Unit
) = E_Package
4409 and then Present
(Renamed_Entity
(Gen_Unit
))
4410 and then In_Open_Scopes
(Renamed_Entity
(Gen_Unit
))
4411 and then Is_Generic_Instance
(Renamed_Entity
(Gen_Unit
))
4412 and then Present
(Homonym
(Gen_Unit
))
4414 Gen_Unit
:= Homonym
(Gen_Unit
);
4417 if Etype
(Gen_Unit
) = Any_Type
then
4421 elsif Ekind
(Gen_Unit
) /= E_Generic_Package
then
4423 -- Ada 2005 (AI-50217): Cannot use instance in limited with_clause
4425 if From_Limited_With
(Gen_Unit
) then
4427 ("cannot instantiate a limited withed package", Gen_Id
);
4430 ("& is not the name of a generic package", Gen_Id
, Gen_Unit
);
4437 if In_Extended_Main_Source_Unit
(N
) then
4438 Set_Is_Instantiated
(Gen_Unit
);
4439 Generate_Reference
(Gen_Unit
, N
);
4441 if Present
(Renamed_Entity
(Gen_Unit
)) then
4442 Set_Is_Instantiated
(Renamed_Entity
(Gen_Unit
));
4443 Generate_Reference
(Renamed_Entity
(Gen_Unit
), N
);
4447 if Nkind
(Gen_Id
) = N_Identifier
4448 and then Chars
(Gen_Unit
) = Chars
(Defining_Entity
(N
))
4451 ("& is hidden within declaration of instance", Gen_Id
, Gen_Unit
);
4453 elsif Nkind
(Gen_Id
) = N_Expanded_Name
4454 and then Is_Child_Unit
(Gen_Unit
)
4455 and then Nkind
(Prefix
(Gen_Id
)) = N_Identifier
4456 and then Chars
(Act_Decl_Id
) = Chars
(Prefix
(Gen_Id
))
4459 ("& is hidden within declaration of instance", Prefix
(Gen_Id
));
4462 Set_Entity
(Gen_Id
, Gen_Unit
);
4464 -- If generic is a renaming, get original generic unit
4466 if Present
(Renamed_Entity
(Gen_Unit
))
4467 and then Ekind
(Renamed_Entity
(Gen_Unit
)) = E_Generic_Package
4469 Gen_Unit
:= Renamed_Entity
(Gen_Unit
);
4472 -- Verify that there are no circular instantiations
4474 if In_Open_Scopes
(Gen_Unit
) then
4475 Error_Msg_NE
("instantiation of & within itself", N
, Gen_Unit
);
4479 elsif Contains_Instance_Of
(Gen_Unit
, Current_Scope
, Gen_Id
) then
4480 Error_Msg_Node_2
:= Current_Scope
;
4482 ("circular instantiation: & instantiated in &!", N
, Gen_Unit
);
4483 Circularity_Detected
:= True;
4488 Mutate_Ekind
(Inst_Id
, E_Package
);
4489 Set_Scope
(Inst_Id
, Current_Scope
);
4491 -- If the context of the instance is subject to SPARK_Mode "off" or
4492 -- the annotation is altogether missing, set the global flag which
4493 -- signals Analyze_Pragma to ignore all SPARK_Mode pragmas within
4496 if SPARK_Mode
/= On
then
4497 Ignore_SPARK_Mode_Pragmas_In_Instance
:= True;
4499 -- Mark the instance spec in case the body is instantiated at a
4500 -- later pass. This preserves the original context in effect for
4503 Set_Ignore_SPARK_Mode_Pragmas
(Act_Decl_Id
);
4506 Gen_Decl
:= Unit_Declaration_Node
(Gen_Unit
);
4507 Gen_Spec
:= Specification
(Gen_Decl
);
4509 -- Initialize renamings map, for error checking, and the list that
4510 -- holds private entities whose views have changed between generic
4511 -- definition and instantiation. If this is the instance created to
4512 -- validate an actual package, the instantiation environment is that
4513 -- of the enclosing instance.
4515 Create_Instantiation_Source
(N
, Gen_Unit
, S_Adjustment
);
4517 -- Copy original generic tree, to produce text for instantiation
4521 (Original_Node
(Gen_Decl
), Empty
, Instantiating
=> True);
4523 Act_Spec
:= Specification
(Act_Tree
);
4525 -- If this is the instance created to validate an actual package,
4526 -- only the formals matter, do not examine the package spec itself.
4528 if Is_Actual_Pack
then
4529 Set_Visible_Declarations
(Act_Spec
, New_List
);
4530 Set_Private_Declarations
(Act_Spec
, New_List
);
4534 Analyze_Associations
4536 Formals
=> Generic_Formal_Declarations
(Act_Tree
),
4537 F_Copy
=> Generic_Formal_Declarations
(Gen_Decl
));
4539 Vis_Prims_List
:= Check_Hidden_Primitives
(Renaming_List
);
4541 Set_Instance_Env
(Gen_Unit
, Act_Decl_Id
);
4542 Set_Defining_Unit_Name
(Act_Spec
, Act_Decl_Name
);
4543 Set_Is_Generic_Instance
(Act_Decl_Id
);
4544 Set_Generic_Parent
(Act_Spec
, Gen_Unit
);
4546 -- References to the generic in its own declaration or its body are
4547 -- references to the instance. Add a renaming declaration for the
4548 -- generic unit itself. This declaration, as well as the renaming
4549 -- declarations for the generic formals, must remain private to the
4550 -- unit: the formals, because this is the language semantics, and
4551 -- the unit because its use is an artifact of the implementation.
4554 Make_Package_Renaming_Declaration
(Loc
,
4555 Defining_Unit_Name
=>
4556 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
)),
4557 Name
=> New_Occurrence_Of
(Act_Decl_Id
, Loc
));
4559 Append
(Unit_Renaming
, Renaming_List
);
4561 -- The renaming declarations are the first local declarations of the
4564 if Is_Non_Empty_List
(Visible_Declarations
(Act_Spec
)) then
4566 (First
(Visible_Declarations
(Act_Spec
)), Renaming_List
);
4568 Set_Visible_Declarations
(Act_Spec
, Renaming_List
);
4571 Act_Decl
:= Make_Package_Declaration
(Loc
, Specification
=> Act_Spec
);
4573 -- Propagate the aspect specifications from the package declaration
4574 -- template to the instantiated version of the package declaration.
4576 if Has_Aspects
(Act_Tree
) then
4577 Set_Aspect_Specifications
(Act_Decl
,
4578 New_Copy_List_Tree
(Aspect_Specifications
(Act_Tree
)));
4581 -- The generic may have a generated Default_Storage_Pool aspect,
4582 -- set at the point of generic declaration. If the instance has
4583 -- that aspect, it overrides the one inherited from the generic.
4585 if Has_Aspects
(Gen_Spec
) then
4586 if No
(Aspect_Specifications
(N
)) then
4587 Set_Aspect_Specifications
(N
,
4589 (Aspect_Specifications
(Gen_Spec
))));
4593 Inherited_Aspects
: constant List_Id
:=
4595 (Aspect_Specifications
(Gen_Spec
));
4599 Pool_Present
: Boolean := False;
4602 ASN1
:= First
(Aspect_Specifications
(N
));
4603 while Present
(ASN1
) loop
4604 if Chars
(Identifier
(ASN1
)) =
4605 Name_Default_Storage_Pool
4607 Pool_Present
:= True;
4614 if Pool_Present
then
4616 -- If generic carries a default storage pool, remove it
4617 -- in favor of the instance one.
4619 ASN2
:= First
(Inherited_Aspects
);
4620 while Present
(ASN2
) loop
4621 if Chars
(Identifier
(ASN2
)) =
4622 Name_Default_Storage_Pool
4633 (Aspect_Specifications
(N
), Inherited_Aspects
);
4638 -- Save the instantiation node for a subsequent instantiation of the
4639 -- body if there is one and it needs to be instantiated here.
4641 -- We instantiate the body only if we are generating code, or if we
4642 -- are generating cross-reference information, or for GNATprove use.
4645 Enclosing_Body_Present
: Boolean := False;
4646 -- If the generic unit is not a compilation unit, then a body may
4647 -- be present in its parent even if none is required. We create a
4648 -- tentative pending instantiation for the body, which will be
4649 -- discarded if none is actually present.
4654 if Scope
(Gen_Unit
) /= Standard_Standard
4655 and then not Is_Child_Unit
(Gen_Unit
)
4657 Scop
:= Scope
(Gen_Unit
);
4658 while Present
(Scop
) and then Scop
/= Standard_Standard
loop
4659 if Unit_Requires_Body
(Scop
) then
4660 Enclosing_Body_Present
:= True;
4663 elsif In_Open_Scopes
(Scop
)
4664 and then In_Package_Body
(Scop
)
4666 Enclosing_Body_Present
:= True;
4670 exit when Is_Compilation_Unit
(Scop
);
4671 Scop
:= Scope
(Scop
);
4675 -- If front-end inlining is enabled or there are any subprograms
4676 -- marked with Inline_Always, and this is a unit for which code
4677 -- will be generated, we instantiate the body at once.
4679 -- This is done if the instance is not the main unit, and if the
4680 -- generic is not a child unit of another generic, to avoid scope
4681 -- problems and the reinstallation of parent instances.
4684 and then (not Is_Child_Unit
(Gen_Unit
)
4685 or else not Is_Generic_Unit
(Scope
(Gen_Unit
)))
4686 and then Might_Inline_Subp
(Gen_Unit
)
4687 and then not Is_Actual_Pack
4689 if not Back_End_Inlining
4690 and then (Front_End_Inlining
or else Has_Inline_Always
)
4691 and then (Is_In_Main_Unit
(N
)
4692 or else In_Main_Context
(Current_Scope
))
4693 and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
4697 -- In configurable_run_time mode we force the inlining of
4698 -- predefined subprograms marked Inline_Always, to minimize
4699 -- the use of the run-time library.
4701 elsif In_Predefined_Unit
(Gen_Decl
)
4702 and then Configurable_Run_Time_Mode
4703 and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
4708 -- If the current scope is itself an instance within a child
4709 -- unit, there will be duplications in the scope stack, and the
4710 -- unstacking mechanism in Inline_Instance_Body will fail.
4711 -- This loses some rare cases of optimization.
4713 if Is_Generic_Instance
(Current_Scope
) then
4715 Curr_Unit
: constant Entity_Id
:=
4716 Cunit_Entity
(Current_Sem_Unit
);
4718 if Curr_Unit
/= Current_Scope
4719 and then Is_Child_Unit
(Curr_Unit
)
4721 Inline_Now
:= False;
4728 (Unit_Requires_Body
(Gen_Unit
)
4729 or else Enclosing_Body_Present
4730 or else Present
(Corresponding_Body
(Gen_Decl
)))
4731 and then Needs_Body_Instantiated
(Gen_Unit
)
4732 and then not Is_Actual_Pack
4733 and then not Inline_Now
4734 and then (Operating_Mode
= Generate_Code
4735 or else (Operating_Mode
= Check_Semantics
4736 and then GNATprove_Mode
));
4738 -- If front-end inlining is enabled or there are any subprograms
4739 -- marked with Inline_Always, do not instantiate body when within
4740 -- a generic context.
4742 if not Back_End_Inlining
4743 and then (Front_End_Inlining
or else Has_Inline_Always
)
4744 and then not Expander_Active
4746 Needs_Body
:= False;
4749 -- If the current context is generic, and the package being
4750 -- instantiated is declared within a formal package, there is no
4751 -- body to instantiate until the enclosing generic is instantiated
4752 -- and there is an actual for the formal package. If the formal
4753 -- package has parameters, we build a regular package instance for
4754 -- it, that precedes the original formal package declaration.
4756 if In_Open_Scopes
(Scope
(Scope
(Gen_Unit
))) then
4758 Decl
: constant Node_Id
:=
4760 (Unit_Declaration_Node
(Scope
(Gen_Unit
)));
4762 if Nkind
(Decl
) = N_Formal_Package_Declaration
4763 or else (Nkind
(Decl
) = N_Package_Declaration
4764 and then Is_List_Member
(Decl
)
4765 and then Present
(Next
(Decl
))
4767 Nkind
(Next
(Decl
)) =
4768 N_Formal_Package_Declaration
)
4770 Needs_Body
:= False;
4776 -- For RCI unit calling stubs, we omit the instance body if the
4777 -- instance is the RCI library unit itself.
4779 -- However there is a special case for nested instances: in this case
4780 -- we do generate the instance body, as it might be required, e.g.
4781 -- because it provides stream attributes for some type used in the
4782 -- profile of a remote subprogram. This is consistent with 12.3(12),
4783 -- which indicates that the instance body occurs at the place of the
4784 -- instantiation, and thus is part of the RCI declaration, which is
4785 -- present on all client partitions (this is E.2.3(18)).
4787 -- Note that AI12-0002 may make it illegal at some point to have
4788 -- stream attributes defined in an RCI unit, in which case this
4789 -- special case will become unnecessary. In the meantime, there
4790 -- is known application code in production that depends on this
4791 -- being possible, so we definitely cannot eliminate the body in
4792 -- the case of nested instances for the time being.
4794 -- When we generate a nested instance body, calling stubs for any
4795 -- relevant subprogram will be inserted immediately after the
4796 -- subprogram declarations, and will take precedence over the
4797 -- subsequent (original) body. (The stub and original body will be
4798 -- complete homographs, but this is permitted in an instance).
4799 -- (Could we do better and remove the original body???)
4801 if Distribution_Stub_Mode
= Generate_Caller_Stub_Body
4802 and then Comes_From_Source
(N
)
4803 and then Nkind
(Parent
(N
)) = N_Compilation_Unit
4805 Needs_Body
:= False;
4808 -- If the context requires a full instantiation, set things up for
4809 -- subsequent construction of the body.
4813 Fin_Scop
, S
: Entity_Id
;
4816 Check_Forward_Instantiation
(Gen_Decl
);
4820 -- For a package instantiation that is not a compilation unit,
4821 -- indicate that cleanup actions of the innermost enclosing
4822 -- scope for which they are generated should be delayed until
4823 -- after the package body is instantiated.
4825 if Nkind
(N
) = N_Package_Instantiation
4826 and then not Is_Compilation_Unit
(Act_Decl_Id
)
4830 while S
/= Standard_Standard
loop
4831 -- Cleanup actions are not generated within generic units
4832 -- or in the formal part of generic units.
4835 or else Is_Generic_Unit
(S
)
4836 or else Ekind
(S
) = E_Void
4840 -- For package scopes, cleanup actions are generated only
4841 -- for compilation units, for spec and body separately.
4843 elsif Ekind
(S
) = E_Package
then
4844 if Is_Compilation_Unit
(S
) then
4845 if In_Package_Body
(S
) then
4846 Fin_Scop
:= Body_Entity
(S
);
4851 Set_Delay_Cleanups
(Fin_Scop
);
4858 -- Cleanup actions are generated for all dynamic scopes
4862 Set_Delay_Cleanups
(Fin_Scop
);
4868 Add_Pending_Instantiation
(N
, Act_Decl
, Fin_Scop
);
4872 Set_Categorization_From_Pragmas
(Act_Decl
);
4874 if Parent_Installed
then
4878 Set_Instance_Spec
(N
, Act_Decl
);
4880 -- If not a compilation unit, insert the package declaration before
4881 -- the original instantiation node.
4883 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
4884 Mark_Rewrite_Insertion
(Act_Decl
);
4885 Insert_Before
(N
, Act_Decl
);
4887 if Has_Aspects
(N
) then
4888 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
4890 -- The pragma created for a Default_Storage_Pool aspect must
4891 -- appear ahead of the declarations in the instance spec.
4892 -- Analysis has placed it after the instance node, so remove
4893 -- it and reinsert it properly now.
4896 ASN
: constant Node_Id
:= First
(Aspect_Specifications
(N
));
4897 A_Name
: constant Name_Id
:= Chars
(Identifier
(ASN
));
4901 if A_Name
= Name_Default_Storage_Pool
then
4902 if No
(Visible_Declarations
(Act_Spec
)) then
4903 Set_Visible_Declarations
(Act_Spec
, New_List
);
4907 while Present
(Decl
) loop
4908 if Nkind
(Decl
) = N_Pragma
then
4910 Prepend
(Decl
, Visible_Declarations
(Act_Spec
));
4922 -- For an instantiation that is a compilation unit, place
4923 -- declaration on current node so context is complete for analysis
4924 -- (including nested instantiations). If this is the main unit,
4925 -- the declaration eventually replaces the instantiation node.
4926 -- If the instance body is created later, it replaces the
4927 -- instance node, and the declaration is attached to it
4928 -- (see Build_Instance_Compilation_Unit_Nodes).
4931 if Cunit_Entity
(Current_Sem_Unit
) = Defining_Entity
(N
) then
4933 -- The entity for the current unit is the newly created one,
4934 -- and all semantic information is attached to it.
4936 Set_Cunit_Entity
(Current_Sem_Unit
, Act_Decl_Id
);
4938 -- If this is the main unit, replace the main entity as well
4940 if Current_Sem_Unit
= Main_Unit
then
4941 Main_Unit_Entity
:= Act_Decl_Id
;
4945 Set_Unit
(Parent
(N
), Act_Decl
);
4946 Set_Parent_Spec
(Act_Decl
, Parent_Spec
(N
));
4947 Set_Package_Instantiation
(Act_Decl_Id
, N
);
4949 -- Process aspect specifications of the instance node, if any, to
4950 -- take into account categorization pragmas before analyzing the
4953 if Has_Aspects
(N
) then
4954 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
4958 Set_Unit
(Parent
(N
), N
);
4959 Set_Body_Required
(Parent
(N
), False);
4961 -- We never need elaboration checks on instantiations, since by
4962 -- definition, the body instantiation is elaborated at the same
4963 -- time as the spec instantiation.
4965 if Legacy_Elaboration_Checks
then
4966 Set_Kill_Elaboration_Checks
(Act_Decl_Id
);
4967 Set_Suppress_Elaboration_Warnings
(Act_Decl_Id
);
4971 if Legacy_Elaboration_Checks
then
4972 Check_Elab_Instantiation
(N
);
4975 -- Save the scenario for later examination by the ABE Processing
4978 Record_Elaboration_Scenario
(N
);
4980 -- The instantiation results in a guaranteed ABE
4982 if Is_Known_Guaranteed_ABE
(N
) and then Needs_Body
then
4983 -- Do not instantiate the corresponding body because gigi cannot
4984 -- handle certain types of premature instantiations.
4986 Remove_Dead_Instance
(N
);
4988 -- Create completing bodies for all subprogram declarations since
4989 -- their real bodies will not be instantiated.
4991 Provide_Completing_Bodies
(Instance_Spec
(N
));
4994 Check_Hidden_Child_Unit
(N
, Gen_Unit
, Act_Decl_Id
);
4996 Set_First_Private_Entity
(Defining_Unit_Name
(Unit_Renaming
),
4997 First_Private_Entity
(Act_Decl_Id
));
4999 -- If the instantiation needs a body, the unit will be turned into
5000 -- a package body and receive its own elaboration entity. Otherwise,
5001 -- the nature of the unit is now a package declaration.
5003 -- Note that the below rewriting means that Act_Decl, which has been
5004 -- analyzed and expanded, will be re-expanded as the rewritten N.
5006 if Nkind
(Parent
(N
)) = N_Compilation_Unit
5007 and then not Needs_Body
5009 Rewrite
(N
, Act_Decl
);
5012 if Present
(Corresponding_Body
(Gen_Decl
))
5013 or else Unit_Requires_Body
(Gen_Unit
)
5015 Set_Has_Completion
(Act_Decl_Id
);
5018 Check_Formal_Packages
(Act_Decl_Id
);
5020 Restore_Hidden_Primitives
(Vis_Prims_List
);
5021 Restore_Private_Views
(Act_Decl_Id
);
5023 Inherit_Context
(Gen_Decl
, N
);
5025 if Parent_Installed
then
5030 Env_Installed
:= False;
5033 Validate_Categorization_Dependency
(N
, Act_Decl_Id
);
5035 -- There used to be a check here to prevent instantiations in local
5036 -- contexts if the No_Local_Allocators restriction was active. This
5037 -- check was removed by a binding interpretation in AI-95-00130/07,
5038 -- but we retain the code for documentation purposes.
5040 -- if Ekind (Act_Decl_Id) /= E_Void
5041 -- and then not Is_Library_Level_Entity (Act_Decl_Id)
5043 -- Check_Restriction (No_Local_Allocators, N);
5047 Inline_Instance_Body
(N
, Gen_Unit
, Act_Decl
);
5050 -- Check that if N is an instantiation of System.Dim_Float_IO or
5051 -- System.Dim_Integer_IO, the formal type has a dimension system.
5053 if Nkind
(N
) = N_Package_Instantiation
5054 and then Is_Dim_IO_Package_Instantiation
(N
)
5057 Assoc
: constant Node_Id
:= First
(Generic_Associations
(N
));
5059 if not Has_Dimension_System
5060 (Etype
(Explicit_Generic_Actual_Parameter
(Assoc
)))
5062 Error_Msg_N
("type with a dimension system expected", Assoc
);
5068 if Has_Aspects
(N
) and then Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
5069 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
5072 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Saved_ISMP
;
5073 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
5074 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
5075 Style_Check
:= Saved_Style_Check
;
5078 when Instantiation_Error
=>
5079 if Parent_Installed
then
5083 if Env_Installed
then
5087 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Saved_ISMP
;
5088 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
5089 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
5090 Style_Check
:= Saved_Style_Check
;
5091 end Analyze_Package_Instantiation
;
5093 --------------------------
5094 -- Inline_Instance_Body --
5095 --------------------------
5097 -- WARNING: This routine manages SPARK regions. Return statements must be
5098 -- replaced by gotos which jump to the end of the routine and restore the
5101 procedure Inline_Instance_Body
5103 Gen_Unit
: Entity_Id
;
5106 Config_Attrs
: constant Config_Switches_Type
:= Save_Config_Switches
;
5108 Curr_Comp
: constant Node_Id
:= Cunit
(Current_Sem_Unit
);
5109 Curr_Unit
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
5110 Gen_Comp
: constant Entity_Id
:=
5111 Cunit_Entity
(Get_Source_Unit
(Gen_Unit
));
5113 Scope_Stack_Depth
: constant Pos
:=
5114 Scope_Stack
.Last
- Scope_Stack
.First
+ 1;
5116 Inner_Scopes
: array (1 .. Scope_Stack_Depth
) of Entity_Id
;
5117 Instances
: array (1 .. Scope_Stack_Depth
) of Entity_Id
;
5118 Use_Clauses
: array (1 .. Scope_Stack_Depth
) of Node_Id
;
5120 Curr_Scope
: Entity_Id
:= Empty
;
5121 List
: Elist_Id
:= No_Elist
; -- init to avoid warning
5122 N_Instances
: Nat
:= 0;
5123 Num_Inner
: Nat
:= 0;
5124 Num_Scopes
: Nat
:= 0;
5125 Removed
: Boolean := False;
5130 -- Case of generic unit defined in another unit. We must remove the
5131 -- complete context of the current unit to install that of the generic.
5133 if Gen_Comp
/= Cunit_Entity
(Current_Sem_Unit
) then
5135 -- Loop through enclosing scopes until we reach a generic instance,
5136 -- package body, or subprogram.
5139 while Present
(S
) and then S
/= Standard_Standard
loop
5141 -- Save use clauses from enclosing scopes into Use_Clauses
5144 Num_Scopes
:= Num_Scopes
+ 1;
5146 Use_Clauses
(Num_Scopes
) :=
5148 (Scope_Stack
.Last
- Num_Scopes
+ 1).First_Use_Clause
);
5149 End_Use_Clauses
(Use_Clauses
(Num_Scopes
));
5151 exit when Scope_Stack
.Last
- Num_Scopes
+ 1 = Scope_Stack
.First
5152 or else Scope_Stack
.Table
5153 (Scope_Stack
.Last
- Num_Scopes
).Entity
= Scope
(S
);
5156 exit when Is_Generic_Instance
(S
)
5157 and then (In_Package_Body
(S
)
5158 or else Ekind
(S
) = E_Procedure
5159 or else Ekind
(S
) = E_Function
);
5163 Vis
:= Is_Immediately_Visible
(Gen_Comp
);
5165 -- Find and save all enclosing instances
5170 and then S
/= Standard_Standard
5172 if Is_Generic_Instance
(S
) then
5173 N_Instances
:= N_Instances
+ 1;
5174 Instances
(N_Instances
) := S
;
5176 exit when In_Package_Body
(S
);
5182 -- Remove context of current compilation unit, unless we are within a
5183 -- nested package instantiation, in which case the context has been
5184 -- removed previously.
5186 -- If current scope is the body of a child unit, remove context of
5187 -- spec as well. If an enclosing scope is an instance body, the
5188 -- context has already been removed, but the entities in the body
5189 -- must be made invisible as well.
5192 while Present
(S
) and then S
/= Standard_Standard
loop
5193 if Is_Generic_Instance
(S
)
5194 and then (In_Package_Body
(S
)
5195 or else Ekind
(S
) in E_Procedure | E_Function
)
5197 -- We still have to remove the entities of the enclosing
5198 -- instance from direct visibility.
5203 E
:= First_Entity
(S
);
5204 while Present
(E
) loop
5205 Set_Is_Immediately_Visible
(E
, False);
5214 or else (Ekind
(Curr_Unit
) = E_Package_Body
5215 and then S
= Spec_Entity
(Curr_Unit
))
5216 or else (Ekind
(Curr_Unit
) = E_Subprogram_Body
5217 and then S
= Corresponding_Spec
5218 (Unit_Declaration_Node
(Curr_Unit
)))
5222 -- Remove entities in current scopes from visibility, so that
5223 -- instance body is compiled in a clean environment.
5225 List
:= Save_Scope_Stack
(Handle_Use
=> False);
5227 if Is_Child_Unit
(S
) then
5229 -- Remove child unit from stack, as well as inner scopes.
5230 -- Removing the context of a child unit removes parent units
5233 while Current_Scope
/= S
loop
5234 Num_Inner
:= Num_Inner
+ 1;
5235 Inner_Scopes
(Num_Inner
) := Current_Scope
;
5240 Remove_Context
(Curr_Comp
);
5244 Remove_Context
(Curr_Comp
);
5247 if Ekind
(Curr_Unit
) = E_Package_Body
then
5248 Remove_Context
(Library_Unit
(Curr_Comp
));
5255 pragma Assert
(Num_Inner
< Num_Scopes
);
5257 Push_Scope
(Standard_Standard
);
5258 Scope_Stack
.Table
(Scope_Stack
.Last
).Is_Active_Stack_Base
:= True;
5260 -- The inlined package body is analyzed with the configuration state
5261 -- of the context prior to the scope manipulations performed above.
5263 -- ??? shouldn't this also use the warning state of the context prior
5264 -- to the scope manipulations?
5266 Instantiate_Package_Body
5269 Act_Decl
=> Act_Decl
,
5271 Config_Switches
=> Config_Attrs
,
5272 Current_Sem_Unit
=> Current_Sem_Unit
,
5273 Expander_Status
=> Expander_Active
,
5274 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
5275 Scope_Suppress
=> Scope_Suppress
,
5276 Warnings
=> Save_Warnings
)),
5277 Inlined_Body
=> True);
5283 Set_Is_Immediately_Visible
(Gen_Comp
, Vis
);
5285 -- Reset Generic_Instance flag so that use clauses can be installed
5286 -- in the proper order. (See Use_One_Package for effect of enclosing
5287 -- instances on processing of use clauses).
5289 for J
in 1 .. N_Instances
loop
5290 Set_Is_Generic_Instance
(Instances
(J
), False);
5294 Install_Context
(Curr_Comp
, Chain
=> False);
5296 if Present
(Curr_Scope
)
5297 and then Is_Child_Unit
(Curr_Scope
)
5299 Push_Scope
(Curr_Scope
);
5300 Set_Is_Immediately_Visible
(Curr_Scope
);
5302 -- Finally, restore inner scopes as well
5304 for J
in reverse 1 .. Num_Inner
loop
5305 Push_Scope
(Inner_Scopes
(J
));
5309 Restore_Scope_Stack
(List
, Handle_Use
=> False);
5311 if Present
(Curr_Scope
)
5313 (In_Private_Part
(Curr_Scope
)
5314 or else In_Package_Body
(Curr_Scope
))
5316 -- Install private declaration of ancestor units, which are
5317 -- currently available. Restore_Scope_Stack and Install_Context
5318 -- only install the visible part of parents.
5323 Par
:= Scope
(Curr_Scope
);
5324 while Present
(Par
) and then Par
/= Standard_Standard
loop
5325 Install_Private_Declarations
(Par
);
5332 -- Restore use clauses. For a child unit, use clauses in the parents
5333 -- are restored when installing the context, so only those in inner
5334 -- scopes (and those local to the child unit itself) need to be
5335 -- installed explicitly.
5337 if Is_Child_Unit
(Curr_Unit
) and then Removed
then
5338 for J
in reverse 1 .. Num_Inner
+ 1 loop
5339 Scope_Stack
.Table
(Scope_Stack
.Last
- J
+ 1).First_Use_Clause
:=
5341 Install_Use_Clauses
(Use_Clauses
(J
));
5345 for J
in reverse 1 .. Num_Scopes
loop
5346 Scope_Stack
.Table
(Scope_Stack
.Last
- J
+ 1).First_Use_Clause
:=
5348 Install_Use_Clauses
(Use_Clauses
(J
));
5352 -- Restore status of instances. If one of them is a body, make its
5353 -- local entities visible again.
5360 for J
in 1 .. N_Instances
loop
5361 Inst
:= Instances
(J
);
5362 Set_Is_Generic_Instance
(Inst
, True);
5364 if In_Package_Body
(Inst
)
5365 or else Ekind
(S
) in E_Procedure | E_Function
5367 E
:= First_Entity
(Instances
(J
));
5368 while Present
(E
) loop
5369 Set_Is_Immediately_Visible
(E
);
5376 -- If generic unit is in current unit, current context is correct. Note
5377 -- that the context is guaranteed to carry the correct SPARK_Mode as no
5378 -- enclosing scopes were removed.
5381 Instantiate_Package_Body
5384 Act_Decl
=> Act_Decl
,
5386 Config_Switches
=> Save_Config_Switches
,
5387 Current_Sem_Unit
=> Current_Sem_Unit
,
5388 Expander_Status
=> Expander_Active
,
5389 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
5390 Scope_Suppress
=> Scope_Suppress
,
5391 Warnings
=> Save_Warnings
)),
5392 Inlined_Body
=> True);
5394 end Inline_Instance_Body
;
5396 -------------------------------------
5397 -- Analyze_Procedure_Instantiation --
5398 -------------------------------------
5400 procedure Analyze_Procedure_Instantiation
(N
: Node_Id
) is
5402 Analyze_Subprogram_Instantiation
(N
, E_Procedure
);
5403 end Analyze_Procedure_Instantiation
;
5405 -----------------------------------
5406 -- Need_Subprogram_Instance_Body --
5407 -----------------------------------
5409 function Need_Subprogram_Instance_Body
5411 Subp
: Entity_Id
) return Boolean
5413 function Is_Inlined_Or_Child_Of_Inlined
(E
: Entity_Id
) return Boolean;
5414 -- Return True if E is an inlined subprogram, an inlined renaming or a
5415 -- subprogram nested in an inlined subprogram. The inlining machinery
5416 -- totally disregards nested subprograms since it considers that they
5417 -- will always be compiled if the parent is (see Inline.Is_Nested).
5419 ------------------------------------
5420 -- Is_Inlined_Or_Child_Of_Inlined --
5421 ------------------------------------
5423 function Is_Inlined_Or_Child_Of_Inlined
(E
: Entity_Id
) return Boolean is
5427 if Is_Inlined
(E
) or else Is_Inlined
(Alias
(E
)) then
5432 while Scop
/= Standard_Standard
loop
5433 if Is_Subprogram
(Scop
) and then Is_Inlined
(Scop
) then
5437 Scop
:= Scope
(Scop
);
5441 end Is_Inlined_Or_Child_Of_Inlined
;
5444 -- Must be in the main unit or inlined (or child of inlined)
5446 if (Is_In_Main_Unit
(N
) or else Is_Inlined_Or_Child_Of_Inlined
(Subp
))
5448 -- Must be generating code or analyzing code in GNATprove mode
5450 and then (Operating_Mode
= Generate_Code
5451 or else (Operating_Mode
= Check_Semantics
5452 and then GNATprove_Mode
))
5454 -- The body is needed when generating code (full expansion) and in
5455 -- in GNATprove mode (special expansion) for formal verification of
5458 and then (Expander_Active
or GNATprove_Mode
)
5460 -- No point in inlining if ABE is inevitable
5462 and then not Is_Known_Guaranteed_ABE
(N
)
5464 -- Or if subprogram is eliminated
5466 and then not Is_Eliminated
(Subp
)
5468 Add_Pending_Instantiation
(N
, Unit_Declaration_Node
(Subp
));
5471 -- Here if not inlined, or we ignore the inlining
5476 end Need_Subprogram_Instance_Body
;
5478 --------------------------------------
5479 -- Analyze_Subprogram_Instantiation --
5480 --------------------------------------
5482 -- WARNING: This routine manages Ghost and SPARK regions. Return statements
5483 -- must be replaced by gotos which jump to the end of the routine in order
5484 -- to restore the Ghost and SPARK modes.
5486 procedure Analyze_Subprogram_Instantiation
5490 Errs
: constant Nat
:= Serious_Errors_Detected
;
5491 Gen_Id
: constant Node_Id
:= Name
(N
);
5492 Inst_Id
: constant Entity_Id
:= Defining_Entity
(N
);
5493 Anon_Id
: constant Entity_Id
:=
5494 Make_Defining_Identifier
(Sloc
(Inst_Id
),
5495 Chars
=> New_External_Name
(Chars
(Inst_Id
), 'R'));
5496 Loc
: constant Source_Ptr
:= Sloc
(N
);
5498 Act_Decl_Id
: Entity_Id
:= Empty
; -- init to avoid warning
5503 Env_Installed
: Boolean := False;
5504 Gen_Unit
: Entity_Id
;
5506 Pack_Id
: Entity_Id
;
5507 Parent_Installed
: Boolean := False;
5509 Renaming_List
: List_Id
;
5510 -- The list of declarations that link formals and actuals of the
5511 -- instance. These are subtype declarations for formal types, and
5512 -- renaming declarations for other formals. The subprogram declaration
5513 -- for the instance is then appended to the list, and the last item on
5514 -- the list is the renaming declaration for the instance.
5516 procedure Analyze_Instance_And_Renamings
;
5517 -- The instance must be analyzed in a context that includes the mappings
5518 -- of generic parameters into actuals. We create a package declaration
5519 -- for this purpose, and a subprogram with an internal name within the
5520 -- package. The subprogram instance is simply an alias for the internal
5521 -- subprogram, declared in the current scope.
5523 procedure Build_Subprogram_Renaming
;
5524 -- If the subprogram is recursive, there are occurrences of the name of
5525 -- the generic within the body, which must resolve to the current
5526 -- instance. We add a renaming declaration after the declaration, which
5527 -- is available in the instance body, as well as in the analysis of
5528 -- aspects that appear in the generic. This renaming declaration is
5529 -- inserted after the instance declaration which it renames.
5531 ------------------------------------
5532 -- Analyze_Instance_And_Renamings --
5533 ------------------------------------
5535 procedure Analyze_Instance_And_Renamings
is
5536 Def_Ent
: constant Entity_Id
:= Defining_Entity
(N
);
5537 Pack_Decl
: Node_Id
;
5540 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
5542 -- For the case of a compilation unit, the container package has
5543 -- the same name as the instantiation, to insure that the binder
5544 -- calls the elaboration procedure with the right name. Copy the
5545 -- entity of the instance, which may have compilation level flags
5546 -- (e.g. Is_Child_Unit) set.
5548 Pack_Id
:= New_Copy
(Def_Ent
);
5551 -- Otherwise we use the name of the instantiation concatenated
5552 -- with its source position to ensure uniqueness if there are
5553 -- several instantiations with the same name.
5556 Make_Defining_Identifier
(Loc
,
5557 Chars
=> New_External_Name
5558 (Related_Id
=> Chars
(Def_Ent
),
5560 Suffix_Index
=> Source_Offset
(Sloc
(Def_Ent
))));
5564 Make_Package_Declaration
(Loc
,
5565 Specification
=> Make_Package_Specification
(Loc
,
5566 Defining_Unit_Name
=> Pack_Id
,
5567 Visible_Declarations
=> Renaming_List
,
5568 End_Label
=> Empty
));
5570 Set_Instance_Spec
(N
, Pack_Decl
);
5571 Set_Is_Generic_Instance
(Pack_Id
);
5572 Set_Debug_Info_Needed
(Pack_Id
);
5574 -- Case of not a compilation unit
5576 if Nkind
(Parent
(N
)) /= N_Compilation_Unit
then
5577 Mark_Rewrite_Insertion
(Pack_Decl
);
5578 Insert_Before
(N
, Pack_Decl
);
5579 Set_Has_Completion
(Pack_Id
);
5581 -- Case of an instantiation that is a compilation unit
5583 -- Place declaration on current node so context is complete for
5584 -- analysis (including nested instantiations), and for use in a
5585 -- context_clause (see Analyze_With_Clause).
5588 Set_Unit
(Parent
(N
), Pack_Decl
);
5589 Set_Parent_Spec
(Pack_Decl
, Parent_Spec
(N
));
5592 Analyze
(Pack_Decl
);
5593 Check_Formal_Packages
(Pack_Id
);
5595 -- Body of the enclosing package is supplied when instantiating the
5596 -- subprogram body, after semantic analysis is completed.
5598 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
5600 -- Remove package itself from visibility, so it does not
5601 -- conflict with subprogram.
5603 Set_Name_Entity_Id
(Chars
(Pack_Id
), Homonym
(Pack_Id
));
5605 -- Set name and scope of internal subprogram so that the proper
5606 -- external name will be generated. The proper scope is the scope
5607 -- of the wrapper package. We need to generate debugging info for
5608 -- the internal subprogram, so set flag accordingly.
5610 Set_Chars
(Anon_Id
, Chars
(Defining_Entity
(N
)));
5611 Set_Scope
(Anon_Id
, Scope
(Pack_Id
));
5613 -- Mark wrapper package as referenced, to avoid spurious warnings
5614 -- if the instantiation appears in various with_ clauses of
5615 -- subunits of the main unit.
5617 Set_Referenced
(Pack_Id
);
5620 Set_Is_Generic_Instance
(Anon_Id
);
5621 Set_Debug_Info_Needed
(Anon_Id
);
5622 Act_Decl_Id
:= New_Copy
(Anon_Id
);
5624 Set_Parent
(Act_Decl_Id
, Parent
(Anon_Id
));
5625 Set_Chars
(Act_Decl_Id
, Chars
(Defining_Entity
(N
)));
5626 Set_Sloc
(Act_Decl_Id
, Sloc
(Defining_Entity
(N
)));
5628 -- Subprogram instance comes from source only if generic does
5630 Preserve_Comes_From_Source
(Act_Decl_Id
, Gen_Unit
);
5632 -- If the instance is a child unit, mark the Id accordingly. Mark
5633 -- the anonymous entity as well, which is the real subprogram and
5634 -- which is used when the instance appears in a context clause.
5635 -- Similarly, propagate the Is_Eliminated flag to handle properly
5636 -- nested eliminated subprograms.
5638 Set_Is_Child_Unit
(Act_Decl_Id
, Is_Child_Unit
(Defining_Entity
(N
)));
5639 Set_Is_Child_Unit
(Anon_Id
, Is_Child_Unit
(Defining_Entity
(N
)));
5640 New_Overloaded_Entity
(Act_Decl_Id
);
5641 Check_Eliminated
(Act_Decl_Id
);
5642 Set_Is_Eliminated
(Anon_Id
, Is_Eliminated
(Act_Decl_Id
));
5644 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
5646 -- In compilation unit case, kill elaboration checks on the
5647 -- instantiation, since they are never needed - the body is
5648 -- instantiated at the same point as the spec.
5650 if Legacy_Elaboration_Checks
then
5651 Set_Kill_Elaboration_Checks
(Act_Decl_Id
);
5652 Set_Suppress_Elaboration_Warnings
(Act_Decl_Id
);
5655 Set_Is_Compilation_Unit
(Anon_Id
);
5656 Set_Cunit_Entity
(Current_Sem_Unit
, Pack_Id
);
5659 -- The instance is not a freezing point for the new subprogram.
5660 -- The anonymous subprogram may have a freeze node, created for
5661 -- some delayed aspects. This freeze node must not be inherited
5662 -- by the visible subprogram entity.
5664 Set_Is_Frozen
(Act_Decl_Id
, False);
5665 Set_Freeze_Node
(Act_Decl_Id
, Empty
);
5667 if Nkind
(Defining_Entity
(N
)) = N_Defining_Operator_Symbol
then
5668 Valid_Operator_Definition
(Act_Decl_Id
);
5671 Set_Alias
(Act_Decl_Id
, Anon_Id
);
5672 Set_Has_Completion
(Act_Decl_Id
);
5673 Set_Related_Instance
(Pack_Id
, Act_Decl_Id
);
5675 if Nkind
(Parent
(N
)) = N_Compilation_Unit
then
5676 Set_Body_Required
(Parent
(N
), False);
5678 end Analyze_Instance_And_Renamings
;
5680 -------------------------------
5681 -- Build_Subprogram_Renaming --
5682 -------------------------------
5684 procedure Build_Subprogram_Renaming
is
5685 Renaming_Decl
: Node_Id
;
5686 Unit_Renaming
: Node_Id
;
5690 Make_Subprogram_Renaming_Declaration
(Loc
,
5693 (Specification
(Original_Node
(Gen_Decl
)),
5695 Instantiating
=> True),
5696 Name
=> New_Occurrence_Of
(Anon_Id
, Loc
));
5698 -- The generic may be a child unit. The renaming needs an identifier
5699 -- with the proper name.
5701 Set_Defining_Unit_Name
(Specification
(Unit_Renaming
),
5702 Make_Defining_Identifier
(Loc
, Chars
(Gen_Unit
)));
5704 -- If there is a formal subprogram with the same name as the unit
5705 -- itself, do not add this renaming declaration, to prevent
5706 -- ambiguities when there is a call with that name in the body.
5708 Renaming_Decl
:= First
(Renaming_List
);
5709 while Present
(Renaming_Decl
) loop
5710 if Nkind
(Renaming_Decl
) = N_Subprogram_Renaming_Declaration
5712 Chars
(Defining_Entity
(Renaming_Decl
)) = Chars
(Gen_Unit
)
5717 Next
(Renaming_Decl
);
5720 if No
(Renaming_Decl
) then
5721 Append
(Unit_Renaming
, Renaming_List
);
5723 end Build_Subprogram_Renaming
;
5727 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
5728 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
5729 Saved_ISMP
: constant Boolean :=
5730 Ignore_SPARK_Mode_Pragmas_In_Instance
;
5731 Saved_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
5732 Saved_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
5733 -- Save the Ghost and SPARK mode-related data to restore on exit
5735 Vis_Prims_List
: Elist_Id
:= No_Elist
;
5736 -- List of primitives made temporarily visible in the instantiation
5737 -- to match the visibility of the formal type
5739 -- Start of processing for Analyze_Subprogram_Instantiation
5742 -- Preserve relevant elaboration-related attributes of the context which
5743 -- are no longer available or very expensive to recompute once analysis,
5744 -- resolution, and expansion are over.
5746 Mark_Elaboration_Attributes
5753 -- Very first thing: check for special Text_IO unit in case we are
5754 -- instantiating one of the children of [[Wide_]Wide_]Text_IO. Of course
5755 -- such an instantiation is bogus (these are packages, not subprograms),
5756 -- but we get a better error message if we do this.
5758 Check_Text_IO_Special_Unit
(Gen_Id
);
5760 -- Make node global for error reporting
5762 Instantiation_Node
:= N
;
5764 -- For package instantiations we turn off style checks, because they
5765 -- will have been emitted in the generic. For subprogram instantiations
5766 -- we want to apply at least the check on overriding indicators so we
5767 -- do not modify the style check status.
5769 -- The renaming declarations for the actuals do not come from source and
5770 -- will not generate spurious warnings.
5772 Preanalyze_Actuals
(N
);
5775 Env_Installed
:= True;
5776 Check_Generic_Child_Unit
(Gen_Id
, Parent_Installed
);
5777 Gen_Unit
:= Entity
(Gen_Id
);
5779 -- A subprogram instantiation is Ghost when it is subject to pragma
5780 -- Ghost or the generic template is Ghost. Set the mode now to ensure
5781 -- that any nodes generated during analysis and expansion are marked as
5784 Mark_And_Set_Ghost_Instantiation
(N
, Gen_Unit
);
5786 Generate_Reference
(Gen_Unit
, Gen_Id
);
5788 if Nkind
(Gen_Id
) = N_Identifier
5789 and then Chars
(Gen_Unit
) = Chars
(Defining_Entity
(N
))
5792 ("& is hidden within declaration of instance", Gen_Id
, Gen_Unit
);
5795 if Etype
(Gen_Unit
) = Any_Type
then
5800 -- Verify that it is a generic subprogram of the right kind, and that
5801 -- it does not lead to a circular instantiation.
5803 if K
= E_Procedure
and then Ekind
(Gen_Unit
) /= E_Generic_Procedure
then
5805 ("& is not the name of a generic procedure", Gen_Id
, Gen_Unit
);
5807 elsif K
= E_Function
and then Ekind
(Gen_Unit
) /= E_Generic_Function
then
5809 ("& is not the name of a generic function", Gen_Id
, Gen_Unit
);
5811 elsif In_Open_Scopes
(Gen_Unit
) then
5812 Error_Msg_NE
("instantiation of & within itself", N
, Gen_Unit
);
5815 Mutate_Ekind
(Inst_Id
, K
);
5816 Set_Scope
(Inst_Id
, Current_Scope
);
5818 Set_Entity
(Gen_Id
, Gen_Unit
);
5820 if In_Extended_Main_Source_Unit
(N
) then
5821 Set_Is_Instantiated
(Gen_Unit
);
5822 Generate_Reference
(Gen_Unit
, N
);
5825 -- If renaming, get original unit
5827 if Present
(Renamed_Entity
(Gen_Unit
))
5828 and then Is_Generic_Subprogram
(Renamed_Entity
(Gen_Unit
))
5830 Gen_Unit
:= Renamed_Entity
(Gen_Unit
);
5831 Set_Is_Instantiated
(Gen_Unit
);
5832 Generate_Reference
(Gen_Unit
, N
);
5835 if Contains_Instance_Of
(Gen_Unit
, Current_Scope
, Gen_Id
) then
5836 Error_Msg_Node_2
:= Current_Scope
;
5838 ("circular instantiation: & instantiated in &!", N
, Gen_Unit
);
5839 Circularity_Detected
:= True;
5840 Restore_Hidden_Primitives
(Vis_Prims_List
);
5844 Gen_Decl
:= Unit_Declaration_Node
(Gen_Unit
);
5846 -- Initialize renamings map, for error checking
5848 Generic_Renamings
.Set_Last
(0);
5849 Generic_Renamings_HTable
.Reset
;
5851 Create_Instantiation_Source
(N
, Gen_Unit
, S_Adjustment
);
5853 -- Copy original generic tree, to produce text for instantiation
5857 (Original_Node
(Gen_Decl
), Empty
, Instantiating
=> True);
5859 -- Inherit overriding indicator from instance node
5861 Act_Spec
:= Specification
(Act_Tree
);
5862 Set_Must_Override
(Act_Spec
, Must_Override
(N
));
5863 Set_Must_Not_Override
(Act_Spec
, Must_Not_Override
(N
));
5866 Analyze_Associations
5868 Formals
=> Generic_Formal_Declarations
(Act_Tree
),
5869 F_Copy
=> Generic_Formal_Declarations
(Gen_Decl
));
5871 Vis_Prims_List
:= Check_Hidden_Primitives
(Renaming_List
);
5873 -- The subprogram itself cannot contain a nested instance, so the
5874 -- current parent is left empty.
5876 Set_Instance_Env
(Gen_Unit
, Empty
);
5878 -- Build the subprogram declaration, which does not appear in the
5879 -- generic template, and give it a sloc consistent with that of the
5882 Set_Defining_Unit_Name
(Act_Spec
, Anon_Id
);
5883 Set_Generic_Parent
(Act_Spec
, Gen_Unit
);
5885 Make_Subprogram_Declaration
(Sloc
(Act_Spec
),
5886 Specification
=> Act_Spec
);
5888 -- The aspects have been copied previously, but they have to be
5889 -- linked explicitly to the new subprogram declaration. Explicit
5890 -- pre/postconditions on the instance are analyzed below, in a
5893 Move_Aspects
(Act_Tree
, To
=> Act_Decl
);
5894 Set_Categorization_From_Pragmas
(Act_Decl
);
5896 if Parent_Installed
then
5900 Append
(Act_Decl
, Renaming_List
);
5902 -- Contract-related source pragmas that follow a generic subprogram
5903 -- must be instantiated explicitly because they are not part of the
5904 -- subprogram template.
5906 Instantiate_Subprogram_Contract
5907 (Original_Node
(Gen_Decl
), Renaming_List
);
5909 Build_Subprogram_Renaming
;
5911 -- If the context of the instance is subject to SPARK_Mode "off" or
5912 -- the annotation is altogether missing, set the global flag which
5913 -- signals Analyze_Pragma to ignore all SPARK_Mode pragmas within
5914 -- the instance. This should be done prior to analyzing the instance.
5916 if SPARK_Mode
/= On
then
5917 Ignore_SPARK_Mode_Pragmas_In_Instance
:= True;
5920 -- If the context of an instance is not subject to SPARK_Mode "off",
5921 -- and the generic spec is subject to an explicit SPARK_Mode pragma,
5922 -- the latter should be the one applicable to the instance.
5924 if not Ignore_SPARK_Mode_Pragmas_In_Instance
5925 and then Saved_SM
/= Off
5926 and then Present
(SPARK_Pragma
(Gen_Unit
))
5928 Set_SPARK_Mode
(Gen_Unit
);
5931 -- Need to mark Anon_Id intrinsic before calling
5932 -- Analyze_Instance_And_Renamings because this flag may be propagated
5935 if Is_Intrinsic_Subprogram
(Gen_Unit
) then
5936 Set_Is_Intrinsic_Subprogram
(Anon_Id
);
5937 Set_Interface_Name
(Anon_Id
, Interface_Name
(Gen_Unit
));
5940 Analyze_Instance_And_Renamings
;
5942 -- Restore SPARK_Mode from the context after analysis of the package
5943 -- declaration, so that the SPARK_Mode on the generic spec does not
5944 -- apply to the pending instance for the instance body.
5946 if not Ignore_SPARK_Mode_Pragmas_In_Instance
5947 and then Saved_SM
/= Off
5948 and then Present
(SPARK_Pragma
(Gen_Unit
))
5950 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
5953 -- If the generic is marked Import (Intrinsic), then so is the
5954 -- instance; this indicates that there is no body to instantiate.
5955 -- We also copy the interface name in case this is handled by the
5956 -- back-end and deal with an instance of unchecked conversion.
5958 if Is_Intrinsic_Subprogram
(Gen_Unit
) then
5959 Set_Is_Intrinsic_Subprogram
(Act_Decl_Id
);
5960 Set_Interface_Name
(Act_Decl_Id
, Interface_Name
(Gen_Unit
));
5962 if Chars
(Gen_Unit
) = Name_Unchecked_Conversion
then
5963 Validate_Unchecked_Conversion
(N
, Act_Decl_Id
);
5967 -- Inherit convention from generic unit. Intrinsic convention, as for
5968 -- an instance of unchecked conversion, is not inherited because an
5969 -- explicit Ada instance has been created.
5971 if Has_Convention_Pragma
(Gen_Unit
)
5972 and then Convention
(Gen_Unit
) /= Convention_Intrinsic
5974 Set_Convention
(Act_Decl_Id
, Convention
(Gen_Unit
));
5975 Set_Is_Exported
(Act_Decl_Id
, Is_Exported
(Gen_Unit
));
5978 Generate_Definition
(Act_Decl_Id
);
5980 -- Inherit all inlining-related flags which apply to the generic in
5981 -- the subprogram and its declaration.
5983 Set_Is_Inlined
(Act_Decl_Id
, Is_Inlined
(Gen_Unit
));
5984 Set_Is_Inlined
(Anon_Id
, Is_Inlined
(Gen_Unit
));
5986 Set_Has_Pragma_Inline
(Act_Decl_Id
, Has_Pragma_Inline
(Gen_Unit
));
5987 Set_Has_Pragma_Inline
(Anon_Id
, Has_Pragma_Inline
(Gen_Unit
));
5989 Set_Has_Pragma_Inline_Always
5990 (Act_Decl_Id
, Has_Pragma_Inline_Always
(Gen_Unit
));
5991 Set_Has_Pragma_Inline_Always
5992 (Anon_Id
, Has_Pragma_Inline_Always
(Gen_Unit
));
5994 Set_Has_Pragma_No_Inline
5995 (Act_Decl_Id
, Has_Pragma_No_Inline
(Gen_Unit
));
5996 Set_Has_Pragma_No_Inline
5997 (Anon_Id
, Has_Pragma_No_Inline
(Gen_Unit
));
5999 -- Propagate No_Return if pragma applied to generic unit. This must
6000 -- be done explicitly because pragma does not appear in generic
6001 -- declaration (unlike the aspect case).
6003 if No_Return
(Gen_Unit
) then
6004 Set_No_Return
(Act_Decl_Id
);
6005 Set_No_Return
(Anon_Id
);
6008 -- Mark both the instance spec and the anonymous package in case the
6009 -- body is instantiated at a later pass. This preserves the original
6010 -- context in effect for the body.
6012 if SPARK_Mode
/= On
then
6013 Set_Ignore_SPARK_Mode_Pragmas
(Act_Decl_Id
);
6014 Set_Ignore_SPARK_Mode_Pragmas
(Anon_Id
);
6017 if Legacy_Elaboration_Checks
6018 and then not Is_Intrinsic_Subprogram
(Gen_Unit
)
6020 Check_Elab_Instantiation
(N
);
6023 -- Save the scenario for later examination by the ABE Processing
6026 Record_Elaboration_Scenario
(N
);
6028 -- The instantiation results in a guaranteed ABE. Create a completing
6029 -- body for the subprogram declaration because the real body will not
6032 if Is_Known_Guaranteed_ABE
(N
) then
6033 Provide_Completing_Bodies
(Instance_Spec
(N
));
6036 if Is_Dispatching_Operation
(Act_Decl_Id
)
6037 and then Ada_Version
>= Ada_2005
6043 Formal
:= First_Formal
(Act_Decl_Id
);
6044 while Present
(Formal
) loop
6045 if Ekind
(Etype
(Formal
)) = E_Anonymous_Access_Type
6046 and then Is_Controlling_Formal
(Formal
)
6047 and then not Can_Never_Be_Null
(Formal
)
6050 ("access parameter& is controlling,", N
, Formal
);
6052 ("\corresponding parameter of & must be explicitly "
6053 & "null-excluding", N
, Gen_Id
);
6056 Next_Formal
(Formal
);
6061 Check_Hidden_Child_Unit
(N
, Gen_Unit
, Act_Decl_Id
);
6063 Validate_Categorization_Dependency
(N
, Act_Decl_Id
);
6065 if not Is_Intrinsic_Subprogram
(Act_Decl_Id
) then
6066 Inherit_Context
(Gen_Decl
, N
);
6068 Restore_Private_Views
(Pack_Id
, False);
6070 -- If the context requires a full instantiation, mark node for
6071 -- subsequent construction of the body.
6073 if Need_Subprogram_Instance_Body
(N
, Act_Decl_Id
) then
6074 Check_Forward_Instantiation
(Gen_Decl
);
6076 -- The wrapper package is always delayed, because it does not
6077 -- constitute a freeze point, but to insure that the freeze node
6078 -- is placed properly, it is created directly when instantiating
6079 -- the body (otherwise the freeze node might appear to early for
6080 -- nested instantiations).
6082 elsif Nkind
(Parent
(N
)) = N_Compilation_Unit
then
6083 Rewrite
(N
, Unit
(Parent
(N
)));
6084 Set_Unit
(Parent
(N
), N
);
6087 -- Replace instance node for library-level instantiations of
6088 -- intrinsic subprograms.
6090 elsif Nkind
(Parent
(N
)) = N_Compilation_Unit
then
6091 Rewrite
(N
, Unit
(Parent
(N
)));
6092 Set_Unit
(Parent
(N
), N
);
6095 if Parent_Installed
then
6099 Restore_Hidden_Primitives
(Vis_Prims_List
);
6101 Env_Installed
:= False;
6102 Generic_Renamings
.Set_Last
(0);
6103 Generic_Renamings_HTable
.Reset
;
6107 -- Analyze aspects in declaration if no errors appear in the instance.
6109 if Has_Aspects
(N
) and then Serious_Errors_Detected
= Errs
then
6110 Analyze_Aspect_Specifications
(N
, Act_Decl_Id
);
6113 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Saved_ISMP
;
6114 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
6115 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
6118 when Instantiation_Error
=>
6119 if Parent_Installed
then
6123 if Env_Installed
then
6127 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Saved_ISMP
;
6128 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
6129 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
6130 end Analyze_Subprogram_Instantiation
;
6132 ---------------------------
6133 -- Get_Associated_Entity --
6134 ---------------------------
6136 function Get_Associated_Entity
(Id
: Entity_Id
) return Entity_Id
is
6140 Assoc
:= Associated_Entity
(Id
);
6142 if Present
(Assoc
) then
6143 while Present
(Associated_Entity
(Assoc
)) loop
6144 Assoc
:= Associated_Entity
(Assoc
);
6149 end Get_Associated_Entity
;
6151 -------------------------
6152 -- Get_Associated_Node --
6153 -------------------------
6155 function Get_Associated_Node
(N
: Node_Id
) return Node_Id
is
6159 Assoc
:= Associated_Node
(N
);
6161 if Nkind
(Assoc
) /= Nkind
(N
) then
6164 elsif Nkind
(Assoc
) in N_Aggregate | N_Extension_Aggregate
then
6168 -- If the node is part of an inner generic, it may itself have been
6169 -- remapped into a further generic copy. Associated_Node is otherwise
6170 -- used for the entity of the node, and will be of a different node
6171 -- kind, or else N has been rewritten as a literal or function call.
6173 while Present
(Associated_Node
(Assoc
))
6174 and then Nkind
(Associated_Node
(Assoc
)) = Nkind
(Assoc
)
6176 Assoc
:= Associated_Node
(Assoc
);
6179 -- Follow an additional link in case the final node was rewritten.
6180 -- This can only happen with nested generic units.
6182 if (Nkind
(Assoc
) = N_Identifier
or else Nkind
(Assoc
) in N_Op
)
6183 and then Present
(Associated_Node
(Assoc
))
6184 and then Nkind
(Associated_Node
(Assoc
)) in N_Function_Call
6185 | N_Explicit_Dereference
6190 Assoc
:= Associated_Node
(Assoc
);
6193 -- An additional special case: an unconstrained type in an object
6194 -- declaration may have been rewritten as a local subtype constrained
6195 -- by the expression in the declaration. We need to recover the
6196 -- original entity, which may be global.
6198 if Present
(Original_Node
(Assoc
))
6199 and then Nkind
(Parent
(N
)) = N_Object_Declaration
6201 Assoc
:= Original_Node
(Assoc
);
6206 end Get_Associated_Node
;
6208 -----------------------------------
6209 -- Build_Subprogram_Decl_Wrapper --
6210 -----------------------------------
6212 function Build_Subprogram_Decl_Wrapper
6213 (Formal_Subp
: Entity_Id
) return Node_Id
6215 Loc
: constant Source_Ptr
:= Sloc
(Current_Scope
);
6216 Ret_Type
: constant Entity_Id
:= Get_Instance_Of
(Etype
(Formal_Subp
));
6219 Parm_Spec
: Node_Id
;
6220 Profile
: List_Id
:= New_List
;
6227 Subp
:= Make_Defining_Identifier
(Loc
, Chars
(Formal_Subp
));
6228 Mutate_Ekind
(Subp
, Ekind
(Formal_Subp
));
6229 Set_Is_Generic_Actual_Subprogram
(Subp
);
6231 Profile
:= Parameter_Specifications
(
6233 (Specification
(Unit_Declaration_Node
(Formal_Subp
))));
6235 Form_F
:= First_Formal
(Formal_Subp
);
6236 Parm_Spec
:= First
(Profile
);
6238 -- Create new entities for the formals. Reset entities so that
6239 -- parameter types are properly resolved when wrapper declaration
6242 while Present
(Parm_Spec
) loop
6243 New_F
:= Make_Defining_Identifier
(Loc
, Chars
(Form_F
));
6244 Set_Defining_Identifier
(Parm_Spec
, New_F
);
6245 Set_Entity
(Parameter_Type
(Parm_Spec
), Empty
);
6247 Next_Formal
(Form_F
);
6250 if Ret_Type
= Standard_Void_Type
then
6252 Make_Procedure_Specification
(Loc
,
6253 Defining_Unit_Name
=> Subp
,
6254 Parameter_Specifications
=> Profile
);
6257 Make_Function_Specification
(Loc
,
6258 Defining_Unit_Name
=> Subp
,
6259 Parameter_Specifications
=> Profile
,
6260 Result_Definition
=> New_Occurrence_Of
(Ret_Type
, Loc
));
6264 Make_Subprogram_Declaration
(Loc
, Specification
=> Spec
);
6267 end Build_Subprogram_Decl_Wrapper
;
6269 -----------------------------------
6270 -- Build_Subprogram_Body_Wrapper --
6271 -----------------------------------
6273 function Build_Subprogram_Body_Wrapper
6274 (Formal_Subp
: Entity_Id
;
6275 Actual_Name
: Node_Id
) return Node_Id
6277 Loc
: constant Source_Ptr
:= Sloc
(Current_Scope
);
6278 Ret_Type
: constant Entity_Id
:= Get_Instance_Of
(Etype
(Formal_Subp
));
6279 Spec_Node
: constant Node_Id
:=
6281 (Build_Subprogram_Decl_Wrapper
(Formal_Subp
));
6284 Body_Node
: Node_Id
;
6287 Actuals
:= New_List
;
6288 Act
:= First
(Parameter_Specifications
(Spec_Node
));
6290 while Present
(Act
) loop
6292 Make_Identifier
(Loc
, Chars
(Defining_Identifier
(Act
))));
6296 if Ret_Type
= Standard_Void_Type
then
6297 Stmt
:= Make_Procedure_Call_Statement
(Loc
,
6298 Name
=> Actual_Name
,
6299 Parameter_Associations
=> Actuals
);
6302 Stmt
:= Make_Simple_Return_Statement
(Loc
,
6304 Make_Function_Call
(Loc
,
6305 Name
=> Actual_Name
,
6306 Parameter_Associations
=> Actuals
));
6309 Body_Node
:= Make_Subprogram_Body
(Loc
,
6310 Specification
=> Spec_Node
,
6311 Declarations
=> New_List
,
6312 Handled_Statement_Sequence
=>
6313 Make_Handled_Sequence_Of_Statements
(Loc
,
6314 Statements
=> New_List
(Stmt
)));
6317 end Build_Subprogram_Body_Wrapper
;
6319 -------------------------------------------
6320 -- Build_Instance_Compilation_Unit_Nodes --
6321 -------------------------------------------
6323 procedure Build_Instance_Compilation_Unit_Nodes
6328 Decl_Cunit
: Node_Id
;
6329 Body_Cunit
: Node_Id
;
6331 New_Main
: constant Entity_Id
:= Defining_Entity
(Act_Decl
);
6332 Old_Main
: constant Entity_Id
:= Cunit_Entity
(Main_Unit
);
6335 -- A new compilation unit node is built for the instance declaration.
6336 -- It relocates the auxiliary declaration node from the compilation unit
6337 -- where the instance appeared, so that declarations that originally
6338 -- followed the instance will be attached to the spec compilation unit.
6341 Make_Compilation_Unit
(Sloc
(N
),
6342 Context_Items
=> Empty_List
,
6344 Aux_Decls_Node
=> Relocate_Node
(Aux_Decls_Node
(Parent
(N
))));
6346 Set_Parent_Spec
(Act_Decl
, Parent_Spec
(N
));
6348 -- The new compilation unit is linked to its body, but both share the
6349 -- same file, so we do not set Body_Required on the new unit so as not
6350 -- to create a spurious dependency on a non-existent body in the ali.
6351 -- This simplifies CodePeer unit traversal.
6353 -- We use the original instantiation compilation unit as the resulting
6354 -- compilation unit of the instance, since this is the main unit.
6356 Rewrite
(N
, Act_Body
);
6358 -- Propagate the aspect specifications from the package body template to
6359 -- the instantiated version of the package body.
6361 if Has_Aspects
(Act_Body
) then
6362 Set_Aspect_Specifications
6363 (N
, New_Copy_List_Tree
(Aspect_Specifications
(Act_Body
)));
6366 Body_Cunit
:= Parent
(N
);
6368 -- The two compilation unit nodes are linked by the Library_Unit field
6370 Set_Library_Unit
(Decl_Cunit
, Body_Cunit
);
6371 Set_Library_Unit
(Body_Cunit
, Decl_Cunit
);
6373 -- Preserve the private nature of the package if needed
6375 Set_Private_Present
(Decl_Cunit
, Private_Present
(Body_Cunit
));
6377 -- If the instance is not the main unit, its context, categorization
6378 -- and elaboration entity are not relevant to the compilation.
6380 if Body_Cunit
/= Cunit
(Main_Unit
) then
6381 Make_Instance_Unit
(Body_Cunit
, In_Main
=> False);
6385 -- The context clause items on the instantiation, which are now attached
6386 -- to the body compilation unit (since the body overwrote the original
6387 -- instantiation node), semantically belong on the spec, so copy them
6388 -- there. It's harmless to leave them on the body as well. In fact one
6389 -- could argue that they belong in both places.
6391 Citem
:= First
(Context_Items
(Body_Cunit
));
6392 while Present
(Citem
) loop
6393 Append
(New_Copy
(Citem
), Context_Items
(Decl_Cunit
));
6397 -- Propagate categorization flags on packages, so that they appear in
6398 -- the ali file for the spec of the unit.
6400 if Ekind
(New_Main
) = E_Package
then
6401 Set_Is_Pure
(Old_Main
, Is_Pure
(New_Main
));
6402 Set_Is_Preelaborated
(Old_Main
, Is_Preelaborated
(New_Main
));
6403 Set_Is_Remote_Types
(Old_Main
, Is_Remote_Types
(New_Main
));
6404 Set_Is_Shared_Passive
(Old_Main
, Is_Shared_Passive
(New_Main
));
6405 Set_Is_Remote_Call_Interface
6406 (Old_Main
, Is_Remote_Call_Interface
(New_Main
));
6409 -- Make entry in Units table, so that binder can generate call to
6410 -- elaboration procedure for body, if any.
6412 Make_Instance_Unit
(Body_Cunit
, In_Main
=> True);
6413 Main_Unit_Entity
:= New_Main
;
6414 Set_Cunit_Entity
(Main_Unit
, Main_Unit_Entity
);
6416 -- Build elaboration entity, since the instance may certainly generate
6417 -- elaboration code requiring a flag for protection.
6419 Build_Elaboration_Entity
(Decl_Cunit
, New_Main
);
6420 end Build_Instance_Compilation_Unit_Nodes
;
6422 --------------------------------
6423 -- Check_Abbreviated_Instance --
6424 --------------------------------
6426 procedure Check_Abbreviated_Instance
6428 Parent_Installed
: in out Boolean)
6430 Inst_Node
: Node_Id
;
6433 if Nkind
(N
) = N_Package_Specification
6434 and then Is_Abbreviated_Instance
(Defining_Entity
(N
))
6436 Inst_Node
:= Get_Unit_Instantiation_Node
(Defining_Entity
(N
));
6437 Check_Generic_Child_Unit
(Name
(Inst_Node
), Parent_Installed
);
6439 end Check_Abbreviated_Instance
;
6441 -----------------------------
6442 -- Check_Access_Definition --
6443 -----------------------------
6445 procedure Check_Access_Definition
(N
: Node_Id
) is
6448 (Ada_Version
>= Ada_2005
and then Present
(Access_Definition
(N
)));
6450 end Check_Access_Definition
;
6452 -----------------------------------
6453 -- Check_Formal_Package_Instance --
6454 -----------------------------------
6456 -- If the formal has specific parameters, they must match those of the
6457 -- actual. Both of them are instances, and the renaming declarations for
6458 -- their formal parameters appear in the same order in both. The analyzed
6459 -- formal has been analyzed in the context of the current instance.
6461 procedure Check_Formal_Package_Instance
6462 (Formal_Pack
: Entity_Id
;
6463 Actual_Pack
: Entity_Id
)
6465 E1
: Entity_Id
:= First_Entity
(Actual_Pack
);
6466 E2
: Entity_Id
:= First_Entity
(Formal_Pack
);
6467 Prev_E1
: Entity_Id
;
6472 procedure Check_Mismatch
(B
: Boolean);
6473 -- Common error routine for mismatch between the parameters of the
6474 -- actual instance and those of the formal package.
6476 function Is_Defaulted
(Param
: Entity_Id
) return Boolean;
6477 -- If the formal package has partly box-initialized formals, skip
6478 -- conformance check for these formals. Previously the code assumed
6479 -- that box initialization for a formal package applied to all its
6480 -- formal parameters.
6482 function Same_Instantiated_Constant
(E1
, E2
: Entity_Id
) return Boolean;
6483 -- The formal may come from a nested formal package, and the actual may
6484 -- have been constant-folded. To determine whether the two denote the
6485 -- same entity we may have to traverse several definitions to recover
6486 -- the ultimate entity that they refer to.
6488 function Same_Instantiated_Function
(E1
, E2
: Entity_Id
) return Boolean;
6489 -- The formal and the actual must be identical, but if both are
6490 -- given by attributes they end up renaming different generated bodies,
6491 -- and we must verify that the attributes themselves match.
6493 function Same_Instantiated_Variable
(E1
, E2
: Entity_Id
) return Boolean;
6494 -- Similarly, if the formal comes from a nested formal package, the
6495 -- actual may designate the formal through multiple renamings, which
6496 -- have to be followed to determine the original variable in question.
6498 --------------------
6499 -- Check_Mismatch --
6500 --------------------
6502 procedure Check_Mismatch
(B
: Boolean) is
6503 -- A Formal_Type_Declaration for a derived private type is rewritten
6504 -- as a private extension decl. (see Analyze_Formal_Derived_Type),
6505 -- which is why we examine the original node.
6507 Kind
: constant Node_Kind
:= Nkind
(Original_Node
(Parent
(E2
)));
6510 if Kind
= N_Formal_Type_Declaration
then
6513 elsif Kind
in N_Formal_Object_Declaration
6514 | N_Formal_Package_Declaration
6515 | N_Formal_Subprogram_Declaration
6519 -- Ada 2012: If both formal and actual are incomplete types they
6522 elsif Is_Incomplete_Type
(E1
) and then Is_Incomplete_Type
(E2
) then
6527 ("actual for & in actual instance does not match formal",
6528 Parent
(Actual_Pack
), E1
);
6536 function Is_Defaulted
(Param
: Entity_Id
) return Boolean is
6541 First
(Generic_Associations
(Parent
6542 (Associated_Formal_Package
(Actual_Pack
))));
6544 while Present
(Assoc
) loop
6545 if Nkind
(Assoc
) = N_Others_Choice
then
6548 elsif Nkind
(Assoc
) = N_Generic_Association
6549 and then Chars
(Selector_Name
(Assoc
)) = Chars
(Param
)
6551 return Box_Present
(Assoc
);
6560 --------------------------------
6561 -- Same_Instantiated_Constant --
6562 --------------------------------
6564 function Same_Instantiated_Constant
6565 (E1
, E2
: Entity_Id
) return Boolean
6571 while Present
(Ent
) loop
6575 elsif Ekind
(Ent
) /= E_Constant
then
6578 elsif Is_Entity_Name
(Constant_Value
(Ent
)) then
6579 if Entity
(Constant_Value
(Ent
)) = E1
then
6582 Ent
:= Entity
(Constant_Value
(Ent
));
6585 -- The actual may be a constant that has been folded. Recover
6588 elsif Is_Entity_Name
(Original_Node
(Constant_Value
(Ent
))) then
6589 Ent
:= Entity
(Original_Node
(Constant_Value
(Ent
)));
6597 end Same_Instantiated_Constant
;
6599 --------------------------------
6600 -- Same_Instantiated_Function --
6601 --------------------------------
6603 function Same_Instantiated_Function
6604 (E1
, E2
: Entity_Id
) return Boolean
6608 if Alias
(E1
) = Alias
(E2
) then
6611 elsif Present
(Alias
(E2
)) then
6612 U1
:= Original_Node
(Unit_Declaration_Node
(E1
));
6613 U2
:= Original_Node
(Unit_Declaration_Node
(Alias
(E2
)));
6615 return Nkind
(U1
) = N_Subprogram_Renaming_Declaration
6616 and then Nkind
(Name
(U1
)) = N_Attribute_Reference
6618 and then Nkind
(U2
) = N_Subprogram_Renaming_Declaration
6619 and then Nkind
(Name
(U2
)) = N_Attribute_Reference
6622 Attribute_Name
(Name
(U1
)) = Attribute_Name
(Name
(U2
));
6626 end Same_Instantiated_Function
;
6628 --------------------------------
6629 -- Same_Instantiated_Variable --
6630 --------------------------------
6632 function Same_Instantiated_Variable
6633 (E1
, E2
: Entity_Id
) return Boolean
6635 function Original_Entity
(E
: Entity_Id
) return Entity_Id
;
6636 -- Follow chain of renamings to the ultimate ancestor
6638 ---------------------
6639 -- Original_Entity --
6640 ---------------------
6642 function Original_Entity
(E
: Entity_Id
) return Entity_Id
is
6647 while Nkind
(Parent
(Orig
)) = N_Object_Renaming_Declaration
6648 and then Present
(Renamed_Object
(Orig
))
6649 and then Is_Entity_Name
(Renamed_Object
(Orig
))
6651 Orig
:= Entity
(Renamed_Object
(Orig
));
6655 end Original_Entity
;
6657 -- Start of processing for Same_Instantiated_Variable
6660 return Ekind
(E1
) = Ekind
(E2
)
6661 and then Original_Entity
(E1
) = Original_Entity
(E2
);
6662 end Same_Instantiated_Variable
;
6664 -- Start of processing for Check_Formal_Package_Instance
6668 while Present
(E1
) and then Present
(E2
) loop
6669 exit when Ekind
(E1
) = E_Package
6670 and then Renamed_Entity
(E1
) = Renamed_Entity
(Actual_Pack
);
6672 -- If the formal is the renaming of the formal package, this
6673 -- is the end of its formal part, which may occur before the
6674 -- end of the formal part in the actual in the presence of
6675 -- defaulted parameters in the formal package.
6677 exit when Nkind
(Parent
(E2
)) = N_Package_Renaming_Declaration
6678 and then Renamed_Entity
(E2
) = Scope
(E2
);
6680 -- The analysis of the actual may generate additional internal
6681 -- entities. If the formal is defaulted, there is no corresponding
6682 -- analysis and the internal entities must be skipped, until we
6683 -- find corresponding entities again.
6685 if Comes_From_Source
(E2
)
6686 and then not Comes_From_Source
(E1
)
6687 and then Chars
(E1
) /= Chars
(E2
)
6689 while Present
(E1
) and then Chars
(E1
) /= Chars
(E2
) loop
6697 -- Entities may be declared without full declaration, such as
6698 -- itypes and predefined operators (concatenation for arrays, eg).
6699 -- Skip it and keep the formal entity to find a later match for it.
6701 elsif No
(Parent
(E2
)) and then Ekind
(E1
) /= Ekind
(E2
) then
6705 -- If the formal entity comes from a formal declaration, it was
6706 -- defaulted in the formal package, and no check is needed on it.
6708 elsif Nkind
(Original_Node
(Parent
(E2
))) in
6709 N_Formal_Object_Declaration | N_Formal_Type_Declaration
6711 -- If the formal is a tagged type the corresponding class-wide
6712 -- type has been generated as well, and it must be skipped.
6714 if Is_Type
(E2
) and then Is_Tagged_Type
(E2
) then
6720 -- Ditto for defaulted formal subprograms.
6722 elsif Is_Overloadable
(E1
)
6723 and then Nkind
(Unit_Declaration_Node
(E2
)) in
6724 N_Formal_Subprogram_Declaration
6728 elsif Is_Defaulted
(E1
) then
6731 elsif Is_Type
(E1
) then
6733 -- Subtypes must statically match. E1, E2 are the local entities
6734 -- that are subtypes of the actuals. Itypes generated for other
6735 -- parameters need not be checked, the check will be performed
6736 -- on the parameters themselves.
6738 -- If E2 is a formal type declaration, it is a defaulted parameter
6739 -- and needs no checking.
6741 if not Is_Itype
(E1
) and then not Is_Itype
(E2
) then
6744 or else Etype
(E1
) /= Etype
(E2
)
6745 or else not Subtypes_Statically_Match
(E1
, E2
));
6748 elsif Ekind
(E1
) = E_Constant
then
6750 -- IN parameters must denote the same static value, or the same
6751 -- constant, or the literal null.
6753 Expr1
:= Expression
(Parent
(E1
));
6755 if Ekind
(E2
) /= E_Constant
then
6756 Check_Mismatch
(True);
6759 Expr2
:= Expression
(Parent
(E2
));
6762 if Is_OK_Static_Expression
(Expr1
) then
6763 if not Is_OK_Static_Expression
(Expr2
) then
6764 Check_Mismatch
(True);
6766 elsif Is_Discrete_Type
(Etype
(E1
)) then
6768 V1
: constant Uint
:= Expr_Value
(Expr1
);
6769 V2
: constant Uint
:= Expr_Value
(Expr2
);
6771 Check_Mismatch
(V1
/= V2
);
6774 elsif Is_Real_Type
(Etype
(E1
)) then
6776 V1
: constant Ureal
:= Expr_Value_R
(Expr1
);
6777 V2
: constant Ureal
:= Expr_Value_R
(Expr2
);
6779 Check_Mismatch
(V1
/= V2
);
6782 elsif Is_String_Type
(Etype
(E1
))
6783 and then Nkind
(Expr1
) = N_String_Literal
6785 if Nkind
(Expr2
) /= N_String_Literal
then
6786 Check_Mismatch
(True);
6789 (not String_Equal
(Strval
(Expr1
), Strval
(Expr2
)));
6793 elsif Is_Entity_Name
(Expr1
) then
6794 if Is_Entity_Name
(Expr2
) then
6795 if Entity
(Expr1
) = Entity
(Expr2
) then
6799 (not Same_Instantiated_Constant
6800 (Entity
(Expr1
), Entity
(Expr2
)));
6804 Check_Mismatch
(True);
6807 elsif Is_Entity_Name
(Original_Node
(Expr1
))
6808 and then Is_Entity_Name
(Expr2
)
6809 and then Same_Instantiated_Constant
6810 (Entity
(Original_Node
(Expr1
)), Entity
(Expr2
))
6814 elsif Nkind
(Expr1
) = N_Null
then
6815 Check_Mismatch
(Nkind
(Expr1
) /= N_Null
);
6818 Check_Mismatch
(True);
6821 elsif Ekind
(E1
) = E_Variable
then
6822 Check_Mismatch
(not Same_Instantiated_Variable
(E1
, E2
));
6824 elsif Ekind
(E1
) = E_Package
then
6826 (Ekind
(E1
) /= Ekind
(E2
)
6827 or else (Present
(Renamed_Entity
(E2
))
6828 and then Renamed_Entity
(E1
) /=
6829 Renamed_Entity
(E2
)));
6831 elsif Is_Overloadable
(E1
) then
6832 -- Verify that the actual subprograms match. Note that actuals
6833 -- that are attributes are rewritten as subprograms. If the
6834 -- subprogram in the formal package is defaulted, no check is
6835 -- needed. Note that this can only happen in Ada 2005 when the
6836 -- formal package can be partially parameterized.
6838 if Nkind
(Unit_Declaration_Node
(E1
)) =
6839 N_Subprogram_Renaming_Declaration
6840 and then From_Default
(Unit_Declaration_Node
(E1
))
6844 -- If the formal package has an "others" box association that
6845 -- covers this formal, there is no need for a check either.
6847 elsif Nkind
(Unit_Declaration_Node
(E2
)) in
6848 N_Formal_Subprogram_Declaration
6849 and then Box_Present
(Unit_Declaration_Node
(E2
))
6853 -- No check needed if subprogram is a defaulted null procedure
6855 elsif No
(Alias
(E2
))
6856 and then Ekind
(E2
) = E_Procedure
6858 Null_Present
(Specification
(Unit_Declaration_Node
(E2
)))
6862 -- Otherwise the actual in the formal and the actual in the
6863 -- instantiation of the formal must match, up to renamings.
6867 (Ekind
(E2
) /= Ekind
(E1
)
6868 or else not Same_Instantiated_Function
(E1
, E2
));
6872 raise Program_Error
;
6880 end Check_Formal_Package_Instance
;
6882 ---------------------------
6883 -- Check_Formal_Packages --
6884 ---------------------------
6886 procedure Check_Formal_Packages
(P_Id
: Entity_Id
) is
6888 Formal_P
: Entity_Id
;
6889 Formal_Decl
: Node_Id
;
6892 -- Iterate through the declarations in the instance, looking for package
6893 -- renaming declarations that denote instances of formal packages, until
6894 -- we find the renaming of the current package itself. The declaration
6895 -- of a formal package that requires conformance checking is followed by
6896 -- an internal entity that is the abbreviated instance.
6898 E
:= First_Entity
(P_Id
);
6899 while Present
(E
) loop
6900 if Ekind
(E
) = E_Package
then
6901 exit when Renamed_Entity
(E
) = P_Id
;
6903 if Nkind
(Parent
(E
)) = N_Package_Renaming_Declaration
then
6904 Formal_Decl
:= Parent
(Associated_Formal_Package
(E
));
6906 if Requires_Conformance_Checking
(Formal_Decl
) then
6907 Formal_P
:= Next_Entity
(E
);
6909 -- If the instance is within an enclosing instance body
6910 -- there is no need to verify the legality of current formal
6911 -- packages because they were legal in the generic body.
6912 -- This optimization may be applicable elsewhere, and it
6913 -- also removes spurious errors that may arise with
6914 -- on-the-fly inlining and confusion between private and
6917 if not In_Instance_Body
then
6918 Check_Formal_Package_Instance
(Formal_P
, E
);
6921 -- Restore the visibility of formals of the formal instance
6922 -- that are not defaulted, and are hidden within the current
6923 -- generic. These formals may be visible within an enclosing
6929 Elmt
:= First_Elmt
(Hidden_In_Formal_Instance
(Formal_P
));
6930 while Present
(Elmt
) loop
6931 Set_Is_Hidden
(Node
(Elmt
), False);
6936 -- After checking, remove the internal validating package.
6937 -- It is only needed for semantic checks, and as it may
6938 -- contain generic formal declarations it should not reach
6941 Remove
(Unit_Declaration_Node
(Formal_P
));
6948 end Check_Formal_Packages
;
6950 ---------------------------------
6951 -- Check_Forward_Instantiation --
6952 ---------------------------------
6954 procedure Check_Forward_Instantiation
(Decl
: Node_Id
) is
6956 Gen_Comp
: Entity_Id
:= Cunit_Entity
(Get_Source_Unit
(Decl
));
6959 -- The instantiation appears before the generic body if we are in the
6960 -- scope of the unit containing the generic, either in its spec or in
6961 -- the package body, and before the generic body.
6963 if Ekind
(Gen_Comp
) = E_Package_Body
then
6964 Gen_Comp
:= Spec_Entity
(Gen_Comp
);
6967 if In_Open_Scopes
(Gen_Comp
)
6968 and then No
(Corresponding_Body
(Decl
))
6973 and then not Is_Compilation_Unit
(S
)
6974 and then not Is_Child_Unit
(S
)
6976 if Ekind
(S
) = E_Package
then
6977 Set_Has_Forward_Instantiation
(S
);
6983 end Check_Forward_Instantiation
;
6985 ---------------------------
6986 -- Check_Generic_Actuals --
6987 ---------------------------
6989 -- The visibility of the actuals may be different between the point of
6990 -- generic instantiation and the instantiation of the body.
6992 procedure Check_Generic_Actuals
6993 (Instance
: Entity_Id
;
6994 Is_Formal_Box
: Boolean)
6996 Gen_Id
: constant Entity_Id
6997 := (if Is_Generic_Unit
(Instance
) then
6999 elsif Is_Wrapper_Package
(Instance
) then
7002 (Unit_Declaration_Node
(Related_Instance
(Instance
))))
7004 Generic_Parent
(Package_Specification
(Instance
)));
7007 Parent_Scope
: constant Entity_Id
:= Scope
(Gen_Id
);
7008 -- The enclosing scope of the generic unit
7010 procedure Check_Actual_Type
(Typ
: Entity_Id
);
7011 -- If the type of the actual is a private type declared in the enclosing
7012 -- scope of the generic, either directly or through packages nested in
7013 -- bodies, but not a derived type of a private type declared elsewhere,
7014 -- then the body of the generic sees the full view of the type because
7015 -- it has to appear in the package body. If the type is private now then
7016 -- exchange views to restore the proper visibility in the instance.
7018 -----------------------
7019 -- Check_Actual_Type --
7020 -----------------------
7022 procedure Check_Actual_Type
(Typ
: Entity_Id
) is
7023 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
7025 function Scope_Within_Body_Or_Same
7027 Outer
: Entity_Id
) return Boolean;
7028 -- Determine whether scope Inner is within the body of scope Outer
7029 -- or is Outer itself.
7031 -------------------------------
7032 -- Scope_Within_Body_Or_Same --
7033 -------------------------------
7035 function Scope_Within_Body_Or_Same
7037 Outer
: Entity_Id
) return Boolean
7039 Curr
: Entity_Id
:= Inner
;
7042 while Curr
/= Standard_Standard
loop
7043 if Curr
= Outer
then
7046 elsif Is_Package_Body_Entity
(Curr
) then
7047 Curr
:= Scope
(Curr
);
7055 end Scope_Within_Body_Or_Same
;
7058 -- The exchange is only needed if the generic is defined
7059 -- within a package which is not a common ancestor of the
7060 -- scope of the instance, and is not already in scope.
7062 if Is_Private_Type
(Btyp
)
7063 and then not Has_Private_Ancestor
(Btyp
)
7064 and then Ekind
(Parent_Scope
) in E_Package | E_Generic_Package
7065 and then Scope_Within_Body_Or_Same
(Parent_Scope
, Scope
(Btyp
))
7066 and then Parent_Scope
/= Scope
(Instance
)
7067 and then not Is_Child_Unit
(Gen_Id
)
7071 -- If the type of the entity is a subtype, it may also have
7072 -- to be made visible, together with the base type of its
7073 -- full view, after exchange.
7075 if Is_Private_Type
(Typ
) then
7077 Switch_View
(Base_Type
(Typ
));
7080 end Check_Actual_Type
;
7087 E
:= First_Entity
(Instance
);
7088 while Present
(E
) loop
7090 and then Nkind
(Parent
(E
)) = N_Subtype_Declaration
7091 and then Scope
(Etype
(E
)) /= Instance
7092 and then Is_Entity_Name
(Subtype_Indication
(Parent
(E
)))
7095 Indic
: constant Node_Id
:= Subtype_Indication
(Parent
(E
));
7098 -- Restore the proper view of the actual from the information
7099 -- saved earlier by Instantiate_Type.
7101 Check_Private_View
(Indic
);
7103 -- If this view is an array type, check its component type.
7104 -- This handles the case of an array type whose component
7105 -- type is private, used as the actual in an instantiation
7106 -- of a generic construct declared in the same package as
7107 -- the component type and taking an array type with this
7108 -- component type as formal type parameter.
7110 if Is_Array_Type
(Etype
(Indic
)) then
7112 (Component_Type_For_Private_View
(Etype
(Indic
)));
7116 -- If the actual is itself the formal of a parent instance,
7117 -- then also restore the proper view of its actual and so on.
7118 -- That's necessary for nested instantiations of the form
7121 -- type Component is private;
7122 -- type Array_Type is array (Positive range <>) of Component;
7125 -- when the outermost actuals have inconsistent views, because
7126 -- the Component_Type of Array_Type of the inner instantiations
7127 -- is the actual of Component of the outermost one and not that
7128 -- of the corresponding inner instantiations.
7130 Astype
:= Ancestor_Subtype
(E
);
7131 while Present
(Astype
)
7132 and then Nkind
(Parent
(Astype
)) = N_Subtype_Declaration
7133 and then Present
(Generic_Parent_Type
(Parent
(Astype
)))
7134 and then Is_Entity_Name
(Subtype_Indication
(Parent
(Astype
)))
7136 Check_Private_View
(Subtype_Indication
(Parent
(Astype
)));
7137 Astype
:= Ancestor_Subtype
(Astype
);
7140 Set_Is_Generic_Actual_Type
(E
);
7142 if Is_Private_Type
(E
) and then Present
(Full_View
(E
)) then
7143 Set_Is_Generic_Actual_Type
(Full_View
(E
));
7146 Set_Is_Hidden
(E
, False);
7147 Set_Is_Potentially_Use_Visible
(E
, In_Use
(Instance
));
7149 -- We constructed the generic actual type as a subtype of the
7150 -- supplied type. This means that it normally would not inherit
7151 -- subtype specific attributes of the actual, which is wrong for
7152 -- the generic case.
7154 Astype
:= Ancestor_Subtype
(E
);
7158 -- This can happen when E is an itype that is the full view of
7159 -- a private type completed, e.g. with a constrained array. In
7160 -- that case, use the first subtype, which will carry size
7161 -- information. The base type itself is unconstrained and will
7164 Astype
:= First_Subtype
(E
);
7167 Set_Size_Info
(E
, Astype
);
7168 Copy_RM_Size
(To
=> E
, From
=> Astype
);
7169 Set_First_Rep_Item
(E
, First_Rep_Item
(Astype
));
7171 if Is_Discrete_Or_Fixed_Point_Type
(E
) then
7172 Set_RM_Size
(E
, RM_Size
(Astype
));
7175 elsif Ekind
(E
) = E_Package
then
7177 -- If this is the renaming for the current instance, we're done.
7178 -- Otherwise it is a formal package. If the corresponding formal
7179 -- was declared with a box, the (instantiations of the) generic
7180 -- formal part are also visible. Otherwise, ignore the entity
7181 -- created to validate the actuals.
7183 if Renamed_Entity
(E
) = Instance
then
7186 elsif Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
then
7189 -- The visibility of a formal of an enclosing generic is already
7192 elsif Denotes_Formal_Package
(E
) then
7195 elsif Present
(Associated_Formal_Package
(E
))
7196 and then not Is_Generic_Formal
(E
)
7198 Check_Generic_Actuals
7199 (Renamed_Entity
(E
),
7201 Box_Present
(Parent
(Associated_Formal_Package
(E
))));
7203 Set_Is_Hidden
(E
, False);
7206 -- If this is a subprogram instance (in a wrapper package) the
7207 -- actual is fully visible.
7209 elsif Is_Wrapper_Package
(Instance
) then
7210 Set_Is_Hidden
(E
, False);
7212 -- If the formal package is declared with a box, or if the formal
7213 -- parameter is defaulted, it is visible in the body.
7215 elsif Is_Formal_Box
or else Is_Visible_Formal
(E
) then
7216 Set_Is_Hidden
(E
, False);
7219 -- Check directly the type of the actual objects, including the
7220 -- component type for array types.
7222 if Ekind
(E
) in E_Constant | E_Variable
then
7223 Check_Actual_Type
(Etype
(E
));
7225 if Is_Array_Type
(Etype
(E
)) then
7226 Check_Actual_Type
(Component_Type
(Etype
(E
)));
7229 -- As well as the type of formal parameters of actual subprograms
7231 elsif Ekind
(E
) in E_Function | E_Procedure
7232 and then Is_Generic_Actual_Subprogram
(E
)
7233 and then Present
(Alias
(E
))
7235 Formal
:= First_Formal
(Alias
(E
));
7236 while Present
(Formal
) loop
7237 Check_Actual_Type
(Etype
(Formal
));
7238 Next_Formal
(Formal
);
7244 end Check_Generic_Actuals
;
7246 ------------------------------
7247 -- Check_Generic_Child_Unit --
7248 ------------------------------
7250 procedure Check_Generic_Child_Unit
7252 Parent_Installed
: in out Boolean)
7254 Loc
: constant Source_Ptr
:= Sloc
(Gen_Id
);
7255 Gen_Par
: Entity_Id
:= Empty
;
7257 Inst_Par
: Entity_Id
;
7260 function Find_Generic_Child
7262 Id
: Node_Id
) return Entity_Id
;
7263 -- Search generic parent for possible child unit with the given name
7265 function In_Enclosing_Instance
return Boolean;
7266 -- Within an instance of the parent, the child unit may be denoted by
7267 -- a simple name, or an abbreviated expanded name. Examine enclosing
7268 -- scopes to locate a possible parent instantiation.
7270 ------------------------
7271 -- Find_Generic_Child --
7272 ------------------------
7274 function Find_Generic_Child
7276 Id
: Node_Id
) return Entity_Id
7281 -- If entity of name is already set, instance has already been
7282 -- resolved, e.g. in an enclosing instantiation.
7284 if Present
(Entity
(Id
)) then
7285 if Scope
(Entity
(Id
)) = Scop
then
7292 E
:= First_Entity
(Scop
);
7293 while Present
(E
) loop
7294 if Chars
(E
) = Chars
(Id
)
7295 and then Is_Child_Unit
(E
)
7297 if Is_Child_Unit
(E
)
7298 and then not Is_Visible_Lib_Unit
(E
)
7301 ("generic child unit& is not visible", Gen_Id
, E
);
7313 end Find_Generic_Child
;
7315 ---------------------------
7316 -- In_Enclosing_Instance --
7317 ---------------------------
7319 function In_Enclosing_Instance
return Boolean is
7320 Enclosing_Instance
: Node_Id
;
7321 Instance_Decl
: Node_Id
;
7324 -- We do not inline any call that contains instantiations, except
7325 -- for instantiations of Unchecked_Conversion, so if we are within
7326 -- an inlined body the current instance does not require parents.
7328 if In_Inlined_Body
then
7329 pragma Assert
(Chars
(Gen_Id
) = Name_Unchecked_Conversion
);
7333 -- Loop to check enclosing scopes
7335 Enclosing_Instance
:= Current_Scope
;
7336 while Present
(Enclosing_Instance
) loop
7337 Instance_Decl
:= Unit_Declaration_Node
(Enclosing_Instance
);
7339 if Ekind
(Enclosing_Instance
) = E_Package
7340 and then Is_Generic_Instance
(Enclosing_Instance
)
7342 (Generic_Parent
(Specification
(Instance_Decl
)))
7344 -- Check whether the generic we are looking for is a child of
7347 E
:= Find_Generic_Child
7348 (Generic_Parent
(Specification
(Instance_Decl
)), Gen_Id
);
7349 exit when Present
(E
);
7355 Enclosing_Instance
:= Scope
(Enclosing_Instance
);
7367 Make_Expanded_Name
(Loc
,
7369 Prefix
=> New_Occurrence_Of
(Enclosing_Instance
, Loc
),
7370 Selector_Name
=> New_Occurrence_Of
(E
, Loc
)));
7372 Set_Entity
(Gen_Id
, E
);
7373 Set_Etype
(Gen_Id
, Etype
(E
));
7374 Parent_Installed
:= False; -- Already in scope.
7377 end In_Enclosing_Instance
;
7379 -- Start of processing for Check_Generic_Child_Unit
7382 -- If the name of the generic is given by a selected component, it may
7383 -- be the name of a generic child unit, and the prefix is the name of an
7384 -- instance of the parent, in which case the child unit must be visible.
7385 -- If this instance is not in scope, it must be placed there and removed
7386 -- after instantiation, because what is being instantiated is not the
7387 -- original child, but the corresponding child present in the instance
7390 -- If the child is instantiated within the parent, it can be given by
7391 -- a simple name. In this case the instance is already in scope, but
7392 -- the child generic must be recovered from the generic parent as well.
7394 if Nkind
(Gen_Id
) = N_Selected_Component
then
7395 S
:= Selector_Name
(Gen_Id
);
7396 Analyze
(Prefix
(Gen_Id
));
7397 Inst_Par
:= Entity
(Prefix
(Gen_Id
));
7399 if Ekind
(Inst_Par
) = E_Package
7400 and then Present
(Renamed_Entity
(Inst_Par
))
7402 Inst_Par
:= Renamed_Entity
(Inst_Par
);
7405 if Ekind
(Inst_Par
) = E_Package
then
7406 if Nkind
(Parent
(Inst_Par
)) = N_Package_Specification
then
7407 Gen_Par
:= Generic_Parent
(Parent
(Inst_Par
));
7409 elsif Nkind
(Parent
(Inst_Par
)) = N_Defining_Program_Unit_Name
7411 Nkind
(Parent
(Parent
(Inst_Par
))) = N_Package_Specification
7413 Gen_Par
:= Generic_Parent
(Parent
(Parent
(Inst_Par
)));
7416 elsif Ekind
(Inst_Par
) = E_Generic_Package
7417 and then Nkind
(Parent
(Gen_Id
)) = N_Formal_Package_Declaration
7419 -- A formal package may be a real child package, and not the
7420 -- implicit instance within a parent. In this case the child is
7421 -- not visible and has to be retrieved explicitly as well.
7423 Gen_Par
:= Inst_Par
;
7426 if Present
(Gen_Par
) then
7428 -- The prefix denotes an instantiation. The entity itself may be a
7429 -- nested generic, or a child unit.
7431 E
:= Find_Generic_Child
(Gen_Par
, S
);
7434 Change_Selected_Component_To_Expanded_Name
(Gen_Id
);
7435 Set_Entity
(Gen_Id
, E
);
7436 Set_Etype
(Gen_Id
, Etype
(E
));
7438 Set_Etype
(S
, Etype
(E
));
7440 -- Indicate that this is a reference to the parent
7442 if In_Extended_Main_Source_Unit
(Gen_Id
) then
7443 Set_Is_Instantiated
(Inst_Par
);
7446 -- A common mistake is to replicate the naming scheme of a
7447 -- hierarchy by instantiating a generic child directly, rather
7448 -- than the implicit child in a parent instance:
7450 -- generic .. package Gpar is ..
7451 -- generic .. package Gpar.Child is ..
7452 -- package Par is new Gpar ();
7455 -- package Par.Child is new Gpar.Child ();
7456 -- rather than Par.Child
7458 -- In this case the instantiation is within Par, which is an
7459 -- instance, but Gpar does not denote Par because we are not IN
7460 -- the instance of Gpar, so this is illegal. The test below
7461 -- recognizes this particular case.
7463 if Is_Child_Unit
(E
)
7464 and then not Comes_From_Source
(Entity
(Prefix
(Gen_Id
)))
7465 and then (not In_Instance
7466 or else Nkind
(Parent
(Parent
(Gen_Id
))) =
7470 ("prefix of generic child unit must be instance of parent",
7474 if not In_Open_Scopes
(Inst_Par
)
7475 and then Nkind
(Parent
(Gen_Id
)) not in
7476 N_Generic_Renaming_Declaration
7478 Install_Parent
(Inst_Par
);
7479 Parent_Installed
:= True;
7481 elsif In_Open_Scopes
(Inst_Par
) then
7483 -- If the parent is already installed, install the actuals
7484 -- for its formal packages. This is necessary when the child
7485 -- instance is a child of the parent instance: in this case,
7486 -- the parent is placed on the scope stack but the formal
7487 -- packages are not made visible.
7489 Install_Formal_Packages
(Inst_Par
);
7493 -- If the generic parent does not contain an entity that
7494 -- corresponds to the selector, the instance doesn't either.
7495 -- Analyzing the node will yield the appropriate error message.
7496 -- If the entity is not a child unit, then it is an inner
7497 -- generic in the parent.
7505 if Is_Child_Unit
(Entity
(Gen_Id
))
7507 Nkind
(Parent
(Gen_Id
)) not in N_Generic_Renaming_Declaration
7508 and then not In_Open_Scopes
(Inst_Par
)
7510 Install_Parent
(Inst_Par
);
7511 Parent_Installed
:= True;
7513 -- The generic unit may be the renaming of the implicit child
7514 -- present in an instance. In that case the parent instance is
7515 -- obtained from the name of the renamed entity.
7517 elsif Ekind
(Entity
(Gen_Id
)) = E_Generic_Package
7518 and then Present
(Renamed_Entity
(Entity
(Gen_Id
)))
7519 and then Is_Child_Unit
(Renamed_Entity
(Entity
(Gen_Id
)))
7522 Renamed_Package
: constant Node_Id
:=
7523 Name
(Parent
(Entity
(Gen_Id
)));
7525 if Nkind
(Renamed_Package
) = N_Expanded_Name
then
7526 Inst_Par
:= Entity
(Prefix
(Renamed_Package
));
7527 Install_Parent
(Inst_Par
);
7528 Parent_Installed
:= True;
7534 elsif Nkind
(Gen_Id
) = N_Expanded_Name
then
7536 -- Entity already present, analyze prefix, whose meaning may be an
7537 -- instance in the current context. If it is an instance of a
7538 -- relative within another, the proper parent may still have to be
7539 -- installed, if they are not of the same generation.
7541 Analyze
(Prefix
(Gen_Id
));
7543 -- Prevent cascaded errors
7545 if Etype
(Prefix
(Gen_Id
)) = Any_Type
then
7549 -- In the unlikely case that a local declaration hides the name of
7550 -- the parent package, locate it on the homonym chain. If the context
7551 -- is an instance of the parent, the renaming entity is flagged as
7554 Inst_Par
:= Entity
(Prefix
(Gen_Id
));
7555 while Present
(Inst_Par
)
7556 and then not Is_Package_Or_Generic_Package
(Inst_Par
)
7558 Inst_Par
:= Homonym
(Inst_Par
);
7561 pragma Assert
(Present
(Inst_Par
));
7562 Set_Entity
(Prefix
(Gen_Id
), Inst_Par
);
7564 if In_Enclosing_Instance
then
7567 elsif Present
(Entity
(Gen_Id
))
7568 and then No
(Renamed_Entity
(Entity
(Gen_Id
)))
7569 and then Is_Child_Unit
(Entity
(Gen_Id
))
7570 and then not In_Open_Scopes
(Inst_Par
)
7572 Install_Parent
(Inst_Par
);
7573 Parent_Installed
:= True;
7575 -- Handle renaming of generic child unit
7577 elsif Present
(Entity
(Gen_Id
))
7578 and then Present
(Renamed_Entity
(Entity
(Gen_Id
)))
7579 and then Is_Child_Unit
(Renamed_Entity
(Entity
(Gen_Id
)))
7586 -- The entity of the renamed generic child unit does not
7587 -- have any reference to the instantiated parent. In order to
7588 -- locate it we traverse the scope containing the renaming
7589 -- declaration; the instance of the parent is available in
7590 -- the prefix of the renaming declaration. For example:
7593 -- package Inst_Par is new ...
7594 -- generic package Ren_Child renames Ins_Par.Child;
7599 -- package Inst_Child is new A.Ren_Child;
7602 E
:= First_Entity
(Entity
(Prefix
(Gen_Id
)));
7603 while Present
(E
) loop
7604 if not Is_Object
(E
)
7605 and then Present
(Renamed_Entity
(E
))
7607 Renamed_Entity
(E
) = Renamed_Entity
(Entity
(Gen_Id
))
7609 Ren_Decl
:= Parent
(E
);
7610 Inst_Par
:= Entity
(Prefix
(Name
(Ren_Decl
)));
7612 if not In_Open_Scopes
(Inst_Par
) then
7613 Install_Parent
(Inst_Par
);
7614 Parent_Installed
:= True;
7620 E
:= Next_Entity
(E
);
7625 elsif In_Enclosing_Instance
then
7627 -- The child unit is found in some enclosing scope
7634 -- If this is the renaming of the implicit child in a parent
7635 -- instance, recover the parent name and install it.
7637 if Is_Entity_Name
(Gen_Id
) then
7638 E
:= Entity
(Gen_Id
);
7640 if Is_Generic_Unit
(E
)
7641 and then Nkind
(Parent
(E
)) in N_Generic_Renaming_Declaration
7642 and then Is_Child_Unit
(Renamed_Entity
(E
))
7643 and then Is_Generic_Unit
(Scope
(Renamed_Entity
(E
)))
7644 and then Nkind
(Name
(Parent
(E
))) = N_Expanded_Name
7646 Rewrite
(Gen_Id
, New_Copy_Tree
(Name
(Parent
(E
))));
7647 Inst_Par
:= Entity
(Prefix
(Gen_Id
));
7649 if not In_Open_Scopes
(Inst_Par
) then
7650 Install_Parent
(Inst_Par
);
7651 Parent_Installed
:= True;
7654 -- If it is a child unit of a non-generic parent, it may be
7655 -- use-visible and given by a direct name. Install parent as
7658 elsif Is_Generic_Unit
(E
)
7659 and then Is_Child_Unit
(E
)
7661 Nkind
(Parent
(Gen_Id
)) not in N_Generic_Renaming_Declaration
7662 and then not Is_Generic_Unit
(Scope
(E
))
7664 if not In_Open_Scopes
(Scope
(E
)) then
7665 Install_Parent
(Scope
(E
));
7666 Parent_Installed
:= True;
7671 end Check_Generic_Child_Unit
;
7673 -----------------------------
7674 -- Check_Hidden_Child_Unit --
7675 -----------------------------
7677 procedure Check_Hidden_Child_Unit
7679 Gen_Unit
: Entity_Id
;
7680 Act_Decl_Id
: Entity_Id
)
7682 Gen_Id
: constant Node_Id
:= Name
(N
);
7685 if Is_Child_Unit
(Gen_Unit
)
7686 and then Is_Child_Unit
(Act_Decl_Id
)
7687 and then Nkind
(Gen_Id
) = N_Expanded_Name
7688 and then Entity
(Prefix
(Gen_Id
)) = Scope
(Act_Decl_Id
)
7689 and then Chars
(Gen_Unit
) = Chars
(Act_Decl_Id
)
7691 Error_Msg_Node_2
:= Scope
(Act_Decl_Id
);
7693 ("generic unit & is implicitly declared in &",
7694 Defining_Unit_Name
(N
), Gen_Unit
);
7695 Error_Msg_N
("\instance must have different name",
7696 Defining_Unit_Name
(N
));
7698 end Check_Hidden_Child_Unit
;
7700 ------------------------
7701 -- Check_Private_View --
7702 ------------------------
7704 procedure Check_Private_View
(N
: Node_Id
) is
7705 Typ
: constant Entity_Id
:= Etype
(N
);
7707 procedure Check_Private_Type
(T
: Entity_Id
; Private_View
: Boolean);
7708 -- Check that the available view of T matches Private_View and, if not,
7709 -- switch the view of T or of its base type.
7711 procedure Check_Private_Type
(T
: Entity_Id
; Private_View
: Boolean) is
7712 BT
: constant Entity_Id
:= Base_Type
(T
);
7715 -- If the full declaration was not visible in the generic, stop here
7717 if Private_View
then
7721 -- Exchange views if the type was not private in the generic but is
7722 -- private at the point of instantiation. Do not exchange views if
7723 -- the scope of the type is in scope. This can happen if both generic
7724 -- and instance are sibling units, or if type is defined in a parent.
7725 -- In this case the visibility of the type will be correct for all
7728 if Is_Private_Type
(T
)
7729 and then Present
(Full_View
(T
))
7730 and then not In_Open_Scopes
(Scope
(T
))
7734 -- Finally, a nonprivate subtype may have a private base type, which
7735 -- must be exchanged for consistency. This can happen when a package
7736 -- body is instantiated, when the scope stack is empty but in fact
7737 -- the subtype and the base type are declared in an enclosing scope.
7739 -- Note that in this case we introduce an inconsistency in the view
7740 -- set, because we switch the base type BT, but there could be some
7741 -- private dependent subtypes of BT which remain unswitched. Such
7742 -- subtypes might need to be switched at a later point (see specific
7743 -- provision for that case in Switch_View).
7745 elsif not Is_Private_Type
(T
)
7746 and then Is_Private_Type
(BT
)
7747 and then Present
(Full_View
(BT
))
7748 and then not In_Open_Scopes
(BT
)
7750 Prepend_Elmt
(Full_View
(BT
), Exchanged_Views
);
7751 Exchange_Declarations
(BT
);
7753 end Check_Private_Type
;
7756 if Present
(Typ
) then
7757 -- If the type appears in a subtype declaration, the subtype in
7758 -- instance must have a view compatible with that of its parent,
7759 -- which must be exchanged (see corresponding code in Restore_
7760 -- Private_Views) so we make an exception to the open scope rule
7761 -- implemented by Check_Private_Type above.
7763 if Has_Private_View
(N
)
7764 and then not Is_Private_Type
(Typ
)
7765 and then not Has_Been_Exchanged
(Typ
)
7766 and then (not In_Open_Scopes
(Scope
(Typ
))
7767 or else Nkind
(Parent
(N
)) = N_Subtype_Declaration
)
7769 -- In the generic, only the private declaration was visible
7771 Prepend_Elmt
(Typ
, Exchanged_Views
);
7772 Exchange_Declarations
(Etype
(Get_Associated_Node
(N
)));
7774 -- Check that the available views of Typ match their respective flag.
7775 -- Note that the type of a visible discriminant is never private.
7778 Check_Private_Type
(Typ
, Has_Private_View
(N
));
7780 if Is_Access_Type
(Typ
) then
7782 (Designated_Type
(Typ
), Has_Secondary_Private_View
(N
));
7784 elsif Is_Array_Type
(Typ
) then
7786 (Component_Type_For_Private_View
(Typ
),
7787 Has_Secondary_Private_View
(N
));
7789 elsif (Is_Record_Type
(Typ
) or else Is_Concurrent_Type
(Typ
))
7790 and then Has_Discriminants
(Typ
)
7796 Disc
:= First_Discriminant
(Typ
);
7797 while Present
(Disc
) loop
7798 Check_Private_Type
(Etype
(Disc
), False);
7799 Next_Discriminant
(Disc
);
7805 end Check_Private_View
;
7807 -----------------------------
7808 -- Check_Hidden_Primitives --
7809 -----------------------------
7811 function Check_Hidden_Primitives
(Assoc_List
: List_Id
) return Elist_Id
is
7814 Result
: Elist_Id
:= No_Elist
;
7817 if No
(Assoc_List
) then
7821 -- Traverse the list of associations between formals and actuals
7822 -- searching for renamings of tagged types
7824 Actual
:= First
(Assoc_List
);
7825 while Present
(Actual
) loop
7826 if Nkind
(Actual
) = N_Subtype_Declaration
then
7827 Gen_T
:= Generic_Parent_Type
(Actual
);
7829 if Present
(Gen_T
) and then Is_Tagged_Type
(Gen_T
) then
7831 -- Traverse the list of primitives of the actual types
7832 -- searching for hidden primitives that are visible in the
7833 -- corresponding generic formal; leave them visible and
7834 -- append them to Result to restore their decoration later.
7836 Install_Hidden_Primitives
7837 (Prims_List
=> Result
,
7839 Act_T
=> Entity
(Subtype_Indication
(Actual
)));
7847 end Check_Hidden_Primitives
;
7849 -------------------------------------
7850 -- Component_Type_For_Private_View --
7851 -------------------------------------
7853 function Component_Type_For_Private_View
(T
: Entity_Id
) return Entity_Id
is
7854 Typ
: constant Entity_Id
:= Component_Type
(T
);
7857 if Is_Array_Type
(Typ
) and then not Has_Private_Declaration
(Typ
) then
7858 return Component_Type_For_Private_View
(Typ
);
7862 end Component_Type_For_Private_View
;
7864 --------------------------
7865 -- Contains_Instance_Of --
7866 --------------------------
7868 function Contains_Instance_Of
7871 N
: Node_Id
) return Boolean
7879 -- Verify that there are no circular instantiations. We check whether
7880 -- the unit contains an instance of the current scope or some enclosing
7881 -- scope (in case one of the instances appears in a subunit). Longer
7882 -- circularities involving subunits might seem too pathological to
7883 -- consider, but they were not too pathological for the authors of
7884 -- DEC bc30vsq, so we loop over all enclosing scopes, and mark all
7885 -- enclosing generic scopes as containing an instance.
7888 -- Within a generic subprogram body, the scope is not generic, to
7889 -- allow for recursive subprograms. Use the declaration to determine
7890 -- whether this is a generic unit.
7892 if Ekind
(Scop
) = E_Generic_Package
7893 or else (Is_Subprogram
(Scop
)
7894 and then Nkind
(Unit_Declaration_Node
(Scop
)) =
7895 N_Generic_Subprogram_Declaration
)
7897 Elmt
:= First_Elmt
(Inner_Instances
(Inner
));
7899 while Present
(Elmt
) loop
7900 if Node
(Elmt
) = Scop
then
7901 Error_Msg_Node_2
:= Inner
;
7903 ("circular instantiation: & instantiated within &!",
7907 elsif Node
(Elmt
) = Inner
then
7910 elsif Contains_Instance_Of
(Node
(Elmt
), Scop
, N
) then
7911 Error_Msg_Node_2
:= Inner
;
7913 ("circular instantiation: & instantiated within &!",
7921 -- Indicate that Inner is being instantiated within Scop
7923 Append_Elmt
(Inner
, Inner_Instances
(Scop
));
7926 if Scop
= Standard_Standard
then
7929 Scop
:= Scope
(Scop
);
7934 end Contains_Instance_Of
;
7936 -----------------------
7937 -- Copy_Generic_Node --
7938 -----------------------
7940 function Copy_Generic_Node
7942 Parent_Id
: Node_Id
;
7943 Instantiating
: Boolean) return Node_Id
7948 function Copy_Generic_Descendant
(D
: Union_Id
) return Union_Id
;
7949 -- Check the given value of one of the Fields referenced by the current
7950 -- node to determine whether to copy it recursively. The field may hold
7951 -- a Node_Id, a List_Id, or an Elist_Id, or a plain value (Sloc, Uint,
7952 -- Char) in which case it need not be copied.
7954 procedure Copy_Descendants
;
7955 -- Common utility for various nodes
7957 function Copy_Generic_Elist
(E
: Elist_Id
) return Elist_Id
;
7958 -- Make copy of element list
7960 function Copy_Generic_List
7962 Parent_Id
: Node_Id
) return List_Id
;
7963 -- Apply Copy_Generic_Node recursively to the members of a node list
7965 function In_Defining_Unit_Name
(Nam
: Node_Id
) return Boolean;
7966 -- True if an identifier is part of the defining program unit name of
7968 -- Consider removing this subprogram now that ASIS no longer uses it.
7970 ----------------------
7971 -- Copy_Descendants --
7972 ----------------------
7974 procedure Copy_Descendants
is
7975 procedure Walk
is new
7976 Walk_Sinfo_Fields_Pairwise
(Copy_Generic_Descendant
);
7979 end Copy_Descendants
;
7981 -----------------------------
7982 -- Copy_Generic_Descendant --
7983 -----------------------------
7985 function Copy_Generic_Descendant
(D
: Union_Id
) return Union_Id
is
7987 if D
= Union_Id
(Empty
) then
7990 elsif D
in Node_Range
then
7992 (Copy_Generic_Node
(Node_Id
(D
), New_N
, Instantiating
));
7994 elsif D
in List_Range
then
7995 return Union_Id
(Copy_Generic_List
(List_Id
(D
), New_N
));
7997 elsif D
in Elist_Range
then
7998 return Union_Id
(Copy_Generic_Elist
(Elist_Id
(D
)));
8000 -- Nothing else is copyable (e.g. Uint values), return as is
8005 end Copy_Generic_Descendant
;
8007 ------------------------
8008 -- Copy_Generic_Elist --
8009 ------------------------
8011 function Copy_Generic_Elist
(E
: Elist_Id
) return Elist_Id
is
8018 M
:= First_Elmt
(E
);
8019 while Present
(M
) loop
8021 (Copy_Generic_Node
(Node
(M
), Empty
, Instantiating
), L
);
8030 end Copy_Generic_Elist
;
8032 -----------------------
8033 -- Copy_Generic_List --
8034 -----------------------
8036 function Copy_Generic_List
8038 Parent_Id
: Node_Id
) return List_Id
8046 Set_Parent
(New_L
, Parent_Id
);
8049 while Present
(N
) loop
8050 Append
(Copy_Generic_Node
(N
, Empty
, Instantiating
), New_L
);
8059 end Copy_Generic_List
;
8061 ---------------------------
8062 -- In_Defining_Unit_Name --
8063 ---------------------------
8065 function In_Defining_Unit_Name
(Nam
: Node_Id
) return Boolean is
8068 Present
(Parent
(Nam
))
8069 and then (Nkind
(Parent
(Nam
)) = N_Defining_Program_Unit_Name
8071 (Nkind
(Parent
(Nam
)) = N_Expanded_Name
8072 and then In_Defining_Unit_Name
(Parent
(Nam
))));
8073 end In_Defining_Unit_Name
;
8075 -- Start of processing for Copy_Generic_Node
8082 New_N
:= New_Copy
(N
);
8084 -- Copy aspects if present
8086 if Has_Aspects
(N
) then
8087 Set_Has_Aspects
(New_N
, False);
8088 Set_Aspect_Specifications
8089 (New_N
, Copy_Generic_List
(Aspect_Specifications
(N
), Parent_Id
));
8092 -- If we are instantiating, we want to adjust the sloc based on the
8093 -- current S_Adjustment. However, if this is the root node of a subunit,
8094 -- we need to defer that adjustment to below (see "elsif Instantiating
8095 -- and Was_Stub"), so it comes after Create_Instantiation_Source has
8096 -- computed the adjustment.
8099 and then not (Nkind
(N
) in N_Proper_Body
8100 and then Was_Originally_Stub
(N
))
8102 Adjust_Instantiation_Sloc
(New_N
, S_Adjustment
);
8105 if not Is_List_Member
(N
) then
8106 Set_Parent
(New_N
, Parent_Id
);
8109 -- Special casing for identifiers and other entity names and operators
8111 if Nkind
(N
) in N_Character_Literal
8117 if not Instantiating
then
8119 -- Link both nodes in order to assign subsequently the entity of
8120 -- the copy to the original node, in case this is a global
8123 Set_Associated_Node
(N
, New_N
);
8125 -- If we are within an instantiation, this is a nested generic
8126 -- that has already been analyzed at the point of definition.
8127 -- We must preserve references that were global to the enclosing
8128 -- parent at that point. Other occurrences, whether global or
8129 -- local to the current generic, must be resolved anew, so we
8130 -- reset the entity in the generic copy. A global reference has a
8131 -- smaller depth than the parent, or else the same depth in case
8132 -- both are distinct compilation units.
8134 -- A child unit is implicitly declared within the enclosing parent
8135 -- but is in fact global to it, and must be preserved.
8137 -- It is also possible for Current_Instantiated_Parent to be
8138 -- defined, and for this not to be a nested generic, namely if
8139 -- the unit is loaded through Rtsfind. In that case, the entity of
8140 -- New_N is only a link to the associated node, and not a defining
8143 -- The entities for parent units in the defining_program_unit of a
8144 -- generic child unit are established when the context of the unit
8145 -- is first analyzed, before the generic copy is made. They are
8146 -- preserved in the copy for use in e.g. ASIS queries.
8148 Ent
:= Entity
(New_N
);
8150 if No
(Current_Instantiated_Parent
.Gen_Id
) then
8152 or else Nkind
(Ent
) /= N_Defining_Identifier
8153 or else not In_Defining_Unit_Name
(N
)
8155 Set_Associated_Node
(New_N
, Empty
);
8159 or else Nkind
(Ent
) not in N_Entity
8160 or else No
(Scope
(Ent
))
8162 (Scope
(Ent
) = Current_Instantiated_Parent
.Gen_Id
8163 and then not Is_Child_Unit
(Ent
))
8165 (Scope_Depth_Set
(Scope
(Ent
))
8167 Scope_Depth
(Scope
(Ent
)) >
8168 Scope_Depth
(Current_Instantiated_Parent
.Gen_Id
)
8170 Get_Source_Unit
(Ent
) =
8171 Get_Source_Unit
(Current_Instantiated_Parent
.Gen_Id
))
8173 Set_Associated_Node
(New_N
, Empty
);
8176 -- Case of instantiating identifier or some other name or operator
8179 -- If the associated node is still defined, the entity in it
8180 -- is global, and must be copied to the instance. If this copy
8181 -- is being made for a body to inline, it is applied to an
8182 -- instantiated tree, and the entity is already present and
8183 -- must be also preserved.
8186 Assoc
: constant Node_Id
:= Get_Associated_Node
(N
);
8189 if Present
(Assoc
) then
8190 if Nkind
(Assoc
) = Nkind
(N
) then
8191 Set_Entity
(New_N
, Entity
(Assoc
));
8192 Check_Private_View
(N
);
8194 -- For the comparison and equality operators, the Etype
8195 -- of the operator does not provide any information so,
8196 -- if one of the operands is of a universal type, we need
8197 -- to manually restore the full view of private types.
8199 if Nkind
(N
) in N_Op_Eq
8206 if Yields_Universal_Type
(Left_Opnd
(Assoc
)) then
8207 if Present
(Etype
(Right_Opnd
(Assoc
)))
8209 Is_Private_Type
(Etype
(Right_Opnd
(Assoc
)))
8211 Switch_View
(Etype
(Right_Opnd
(Assoc
)));
8214 elsif Yields_Universal_Type
(Right_Opnd
(Assoc
)) then
8215 if Present
(Etype
(Left_Opnd
(Assoc
)))
8217 Is_Private_Type
(Etype
(Left_Opnd
(Assoc
)))
8219 Switch_View
(Etype
(Left_Opnd
(Assoc
)));
8224 -- The node is a reference to a global type and acts as the
8225 -- subtype mark of a qualified expression created in order
8226 -- to aid resolution of accidental overloading in instances.
8227 -- Since N is a reference to a type, the Associated_Node of
8228 -- N denotes an entity rather than another identifier. See
8229 -- Qualify_Universal_Operands for details.
8231 elsif Nkind
(N
) = N_Identifier
8232 and then Nkind
(Parent
(N
)) = N_Qualified_Expression
8233 and then Subtype_Mark
(Parent
(N
)) = N
8234 and then Is_Qualified_Universal_Literal
(Parent
(N
))
8236 Set_Entity
(New_N
, Assoc
);
8238 -- Cope with the rewriting into expanded name that may have
8239 -- occurred in between, e.g. in Check_Generic_Child_Unit for
8240 -- generic renaming declarations.
8242 elsif Nkind
(Assoc
) = N_Expanded_Name
then
8243 Rewrite
(N
, New_Copy_Tree
(Assoc
));
8244 Set_Associated_Node
(N
, Assoc
);
8245 return Copy_Generic_Node
(N
, Parent_Id
, Instantiating
);
8247 -- The name in the call may be a selected component if the
8248 -- call has not been analyzed yet, as may be the case for
8249 -- pre/post conditions in a generic unit.
8251 elsif Nkind
(Assoc
) = N_Function_Call
8252 and then Is_Entity_Name
(Name
(Assoc
))
8254 Set_Entity
(New_N
, Entity
(Name
(Assoc
)));
8255 Check_Private_View
(N
);
8257 elsif Nkind
(Assoc
) in N_Entity
8258 and then (Expander_Active
8259 or else (GNATprove_Mode
8260 and then not In_Spec_Expression
8261 and then not Inside_A_Generic
))
8263 -- Inlining case: we are copying a tree that contains
8264 -- global entities, which are preserved in the copy to be
8265 -- used for subsequent inlining.
8270 Set_Entity
(New_N
, Empty
);
8276 -- For expanded name, we must copy the Prefix and Selector_Name
8278 if Nkind
(N
) = N_Expanded_Name
then
8280 (New_N
, Copy_Generic_Node
(Prefix
(N
), New_N
, Instantiating
));
8282 Set_Selector_Name
(New_N
,
8283 Copy_Generic_Node
(Selector_Name
(N
), New_N
, Instantiating
));
8285 -- For operators, copy the operands
8287 elsif Nkind
(N
) in N_Op
then
8288 if Nkind
(N
) in N_Binary_Op
then
8289 Set_Left_Opnd
(New_N
,
8290 Copy_Generic_Node
(Left_Opnd
(N
), New_N
, Instantiating
));
8293 Set_Right_Opnd
(New_N
,
8294 Copy_Generic_Node
(Right_Opnd
(N
), New_N
, Instantiating
));
8297 -- Establish a link between an entity from the generic template and the
8298 -- corresponding entity in the generic copy to be analyzed.
8300 elsif Nkind
(N
) in N_Entity
then
8301 if not Instantiating
then
8302 Set_Associated_Entity
(N
, New_N
);
8305 -- Clear any existing link the copy may inherit from the replicated
8306 -- generic template entity.
8308 Set_Associated_Entity
(New_N
, Empty
);
8310 -- Special casing for stubs
8312 elsif Nkind
(N
) in N_Body_Stub
then
8314 -- In any case, we must copy the specification or defining
8315 -- identifier as appropriate.
8317 if Nkind
(N
) = N_Subprogram_Body_Stub
then
8318 Set_Specification
(New_N
,
8319 Copy_Generic_Node
(Specification
(N
), New_N
, Instantiating
));
8322 Set_Defining_Identifier
(New_N
,
8324 (Defining_Identifier
(N
), New_N
, Instantiating
));
8327 -- If we are not instantiating, then this is where we load and
8328 -- analyze subunits, i.e. at the point where the stub occurs. A
8329 -- more permissive system might defer this analysis to the point
8330 -- of instantiation, but this seems too complicated for now.
8332 if not Instantiating
then
8334 Subunit_Name
: constant Unit_Name_Type
:= Get_Unit_Name
(N
);
8336 Unum
: Unit_Number_Type
;
8340 -- Make sure that, if it is a subunit of the main unit that is
8341 -- preprocessed and if -gnateG is specified, the preprocessed
8342 -- file will be written.
8344 Lib
.Analysing_Subunit_Of_Main
:=
8345 Lib
.In_Extended_Main_Source_Unit
(N
);
8348 (Load_Name
=> Subunit_Name
,
8352 Lib
.Analysing_Subunit_Of_Main
:= False;
8354 -- If the proper body is not found, a warning message will be
8355 -- emitted when analyzing the stub, or later at the point of
8356 -- instantiation. Here we just leave the stub as is.
8358 if Unum
= No_Unit
then
8359 Subunits_Missing
:= True;
8360 goto Subunit_Not_Found
;
8363 Subunit
:= Cunit
(Unum
);
8365 if Nkind
(Unit
(Subunit
)) /= N_Subunit
then
8367 ("found child unit instead of expected SEPARATE subunit",
8369 Error_Msg_Sloc
:= Sloc
(N
);
8370 Error_Msg_N
("\to complete stub #", Subunit
);
8371 goto Subunit_Not_Found
;
8374 -- We must create a generic copy of the subunit, in order to
8375 -- perform semantic analysis on it, and we must replace the
8376 -- stub in the original generic unit with the subunit, in order
8377 -- to preserve non-local references within.
8379 -- Only the proper body needs to be copied. Library_Unit and
8380 -- context clause are simply inherited by the generic copy.
8381 -- Note that the copy (which may be recursive if there are
8382 -- nested subunits) must be done first, before attaching it to
8383 -- the enclosing generic.
8387 (Proper_Body
(Unit
(Subunit
)),
8388 Empty
, Instantiating
=> False);
8390 -- Now place the original proper body in the original generic
8391 -- unit. This is a body, not a compilation unit.
8393 Rewrite
(N
, Proper_Body
(Unit
(Subunit
)));
8394 Set_Is_Compilation_Unit
(Defining_Entity
(N
), False);
8395 Set_Was_Originally_Stub
(N
);
8397 -- Finally replace the body of the subunit with its copy, and
8398 -- make this new subunit into the library unit of the generic
8399 -- copy, which does not have stubs any longer.
8401 Set_Proper_Body
(Unit
(Subunit
), New_Body
);
8402 Set_Library_Unit
(New_N
, Subunit
);
8403 Inherit_Context
(Unit
(Subunit
), N
);
8406 -- If we are instantiating, this must be an error case, since
8407 -- otherwise we would have replaced the stub node by the proper body
8408 -- that corresponds. So just ignore it in the copy (i.e. we have
8409 -- copied it, and that is good enough).
8415 <<Subunit_Not_Found
>> null;
8417 -- If the node is a compilation unit, it is the subunit of a stub, which
8418 -- has been loaded already (see code below). In this case, the library
8419 -- unit field of N points to the parent unit (which is a compilation
8420 -- unit) and need not (and cannot) be copied.
8422 -- When the proper body of the stub is analyzed, the library_unit link
8423 -- is used to establish the proper context (see sem_ch10).
8425 -- The other fields of a compilation unit are copied as usual
8427 elsif Nkind
(N
) = N_Compilation_Unit
then
8429 -- This code can only be executed when not instantiating, because in
8430 -- the copy made for an instantiation, the compilation unit node has
8431 -- disappeared at the point that a stub is replaced by its proper
8434 pragma Assert
(not Instantiating
);
8436 Set_Context_Items
(New_N
,
8437 Copy_Generic_List
(Context_Items
(N
), New_N
));
8440 Copy_Generic_Node
(Unit
(N
), New_N
, Instantiating
=> False));
8442 Set_First_Inlined_Subprogram
(New_N
,
8444 (First_Inlined_Subprogram
(N
), New_N
, Instantiating
=> False));
8449 (Aux_Decls_Node
(N
), New_N
, Instantiating
=> False));
8451 -- For an assignment node, the assignment is known to be semantically
8452 -- legal if we are instantiating the template. This avoids incorrect
8453 -- diagnostics in generated code.
8455 elsif Nkind
(N
) = N_Assignment_Statement
then
8457 -- Copy name and expression fields in usual manner
8460 Copy_Generic_Node
(Name
(N
), New_N
, Instantiating
));
8462 Set_Expression
(New_N
,
8463 Copy_Generic_Node
(Expression
(N
), New_N
, Instantiating
));
8465 if Instantiating
then
8466 Set_Assignment_OK
(Name
(New_N
), True);
8469 elsif Nkind
(N
) in N_Aggregate | N_Extension_Aggregate
then
8470 if not Instantiating
then
8471 Set_Associated_Node
(N
, New_N
);
8474 if Present
(Get_Associated_Node
(N
))
8475 and then Nkind
(Get_Associated_Node
(N
)) = Nkind
(N
)
8477 -- In the generic the aggregate has some composite type. If at
8478 -- the point of instantiation the type has a private view,
8479 -- install the full view (and that of its ancestors, if any).
8482 T
: Entity_Id
:= Etype
(Get_Associated_Node
(N
));
8486 if Present
(T
) and then Is_Private_Type
(T
) then
8491 and then Is_Tagged_Type
(T
)
8492 and then Is_Derived_Type
(T
)
8494 Rt
:= Root_Type
(T
);
8499 if Is_Private_Type
(T
) then
8510 -- Do not copy the associated node, which points to the generic copy
8511 -- of the aggregate.
8513 if Nkind
(N
) = N_Aggregate
then
8514 Set_Aggregate_Bounds
8516 Node_Id
(Copy_Generic_Descendant
8517 (Union_Id
(Aggregate_Bounds
(N
)))));
8519 elsif Nkind
(N
) = N_Extension_Aggregate
then
8522 Node_Id
(Copy_Generic_Descendant
8523 (Union_Id
(Ancestor_Part
(N
)))));
8526 pragma Assert
(False);
8531 List_Id
(Copy_Generic_Descendant
(Union_Id
(Expressions
(N
)))));
8532 Set_Component_Associations
8534 List_Id
(Copy_Generic_Descendant
8535 (Union_Id
(Component_Associations
(N
)))));
8537 (New_N
, Node_Id
(Copy_Generic_Descendant
(Union_Id
(Etype
(N
)))));
8539 -- Allocators do not have an identifier denoting the access type, so we
8540 -- must locate it through the expression to check whether the views are
8543 elsif Nkind
(N
) = N_Allocator
8544 and then Nkind
(Expression
(N
)) = N_Qualified_Expression
8545 and then Is_Entity_Name
(Subtype_Mark
(Expression
(N
)))
8546 and then Instantiating
8549 T
: constant Node_Id
:=
8550 Get_Associated_Node
(Subtype_Mark
(Expression
(N
)));
8556 -- Retrieve the allocator node in the generic copy
8558 Acc_T
:= Etype
(Parent
(Parent
(T
)));
8560 if Present
(Acc_T
) and then Is_Private_Type
(Acc_T
) then
8561 Switch_View
(Acc_T
);
8568 -- Loop parameter specifications do not have an identifier denoting the
8569 -- index type, so we must locate it through the defining identifier to
8570 -- check whether the views are consistent.
8572 elsif Nkind
(N
) = N_Loop_Parameter_Specification
8573 and then Instantiating
8576 Id
: constant Entity_Id
:=
8577 Get_Associated_Entity
(Defining_Identifier
(N
));
8579 Index_T
: Entity_Id
;
8582 if Present
(Id
) and then Present
(Etype
(Id
)) then
8583 Index_T
:= First_Subtype
(Etype
(Id
));
8585 if Present
(Index_T
) and then Is_Private_Type
(Index_T
) then
8586 Switch_View
(Index_T
);
8593 -- For a proper body, we must catch the case of a proper body that
8594 -- replaces a stub. This represents the point at which a separate
8595 -- compilation unit, and hence template file, may be referenced, so we
8596 -- must make a new source instantiation entry for the template of the
8597 -- subunit, and ensure that all nodes in the subunit are adjusted using
8598 -- this new source instantiation entry.
8600 elsif Nkind
(N
) in N_Proper_Body
then
8602 Save_Adjustment
: constant Sloc_Adjustment
:= S_Adjustment
;
8604 if Instantiating
and then Was_Originally_Stub
(N
) then
8605 Create_Instantiation_Source
8606 (Instantiation_Node
,
8607 Defining_Entity
(N
),
8610 Adjust_Instantiation_Sloc
(New_N
, S_Adjustment
);
8613 -- Now copy the fields of the proper body, using the new
8614 -- adjustment factor if one was needed as per test above.
8618 -- Restore the original adjustment factor
8620 S_Adjustment
:= Save_Adjustment
;
8623 elsif Nkind
(N
) = N_Pragma
and then Instantiating
then
8625 -- Do not copy Comment or Ident pragmas their content is relevant to
8626 -- the generic unit, not to the instantiating unit.
8628 if Pragma_Name_Unmapped
(N
) in Name_Comment | Name_Ident
then
8629 New_N
:= Make_Null_Statement
(Sloc
(N
));
8631 -- Do not copy pragmas generated from aspects because the pragmas do
8632 -- not carry any semantic information, plus they will be regenerated
8635 -- However, generating C we need to copy them since postconditions
8636 -- are inlined by the front end, and the front-end inlining machinery
8637 -- relies on this routine to perform inlining.
8639 elsif From_Aspect_Specification
(N
)
8640 and then not Modify_Tree_For_C
8642 New_N
:= Make_Null_Statement
(Sloc
(N
));
8648 elsif Nkind
(N
) in N_Integer_Literal | N_Real_Literal
then
8650 -- No descendant fields need traversing
8654 elsif Nkind
(N
) = N_String_Literal
8655 and then Present
(Etype
(N
))
8656 and then Instantiating
8658 -- If the string is declared in an outer scope, the string_literal
8659 -- subtype created for it may have the wrong scope. Force reanalysis
8660 -- of the constant to generate a new itype in the proper context.
8662 Set_Etype
(New_N
, Empty
);
8663 Set_Analyzed
(New_N
, False);
8665 -- For the remaining nodes, copy their descendants recursively
8670 if Instantiating
and then Nkind
(N
) = N_Subprogram_Body
then
8671 Set_Generic_Parent
(Specification
(New_N
), N
);
8673 -- Should preserve Corresponding_Spec??? (12.3(14))
8677 -- Propagate dimensions if present, so that they are reflected in the
8680 if Nkind
(N
) in N_Has_Etype
8681 and then (Nkind
(N
) in N_Op
or else Is_Entity_Name
(N
))
8682 and then Present
(Etype
(N
))
8683 and then Is_Floating_Point_Type
(Etype
(N
))
8684 and then Has_Dimension_System
(Etype
(N
))
8686 Copy_Dimensions
(N
, New_N
);
8690 end Copy_Generic_Node
;
8692 ----------------------------
8693 -- Denotes_Formal_Package --
8694 ----------------------------
8696 function Denotes_Formal_Package
8698 On_Exit
: Boolean := False;
8699 Instance
: Entity_Id
:= Empty
) return Boolean
8702 Scop
: constant Entity_Id
:= Scope
(Pack
);
8705 function Is_Actual_Of_Previous_Formal
(P
: Entity_Id
) return Boolean;
8706 -- The package in question may be an actual for a previous formal
8707 -- package P of the current instance, so examine its actuals as well.
8708 -- This must be recursive over other formal packages.
8710 ----------------------------------
8711 -- Is_Actual_Of_Previous_Formal --
8712 ----------------------------------
8714 function Is_Actual_Of_Previous_Formal
(P
: Entity_Id
) return Boolean is
8718 E1
:= First_Entity
(P
);
8719 while Present
(E1
) and then E1
/= Instance
loop
8720 if Ekind
(E1
) = E_Package
8721 and then Nkind
(Parent
(E1
)) = N_Package_Renaming_Declaration
8723 if Renamed_Entity
(E1
) = Pack
then
8726 elsif E1
= P
or else Renamed_Entity
(E1
) = P
then
8729 elsif Is_Actual_Of_Previous_Formal
(E1
) then
8738 end Is_Actual_Of_Previous_Formal
;
8740 -- Start of processing for Denotes_Formal_Package
8746 (Instance_Envs
.Last
).Instantiated_Parent
.Act_Id
;
8748 Par
:= Current_Instantiated_Parent
.Act_Id
;
8751 if Ekind
(Scop
) = E_Generic_Package
8752 or else Nkind
(Unit_Declaration_Node
(Scop
)) =
8753 N_Generic_Subprogram_Declaration
8757 elsif Nkind
(Original_Node
(Unit_Declaration_Node
(Pack
))) =
8758 N_Formal_Package_Declaration
8766 -- Check whether this package is associated with a formal package of
8767 -- the enclosing instantiation. Iterate over the list of renamings.
8769 E
:= First_Entity
(Par
);
8770 while Present
(E
) loop
8771 if Ekind
(E
) /= E_Package
8772 or else Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
8776 elsif Renamed_Entity
(E
) = Par
then
8779 elsif Renamed_Entity
(E
) = Pack
then
8782 elsif Is_Actual_Of_Previous_Formal
(E
) then
8792 end Denotes_Formal_Package
;
8798 procedure End_Generic
is
8800 -- ??? More things could be factored out in this routine. Should
8801 -- probably be done at a later stage.
8803 Inside_A_Generic
:= Generic_Flags
.Table
(Generic_Flags
.Last
);
8804 Generic_Flags
.Decrement_Last
;
8806 Expander_Mode_Restore
;
8813 function Earlier
(N1
, N2
: Node_Id
) return Boolean is
8814 procedure Find_Depth
(P
: in out Node_Id
; D
: in out Integer);
8815 -- Find distance from given node to enclosing compilation unit
8821 procedure Find_Depth
(P
: in out Node_Id
; D
: in out Integer) is
8824 and then Nkind
(P
) /= N_Compilation_Unit
8826 P
:= True_Parent
(P
);
8831 -- Local declarations
8840 -- Start of processing for Earlier
8843 Find_Depth
(P1
, D1
);
8844 Find_Depth
(P2
, D2
);
8854 P1
:= True_Parent
(P1
);
8859 P2
:= True_Parent
(P2
);
8863 -- At this point P1 and P2 are at the same distance from the root.
8864 -- We examine their parents until we find a common declarative list.
8865 -- If we reach the root, N1 and N2 do not descend from the same
8866 -- declarative list (e.g. one is nested in the declarative part and
8867 -- the other is in a block in the statement part) and the earlier
8868 -- one is already frozen.
8870 while not Is_List_Member
(P1
)
8871 or else not Is_List_Member
(P2
)
8872 or else not In_Same_List
(P1
, P2
)
8874 P1
:= True_Parent
(P1
);
8875 P2
:= True_Parent
(P2
);
8877 if Nkind
(Parent
(P1
)) = N_Subunit
then
8878 P1
:= Corresponding_Stub
(Parent
(P1
));
8881 if Nkind
(Parent
(P2
)) = N_Subunit
then
8882 P2
:= Corresponding_Stub
(Parent
(P2
));
8890 -- Expanded code usually shares the source location of the original
8891 -- construct it was generated for. This however may not necessarily
8892 -- reflect the true location of the code within the tree.
8894 -- Before comparing the slocs of the two nodes, make sure that we are
8895 -- working with correct source locations. Assume that P1 is to the left
8896 -- of P2. If either one does not come from source, traverse the common
8897 -- list heading towards the other node and locate the first source
8901 -- ----+===+===+--------------+===+===+----
8902 -- expanded code expanded code
8904 if not Comes_From_Source
(P1
) then
8905 while Present
(P1
) loop
8907 -- Neither P2 nor a source statement were located during the
8908 -- search. If we reach the end of the list, then P1 does not
8909 -- occur earlier than P2.
8912 -- start --- P2 ----- P1 --- end
8914 if No
(Next
(P1
)) then
8917 -- We encounter P2 while going to the right of the list. This
8918 -- means that P1 does indeed appear earlier.
8921 -- start --- P1 ===== P2 --- end
8922 -- expanded code in between
8927 -- No need to look any further since we have located a source
8930 elsif Comes_From_Source
(P1
) then
8940 if not Comes_From_Source
(P2
) then
8941 while Present
(P2
) loop
8943 -- Neither P1 nor a source statement were located during the
8944 -- search. If we reach the start of the list, then P1 does not
8945 -- occur earlier than P2.
8948 -- start --- P2 --- P1 --- end
8950 if No
(Prev
(P2
)) then
8953 -- We encounter P1 while going to the left of the list. This
8954 -- means that P1 does indeed appear earlier.
8957 -- start --- P1 ===== P2 --- end
8958 -- expanded code in between
8963 -- No need to look any further since we have located a source
8966 elsif Comes_From_Source
(P2
) then
8976 -- At this point either both nodes came from source or we approximated
8977 -- their source locations through neighboring source statements.
8979 T1
:= Top_Level_Location
(Sloc
(P1
));
8980 T2
:= Top_Level_Location
(Sloc
(P2
));
8982 -- When two nodes come from the same instance, they have identical top
8983 -- level locations. To determine proper relation within the tree, check
8984 -- their locations within the template.
8987 return Sloc
(P1
) < Sloc
(P2
);
8989 -- The two nodes either come from unrelated instances or do not come
8990 -- from instantiated code at all.
8997 ----------------------
8998 -- Find_Actual_Type --
8999 ----------------------
9001 function Find_Actual_Type
9003 Gen_Type
: Entity_Id
) return Entity_Id
9005 Gen_Scope
: constant Entity_Id
:= Scope
(Gen_Type
);
9009 -- Special processing only applies to child units
9011 if not Is_Child_Unit
(Gen_Scope
) then
9012 return Get_Instance_Of
(Typ
);
9014 -- If designated or component type is itself a formal of the child unit,
9015 -- its instance is available.
9017 elsif Scope
(Typ
) = Gen_Scope
then
9018 return Get_Instance_Of
(Typ
);
9020 -- If the array or access type is not declared in the parent unit,
9021 -- no special processing needed.
9023 elsif not Is_Generic_Type
(Typ
)
9024 and then Scope
(Gen_Scope
) /= Scope
(Typ
)
9026 return Get_Instance_Of
(Typ
);
9028 -- Otherwise, retrieve designated or component type by visibility
9031 T
:= Current_Entity
(Typ
);
9032 while Present
(T
) loop
9033 if In_Open_Scopes
(Scope
(T
)) then
9035 elsif Is_Generic_Actual_Type
(T
) then
9044 end Find_Actual_Type
;
9046 -----------------------------
9047 -- Freeze_Package_Instance --
9048 -----------------------------
9050 procedure Freeze_Package_Instance
9056 function In_Same_Scope
(Gen_Id
, Act_Id
: Node_Id
) return Boolean;
9057 -- Check if the generic definition and the instantiation come from
9058 -- a common scope, in which case the instance must be frozen after
9059 -- the generic body.
9061 function True_Sloc
(N
, Act_Unit
: Node_Id
) return Source_Ptr
;
9062 -- If the instance is nested inside a generic unit, the Sloc of the
9063 -- instance indicates the place of the original definition, not the
9064 -- point of the current enclosing instance. Pending a better usage of
9065 -- Slocs to indicate instantiation places, we determine the place of
9066 -- origin of a node by finding the maximum sloc of any ancestor node.
9068 -- Why is this not equivalent to Top_Level_Location ???
9074 function In_Same_Scope
(Gen_Id
, Act_Id
: Node_Id
) return Boolean is
9075 Act_Scop
: Entity_Id
:= Scope
(Act_Id
);
9076 Gen_Scop
: Entity_Id
:= Scope
(Gen_Id
);
9079 while Act_Scop
/= Standard_Standard
9080 and then Gen_Scop
/= Standard_Standard
9082 if Act_Scop
= Gen_Scop
then
9086 Act_Scop
:= Scope
(Act_Scop
);
9087 Gen_Scop
:= Scope
(Gen_Scop
);
9097 function True_Sloc
(N
, Act_Unit
: Node_Id
) return Source_Ptr
is
9104 while Present
(N1
) and then N1
/= Act_Unit
loop
9105 if Sloc
(N1
) > Res
then
9117 Gen_Id
: constant Entity_Id
:= Get_Generic_Entity
(N
);
9118 Par_Id
: constant Entity_Id
:= Scope
(Gen_Id
);
9119 Act_Unit
: constant Node_Id
:= Unit
(Cunit
(Get_Source_Unit
(N
)));
9120 Gen_Unit
: constant Node_Id
:=
9121 Unit
(Cunit
(Get_Source_Unit
(Gen_Decl
)));
9123 Body_Unit
: Node_Id
;
9125 Must_Delay
: Boolean;
9126 Orig_Body
: Node_Id
;
9128 -- Start of processing for Freeze_Package_Instance
9131 -- If the body is a subunit, the freeze point is the corresponding stub
9132 -- in the current compilation, not the subunit itself.
9134 if Nkind
(Parent
(Gen_Body
)) = N_Subunit
then
9135 Orig_Body
:= Corresponding_Stub
(Parent
(Gen_Body
));
9137 Orig_Body
:= Gen_Body
;
9140 Body_Unit
:= Unit
(Cunit
(Get_Source_Unit
(Orig_Body
)));
9142 -- If the instantiation and the generic definition appear in the same
9143 -- package declaration, this is an early instantiation. If they appear
9144 -- in the same declarative part, it is an early instantiation only if
9145 -- the generic body appears textually later, and the generic body is
9146 -- also in the main unit.
9148 -- If instance is nested within a subprogram, and the generic body
9149 -- is not, the instance is delayed because the enclosing body is. If
9150 -- instance and body are within the same scope, or the same subprogram
9151 -- body, indicate explicitly that the instance is delayed.
9154 (Gen_Unit
= Act_Unit
9155 and then (Nkind
(Gen_Unit
) in N_Generic_Package_Declaration
9156 | N_Package_Declaration
9157 or else (Gen_Unit
= Body_Unit
9159 True_Sloc
(N
, Act_Unit
) < Sloc
(Orig_Body
)))
9160 and then Is_In_Main_Unit
(Original_Node
(Gen_Unit
))
9161 and then In_Same_Scope
(Gen_Id
, Act_Id
));
9163 -- If this is an early instantiation, the freeze node is placed after
9164 -- the generic body. Otherwise, if the generic appears in an instance,
9165 -- we cannot freeze the current instance until the outer one is frozen.
9166 -- This is only relevant if the current instance is nested within some
9167 -- inner scope not itself within the outer instance. If this scope is
9168 -- a package body in the same declarative part as the outer instance,
9169 -- then that body needs to be frozen after the outer instance. Finally,
9170 -- if no delay is needed, we place the freeze node at the end of the
9171 -- current declarative part.
9173 if No
(Freeze_Node
(Act_Id
))
9174 or else not Is_List_Member
(Freeze_Node
(Act_Id
))
9176 Ensure_Freeze_Node
(Act_Id
);
9177 F_Node
:= Freeze_Node
(Act_Id
);
9180 Insert_After
(Orig_Body
, F_Node
);
9182 elsif Is_Generic_Instance
(Par_Id
)
9183 and then Present
(Freeze_Node
(Par_Id
))
9184 and then Scope
(Act_Id
) /= Par_Id
9186 -- Freeze instance of inner generic after instance of enclosing
9189 if In_Same_Declarative_Part
(Parent
(Freeze_Node
(Par_Id
)), N
) then
9191 -- Handle the following case:
9193 -- package Parent_Inst is new ...
9194 -- freeze Parent_Inst []
9196 -- procedure P ... -- this body freezes Parent_Inst
9198 -- package Inst is new ...
9200 -- In this particular scenario, the freeze node for Inst must
9201 -- be inserted in the same manner as that of Parent_Inst,
9202 -- before the next source body or at the end of the declarative
9203 -- list (body not available). If body P did not exist and
9204 -- Parent_Inst was frozen after Inst, either by a body
9205 -- following Inst or at the end of the declarative region,
9206 -- the freeze node for Inst must be inserted after that of
9207 -- Parent_Inst. This relation is established by comparing
9208 -- the Slocs of Parent_Inst freeze node and Inst.
9209 -- We examine the parents of the enclosing lists to handle
9210 -- the case where the parent instance is in the visible part
9211 -- of a package declaration, and the inner instance is in
9212 -- the corresponding private part.
9214 if Parent
(List_Containing
(Freeze_Node
(Par_Id
)))
9215 = Parent
(List_Containing
(N
))
9216 and then Sloc
(Freeze_Node
(Par_Id
)) <= Sloc
(N
)
9218 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9220 Insert_After
(Freeze_Node
(Par_Id
), F_Node
);
9223 -- Freeze package enclosing instance of inner generic after
9224 -- instance of enclosing generic.
9226 elsif Nkind
(Parent
(N
)) in N_Package_Body | N_Subprogram_Body
9227 and then In_Same_Declarative_Part
9228 (Parent
(Freeze_Node
(Par_Id
)), Parent
(N
))
9231 Enclosing
: Entity_Id
;
9234 Enclosing
:= Corresponding_Spec
(Parent
(N
));
9236 if No
(Enclosing
) then
9237 Enclosing
:= Defining_Entity
(Parent
(N
));
9240 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9241 Ensure_Freeze_Node
(Enclosing
);
9243 if not Is_List_Member
(Freeze_Node
(Enclosing
)) then
9245 -- The enclosing context is a subunit, insert the freeze
9246 -- node after the stub.
9248 if Nkind
(Parent
(Parent
(N
))) = N_Subunit
then
9249 Insert_Freeze_Node_For_Instance
9250 (Corresponding_Stub
(Parent
(Parent
(N
))),
9251 Freeze_Node
(Enclosing
));
9253 -- The enclosing context is a package with a stub body
9254 -- which has already been replaced by the real body.
9255 -- Insert the freeze node after the actual body.
9257 elsif Ekind
(Enclosing
) = E_Package
9258 and then Present
(Body_Entity
(Enclosing
))
9259 and then Was_Originally_Stub
9260 (Parent
(Body_Entity
(Enclosing
)))
9262 Insert_Freeze_Node_For_Instance
9263 (Parent
(Body_Entity
(Enclosing
)),
9264 Freeze_Node
(Enclosing
));
9266 -- The parent instance has been frozen before the body of
9267 -- the enclosing package, insert the freeze node after
9270 elsif In_Same_List
(Freeze_Node
(Par_Id
), Parent
(N
))
9272 Sloc
(Freeze_Node
(Par_Id
)) <= Sloc
(Parent
(N
))
9274 Insert_Freeze_Node_For_Instance
9275 (Parent
(N
), Freeze_Node
(Enclosing
));
9279 (Freeze_Node
(Par_Id
), Freeze_Node
(Enclosing
));
9285 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9289 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9292 end Freeze_Package_Instance
;
9294 --------------------------------
9295 -- Freeze_Subprogram_Instance --
9296 --------------------------------
9298 procedure Freeze_Subprogram_Instance
9301 Pack_Id
: Entity_Id
)
9303 function Enclosing_Package_Body
(N
: Node_Id
) return Node_Id
;
9304 -- Find innermost package body that encloses the given node, and which
9305 -- is not a compilation unit. Freeze nodes for the instance, or for its
9306 -- enclosing body, may be inserted after the enclosing_body of the
9307 -- generic unit. Used to determine proper placement of freeze node for
9308 -- both package and subprogram instances.
9310 function Package_Freeze_Node
(B
: Node_Id
) return Node_Id
;
9311 -- Find entity for given package body, and locate or create a freeze
9314 ----------------------------
9315 -- Enclosing_Package_Body --
9316 ----------------------------
9318 function Enclosing_Package_Body
(N
: Node_Id
) return Node_Id
is
9324 and then Nkind
(Parent
(P
)) /= N_Compilation_Unit
9326 if Nkind
(P
) = N_Package_Body
then
9327 if Nkind
(Parent
(P
)) = N_Subunit
then
9328 return Corresponding_Stub
(Parent
(P
));
9334 P
:= True_Parent
(P
);
9338 end Enclosing_Package_Body
;
9340 -------------------------
9341 -- Package_Freeze_Node --
9342 -------------------------
9344 function Package_Freeze_Node
(B
: Node_Id
) return Node_Id
is
9348 if Nkind
(B
) = N_Package_Body
then
9349 Id
:= Corresponding_Spec
(B
);
9350 else pragma Assert
(Nkind
(B
) = N_Package_Body_Stub
);
9351 Id
:= Corresponding_Spec
(Proper_Body
(Unit
(Library_Unit
(B
))));
9354 Ensure_Freeze_Node
(Id
);
9355 return Freeze_Node
(Id
);
9356 end Package_Freeze_Node
;
9360 Enc_G
: constant Node_Id
:= Enclosing_Package_Body
(Gen_Body
);
9361 Enc_N
: constant Node_Id
:= Enclosing_Package_Body
(N
);
9362 Par_Id
: constant Entity_Id
:= Scope
(Get_Generic_Entity
(N
));
9367 -- Start of processing for Freeze_Subprogram_Instance
9370 -- If the instance and the generic body appear within the same unit, and
9371 -- the instance precedes the generic, the freeze node for the instance
9372 -- must appear after that of the generic. If the generic is nested
9373 -- within another instance I2, then current instance must be frozen
9374 -- after I2. In both cases, the freeze nodes are those of enclosing
9375 -- packages. Otherwise, the freeze node is placed at the end of the
9376 -- current declarative part.
9378 Ensure_Freeze_Node
(Pack_Id
);
9379 F_Node
:= Freeze_Node
(Pack_Id
);
9381 if Is_Generic_Instance
(Par_Id
)
9382 and then Present
(Freeze_Node
(Par_Id
))
9383 and then In_Same_Declarative_Part
(Parent
(Freeze_Node
(Par_Id
)), N
)
9385 -- The parent was a premature instantiation. Insert freeze node at
9386 -- the end the current declarative part.
9388 if Is_Known_Guaranteed_ABE
(Get_Unit_Instantiation_Node
(Par_Id
)) then
9389 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9391 -- Handle the following case:
9393 -- package Parent_Inst is new ...
9394 -- freeze Parent_Inst []
9396 -- procedure P ... -- this body freezes Parent_Inst
9398 -- procedure Inst is new ...
9400 -- In this particular scenario, the freeze node for Inst must be
9401 -- inserted in the same manner as that of Parent_Inst - before the
9402 -- next source body or at the end of the declarative list (body not
9403 -- available). If body P did not exist and Parent_Inst was frozen
9404 -- after Inst, either by a body following Inst or at the end of the
9405 -- declarative region, the freeze node for Inst must be inserted
9406 -- after that of Parent_Inst. This relation is established by
9407 -- comparing the Slocs of Parent_Inst freeze node and Inst.
9409 elsif In_Same_List
(Freeze_Node
(Par_Id
), N
)
9410 and then Sloc
(Freeze_Node
(Par_Id
)) <= Sloc
(N
)
9412 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9415 Insert_After
(Freeze_Node
(Par_Id
), F_Node
);
9418 -- The body enclosing the instance should be frozen after the body that
9419 -- includes the generic, because the body of the instance may make
9420 -- references to entities therein. If the two are not in the same
9421 -- declarative part, or if the one enclosing the instance is frozen
9422 -- already, freeze the instance at the end of the current declarative
9425 elsif Is_Generic_Instance
(Par_Id
)
9426 and then Present
(Freeze_Node
(Par_Id
))
9427 and then Present
(Enc_N
)
9429 if In_Same_Declarative_Part
(Parent
(Freeze_Node
(Par_Id
)), Enc_N
)
9431 -- The enclosing package may contain several instances. Rather
9432 -- than computing the earliest point at which to insert its freeze
9433 -- node, we place it at the end of the declarative part of the
9434 -- parent of the generic.
9436 Insert_Freeze_Node_For_Instance
9437 (Freeze_Node
(Par_Id
), Package_Freeze_Node
(Enc_N
));
9440 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9442 elsif Present
(Enc_G
)
9443 and then Present
(Enc_N
)
9444 and then Enc_G
/= Enc_N
9445 and then Earlier
(N
, Gen_Body
)
9447 -- Freeze package that encloses instance, and place node after the
9448 -- package that encloses generic. If enclosing package is already
9449 -- frozen we have to assume it is at the proper place. This may be a
9450 -- potential ABE that requires dynamic checking. Do not add a freeze
9451 -- node if the package that encloses the generic is inside the body
9452 -- that encloses the instance, because the freeze node would be in
9453 -- the wrong scope. Additional contortions needed if the bodies are
9454 -- within a subunit.
9457 Enclosing_Body
: Node_Id
;
9460 if Nkind
(Enc_N
) = N_Package_Body_Stub
then
9461 Enclosing_Body
:= Proper_Body
(Unit
(Library_Unit
(Enc_N
)));
9463 Enclosing_Body
:= Enc_N
;
9466 if Parent
(List_Containing
(Enc_G
)) /= Enclosing_Body
then
9467 Insert_Freeze_Node_For_Instance
9468 (Enc_G
, Package_Freeze_Node
(Enc_N
));
9472 -- Freeze enclosing subunit before instance
9474 Enc_G_F
:= Package_Freeze_Node
(Enc_G
);
9476 if not Is_List_Member
(Enc_G_F
) then
9477 Insert_After
(Enc_G
, Enc_G_F
);
9480 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9483 -- If none of the above, insert freeze node at the end of the current
9484 -- declarative part.
9486 Insert_Freeze_Node_For_Instance
(N
, F_Node
);
9488 end Freeze_Subprogram_Instance
;
9494 function Get_Gen_Id
(E
: Assoc_Ptr
) return Entity_Id
is
9496 return Generic_Renamings
.Table
(E
).Gen_Id
;
9499 ---------------------
9500 -- Get_Instance_Of --
9501 ---------------------
9503 function Get_Instance_Of
(A
: Entity_Id
) return Entity_Id
is
9504 Res
: constant Assoc_Ptr
:= Generic_Renamings_HTable
.Get
(A
);
9507 if Res
/= Assoc_Null
then
9508 return Generic_Renamings
.Table
(Res
).Act_Id
;
9511 -- On exit, entity is not instantiated: not a generic parameter, or
9512 -- else parameter of an inner generic unit.
9516 end Get_Instance_Of
;
9518 ---------------------------------
9519 -- Get_Unit_Instantiation_Node --
9520 ---------------------------------
9522 function Get_Unit_Instantiation_Node
(A
: Entity_Id
) return Node_Id
is
9523 Decl
: Node_Id
:= Unit_Declaration_Node
(A
);
9527 -- If the Package_Instantiation attribute has been set on the package
9528 -- entity, then use it directly when it (or its Original_Node) refers
9529 -- to an N_Package_Instantiation node. In principle it should be
9530 -- possible to have this field set in all cases, which should be
9531 -- investigated, and would allow this function to be significantly
9534 Inst
:= Package_Instantiation
(A
);
9536 if Present
(Inst
) then
9537 if Nkind
(Inst
) = N_Package_Instantiation
then
9540 elsif Nkind
(Original_Node
(Inst
)) = N_Package_Instantiation
then
9541 return Original_Node
(Inst
);
9545 -- If the instantiation is a compilation unit that does not need body
9546 -- then the instantiation node has been rewritten as a package
9547 -- declaration for the instance, and we return the original node.
9549 -- If it is a compilation unit and the instance node has not been
9550 -- rewritten, then it is still the unit of the compilation. Finally, if
9551 -- a body is present, this is a parent of the main unit whose body has
9552 -- been compiled for inlining purposes, and the instantiation node has
9553 -- been rewritten with the instance body.
9555 -- Otherwise the instantiation node appears after the declaration. If
9556 -- the entity is a formal package, the declaration may have been
9557 -- rewritten as a generic declaration (in the case of a formal with box)
9558 -- or left as a formal package declaration if it has actuals, and is
9559 -- found with a forward search.
9561 if Nkind
(Parent
(Decl
)) = N_Compilation_Unit
then
9562 if Nkind
(Decl
) = N_Package_Declaration
9563 and then Present
(Corresponding_Body
(Decl
))
9565 Decl
:= Unit_Declaration_Node
(Corresponding_Body
(Decl
));
9568 if Nkind
(Original_Node
(Decl
)) in N_Generic_Instantiation
then
9569 return Original_Node
(Decl
);
9571 return Unit
(Parent
(Decl
));
9574 elsif Nkind
(Decl
) = N_Package_Declaration
9575 and then Nkind
(Original_Node
(Decl
)) = N_Formal_Package_Declaration
9577 return Original_Node
(Decl
);
9580 Inst
:= Next
(Decl
);
9581 while Nkind
(Inst
) not in N_Formal_Package_Declaration
9582 | N_Function_Instantiation
9583 | N_Package_Instantiation
9584 | N_Procedure_Instantiation
9591 end Get_Unit_Instantiation_Node
;
9593 ------------------------
9594 -- Has_Been_Exchanged --
9595 ------------------------
9597 function Has_Been_Exchanged
(E
: Entity_Id
) return Boolean is
9601 Next
:= First_Elmt
(Exchanged_Views
);
9602 while Present
(Next
) loop
9603 if Full_View
(Node
(Next
)) = E
then
9611 end Has_Been_Exchanged
;
9617 function Has_Contracts
(Decl
: Node_Id
) return Boolean is
9618 A_List
: constant List_Id
:= Aspect_Specifications
(Decl
);
9625 A_Spec
:= First
(A_List
);
9626 while Present
(A_Spec
) loop
9627 A_Id
:= Get_Aspect_Id
(A_Spec
);
9628 if A_Id
= Aspect_Pre
or else A_Id
= Aspect_Post
then
9643 function Hash
(F
: Entity_Id
) return HTable_Range
is
9645 return HTable_Range
(F
mod HTable_Size
);
9648 ------------------------
9649 -- Hide_Current_Scope --
9650 ------------------------
9652 procedure Hide_Current_Scope
is
9653 C
: constant Entity_Id
:= Current_Scope
;
9657 Set_Is_Hidden_Open_Scope
(C
);
9659 E
:= First_Entity
(C
);
9660 while Present
(E
) loop
9661 if Is_Immediately_Visible
(E
) then
9662 Set_Is_Immediately_Visible
(E
, False);
9663 Append_Elmt
(E
, Hidden_Entities
);
9669 -- Make the scope name invisible as well. This is necessary, but might
9670 -- conflict with calls to Rtsfind later on, in case the scope is a
9671 -- predefined one. There is no clean solution to this problem, so for
9672 -- now we depend on the user not redefining Standard itself in one of
9673 -- the parent units.
9675 if Is_Immediately_Visible
(C
) and then C
/= Standard_Standard
then
9676 Set_Is_Immediately_Visible
(C
, False);
9677 Append_Elmt
(C
, Hidden_Entities
);
9680 end Hide_Current_Scope
;
9686 procedure Init_Env
is
9687 Saved
: Instance_Env
;
9690 Saved
.Instantiated_Parent
:= Current_Instantiated_Parent
;
9691 Saved
.Exchanged_Views
:= Exchanged_Views
;
9692 Saved
.Hidden_Entities
:= Hidden_Entities
;
9693 Saved
.Current_Sem_Unit
:= Current_Sem_Unit
;
9694 Saved
.Parent_Unit_Visible
:= Parent_Unit_Visible
;
9695 Saved
.Instance_Parent_Unit
:= Instance_Parent_Unit
;
9697 -- Save configuration switches. These may be reset if the unit is a
9698 -- predefined unit, and the current mode is not Ada 2005.
9700 Saved
.Switches
:= Save_Config_Switches
;
9702 Instance_Envs
.Append
(Saved
);
9704 Exchanged_Views
:= New_Elmt_List
;
9705 Hidden_Entities
:= New_Elmt_List
;
9707 -- Make dummy entry for Instantiated parent. If generic unit is legal,
9708 -- this is set properly in Set_Instance_Env.
9710 Current_Instantiated_Parent
:=
9711 (Current_Scope
, Current_Scope
, Assoc_Null
);
9714 ---------------------
9715 -- In_Main_Context --
9716 ---------------------
9718 function In_Main_Context
(E
: Entity_Id
) return Boolean is
9724 if not Is_Compilation_Unit
(E
)
9725 or else Ekind
(E
) /= E_Package
9726 or else In_Private_Part
(E
)
9731 Context
:= Context_Items
(Cunit
(Main_Unit
));
9733 Clause
:= First
(Context
);
9734 while Present
(Clause
) loop
9735 if Nkind
(Clause
) = N_With_Clause
then
9736 Nam
:= Name
(Clause
);
9738 -- If the current scope is part of the context of the main unit,
9739 -- analysis of the corresponding with_clause is not complete, and
9740 -- the entity is not set. We use the Chars field directly, which
9741 -- might produce false positives in rare cases, but guarantees
9742 -- that we produce all the instance bodies we will need.
9744 if (Is_Entity_Name
(Nam
) and then Chars
(Nam
) = Chars
(E
))
9745 or else (Nkind
(Nam
) = N_Selected_Component
9746 and then Chars
(Selector_Name
(Nam
)) = Chars
(E
))
9756 end In_Main_Context
;
9758 ---------------------
9759 -- Inherit_Context --
9760 ---------------------
9762 procedure Inherit_Context
(Gen_Decl
: Node_Id
; Inst
: Node_Id
) is
9763 Current_Context
: List_Id
;
9764 Current_Unit
: Node_Id
;
9773 if Nkind
(Parent
(Gen_Decl
)) = N_Compilation_Unit
then
9775 -- The inherited context is attached to the enclosing compilation
9776 -- unit. This is either the main unit, or the declaration for the
9777 -- main unit (in case the instantiation appears within the package
9778 -- declaration and the main unit is its body).
9780 Current_Unit
:= Parent
(Inst
);
9781 while Present
(Current_Unit
)
9782 and then Nkind
(Current_Unit
) /= N_Compilation_Unit
9784 Current_Unit
:= Parent
(Current_Unit
);
9787 Current_Context
:= Context_Items
(Current_Unit
);
9789 Item
:= First
(Context_Items
(Parent
(Gen_Decl
)));
9790 while Present
(Item
) loop
9791 if Nkind
(Item
) = N_With_Clause
then
9792 Lib_Unit
:= Library_Unit
(Item
);
9794 -- Take care to prevent direct cyclic with's
9796 if Lib_Unit
/= Current_Unit
then
9798 -- Do not add a unit if it is already in the context
9800 Clause
:= First
(Current_Context
);
9802 while Present
(Clause
) loop
9803 if Nkind
(Clause
) = N_With_Clause
9804 and then Library_Unit
(Clause
) = Lib_Unit
9814 New_I
:= New_Copy
(Item
);
9815 Set_Implicit_With
(New_I
);
9817 Append
(New_I
, Current_Context
);
9825 end Inherit_Context
;
9831 procedure Initialize
is
9833 Generic_Renamings
.Init
;
9836 Generic_Renamings_HTable
.Reset
;
9837 Circularity_Detected
:= False;
9838 Exchanged_Views
:= No_Elist
;
9839 Hidden_Entities
:= No_Elist
;
9842 -------------------------------------
9843 -- Insert_Freeze_Node_For_Instance --
9844 -------------------------------------
9846 procedure Insert_Freeze_Node_For_Instance
9850 function Enclosing_Body
(N
: Node_Id
) return Node_Id
;
9851 -- Find enclosing package or subprogram body, if any. Freeze node may
9852 -- be placed at end of current declarative list if previous instance
9853 -- and current one have different enclosing bodies.
9855 function Previous_Instance
(Gen
: Entity_Id
) return Entity_Id
;
9856 -- Find the local instance, if any, that declares the generic that is
9857 -- being instantiated. If present, the freeze node for this instance
9858 -- must follow the freeze node for the previous instance.
9860 --------------------
9861 -- Enclosing_Body --
9862 --------------------
9864 function Enclosing_Body
(N
: Node_Id
) return Node_Id
is
9870 and then Nkind
(Parent
(P
)) /= N_Compilation_Unit
9872 if Nkind
(P
) in N_Package_Body | N_Subprogram_Body
then
9873 if Nkind
(Parent
(P
)) = N_Subunit
then
9874 return Corresponding_Stub
(Parent
(P
));
9880 P
:= True_Parent
(P
);
9886 -----------------------
9887 -- Previous_Instance --
9888 -----------------------
9890 function Previous_Instance
(Gen
: Entity_Id
) return Entity_Id
is
9895 while Present
(S
) and then S
/= Standard_Standard
loop
9896 if Is_Generic_Instance
(S
)
9897 and then In_Same_Source_Unit
(S
, N
)
9906 end Previous_Instance
;
9917 -- Start of processing for Insert_Freeze_Node_For_Instance
9920 -- Nothing to do if the freeze node has already been inserted
9922 if Is_List_Member
(F_Node
) then
9926 Inst
:= Entity
(F_Node
);
9928 -- When processing a subprogram instantiation, utilize the actual
9929 -- subprogram instantiation rather than its package wrapper as it
9930 -- carries all the context information.
9932 if Is_Wrapper_Package
(Inst
) then
9933 Inst
:= Related_Instance
(Inst
);
9936 Par_Inst
:= Parent
(Inst
);
9938 -- If this is a package instance, check whether the generic is declared
9939 -- in a previous instance and the current instance is not within the
9942 if Present
(Generic_Parent
(Par_Inst
)) and then Is_In_Main_Unit
(N
) then
9944 Enclosing_N
: constant Node_Id
:= Enclosing_Body
(N
);
9945 Par_I
: constant Entity_Id
:=
9946 Previous_Instance
(Generic_Parent
(Par_Inst
));
9950 if Present
(Par_I
) and then Earlier
(N
, Freeze_Node
(Par_I
)) then
9951 Scop
:= Scope
(Inst
);
9953 -- If the current instance is within the one that contains
9954 -- the generic, the freeze node for the current one must
9955 -- appear in the current declarative part. Ditto, if the
9956 -- current instance is within another package instance or
9957 -- within a body that does not enclose the current instance.
9958 -- In these three cases the freeze node of the previous
9959 -- instance is not relevant.
9961 while Present
(Scop
) and then Scop
/= Standard_Standard
loop
9962 exit when Scop
= Par_I
9964 (Is_Generic_Instance
(Scop
)
9965 and then Scope_Depth
(Scop
) > Scope_Depth
(Par_I
));
9966 Scop
:= Scope
(Scop
);
9969 -- Previous instance encloses current instance
9971 if Scop
= Par_I
then
9974 -- If the next node is a source body we must freeze in the
9975 -- current scope as well.
9977 elsif Present
(Next
(N
))
9978 and then Nkind
(Next
(N
)) in N_Subprogram_Body
9980 and then Comes_From_Source
(Next
(N
))
9984 -- Current instance is within an unrelated instance
9986 elsif Is_Generic_Instance
(Scop
) then
9989 -- Current instance is within an unrelated body
9991 elsif Present
(Enclosing_N
)
9992 and then Enclosing_N
/= Enclosing_Body
(Par_I
)
9997 Insert_After
(Freeze_Node
(Par_I
), F_Node
);
10005 Decls
:= List_Containing
(N
);
10006 Par_N
:= Parent
(Decls
);
10009 -- Determine the proper freeze point of an instantiation
10011 if Is_Generic_Instance
(Inst
) then
10013 -- When the instantiation occurs in a package spec, append the
10014 -- freeze node to the private declarations (if any).
10016 if Nkind
(Par_N
) = N_Package_Specification
10017 and then Decls
= Visible_Declarations
(Par_N
)
10018 and then not Is_Empty_List
(Private_Declarations
(Par_N
))
10020 Decls
:= Private_Declarations
(Par_N
);
10021 Decl
:= First
(Decls
);
10024 -- We adhere to the general rule of a package or subprogram body
10025 -- causing freezing of anything before it in the same declarative
10026 -- region. In this respect, the proper freeze point of a package
10027 -- instantiation is before the first source body which follows, or
10028 -- before a stub. This ensures that entities from the instance are
10029 -- already frozen and therefore usable in source bodies.
10031 if Nkind
(Par_N
) /= N_Package_Declaration
10033 not In_Same_Source_Unit
(Generic_Parent
(Par_Inst
), Inst
)
10035 while Present
(Decl
) loop
10036 if ((Nkind
(Decl
) in N_Unit_Body
10038 Nkind
(Decl
) in N_Body_Stub
)
10039 and then Comes_From_Source
(Decl
))
10040 or else (Present
(Origin
)
10041 and then Nkind
(Decl
) in N_Generic_Instantiation
10042 and then Instance_Spec
(Decl
) /= Origin
)
10044 Set_Sloc
(F_Node
, Sloc
(Decl
));
10045 Insert_Before
(Decl
, F_Node
);
10053 -- When the instantiation occurs in a package spec and there is
10054 -- no source body which follows, and the package has a body but
10055 -- is delayed, then insert immediately before its freeze node.
10057 if Nkind
(Par_N
) = N_Package_Specification
10058 and then Present
(Corresponding_Body
(Parent
(Par_N
)))
10059 and then Present
(Freeze_Node
(Defining_Entity
(Par_N
)))
10061 Set_Sloc
(F_Node
, Sloc
(Freeze_Node
(Defining_Entity
(Par_N
))));
10062 Insert_Before
(Freeze_Node
(Defining_Entity
(Par_N
)), F_Node
);
10065 -- When the instantiation occurs in a package spec and there is
10066 -- no source body which follows, not even of the package itself,
10067 -- then insert into the declaration list of the outer level, but
10068 -- do not jump over following instantiations in this list because
10069 -- they may have a body that has not materialized yet, see above.
10071 elsif Nkind
(Par_N
) = N_Package_Specification
10072 and then No
(Corresponding_Body
(Parent
(Par_N
)))
10073 and then Is_List_Member
(Parent
(Par_N
))
10075 Decl
:= Parent
(Par_N
);
10076 Decls
:= List_Containing
(Decl
);
10077 Par_N
:= Parent
(Decls
);
10080 -- In a package declaration, or if no source body which follows
10081 -- and at library level, then insert at end of list.
10089 -- Insert and adjust the Sloc of the freeze node
10091 Set_Sloc
(F_Node
, Sloc
(Last
(Decls
)));
10092 Insert_After
(Last
(Decls
), F_Node
);
10093 end Insert_Freeze_Node_For_Instance
;
10095 -----------------------------
10096 -- Install_Formal_Packages --
10097 -----------------------------
10099 procedure Install_Formal_Packages
(Par
: Entity_Id
) is
10102 Gen_E
: Entity_Id
:= Empty
;
10105 E
:= First_Entity
(Par
);
10107 -- If we are installing an instance parent, locate the formal packages
10108 -- of its generic parent.
10110 if Is_Generic_Instance
(Par
) then
10111 Gen
:= Generic_Parent
(Package_Specification
(Par
));
10112 Gen_E
:= First_Entity
(Gen
);
10115 while Present
(E
) loop
10116 if Ekind
(E
) = E_Package
10117 and then Nkind
(Parent
(E
)) = N_Package_Renaming_Declaration
10119 -- If this is the renaming for the parent instance, done
10121 if Renamed_Entity
(E
) = Par
then
10124 -- The visibility of a formal of an enclosing generic is already
10127 elsif Denotes_Formal_Package
(E
) then
10130 elsif Present
(Associated_Formal_Package
(E
)) then
10131 Check_Generic_Actuals
(Renamed_Entity
(E
), True);
10132 Set_Is_Hidden
(E
, False);
10134 -- Find formal package in generic unit that corresponds to
10135 -- (instance of) formal package in instance.
10137 while Present
(Gen_E
) and then Chars
(Gen_E
) /= Chars
(E
) loop
10138 Next_Entity
(Gen_E
);
10141 if Present
(Gen_E
) then
10142 Map_Formal_Package_Entities
(Gen_E
, E
);
10149 if Present
(Gen_E
) then
10150 Next_Entity
(Gen_E
);
10153 end Install_Formal_Packages
;
10155 --------------------
10156 -- Install_Parent --
10157 --------------------
10159 procedure Install_Parent
(P
: Entity_Id
; In_Body
: Boolean := False) is
10160 Ancestors
: constant Elist_Id
:= New_Elmt_List
;
10161 S
: constant Entity_Id
:= Current_Scope
;
10162 Inst_Par
: Entity_Id
;
10163 First_Par
: Entity_Id
;
10164 Inst_Node
: Node_Id
;
10165 Gen_Par
: Entity_Id
;
10166 First_Gen
: Entity_Id
;
10169 procedure Install_Noninstance_Specs
(Par
: Entity_Id
);
10170 -- Install the scopes of noninstance parent units ending with Par
10172 procedure Install_Spec
(Par
: Entity_Id
);
10173 -- The child unit is within the declarative part of the parent, so the
10174 -- declarations within the parent are immediately visible.
10176 -------------------------------
10177 -- Install_Noninstance_Specs --
10178 -------------------------------
10180 procedure Install_Noninstance_Specs
(Par
: Entity_Id
) is
10183 and then Par
/= Standard_Standard
10184 and then not In_Open_Scopes
(Par
)
10186 Install_Noninstance_Specs
(Scope
(Par
));
10187 Install_Spec
(Par
);
10189 end Install_Noninstance_Specs
;
10195 procedure Install_Spec
(Par
: Entity_Id
) is
10196 Spec
: constant Node_Id
:= Package_Specification
(Par
);
10199 -- If this parent of the child instance is a top-level unit,
10200 -- then record the unit and its visibility for later resetting in
10201 -- Remove_Parent. We exclude units that are generic instances, as we
10202 -- only want to record this information for the ultimate top-level
10203 -- noninstance parent (is that always correct???).
10205 if Scope
(Par
) = Standard_Standard
10206 and then not Is_Generic_Instance
(Par
)
10208 Parent_Unit_Visible
:= Is_Immediately_Visible
(Par
);
10209 Instance_Parent_Unit
:= Par
;
10212 -- Open the parent scope and make it and its declarations visible.
10213 -- If this point is not within a body, then only the visible
10214 -- declarations should be made visible, and installation of the
10215 -- private declarations is deferred until the appropriate point
10216 -- within analysis of the spec being instantiated (see the handling
10217 -- of parent visibility in Analyze_Package_Specification). This is
10218 -- relaxed in the case where the parent unit is Ada.Tags, to avoid
10219 -- private view problems that occur when compiling instantiations of
10220 -- a generic child of that package (Generic_Dispatching_Constructor).
10221 -- If the instance freezes a tagged type, inlinings of operations
10222 -- from Ada.Tags may need the full view of type Tag. If inlining took
10223 -- proper account of establishing visibility of inlined subprograms'
10224 -- parents then it should be possible to remove this
10225 -- special check. ???
10228 Set_Is_Immediately_Visible
(Par
);
10229 Install_Visible_Declarations
(Par
);
10230 Set_Use
(Visible_Declarations
(Spec
));
10232 if In_Body
or else Is_RTU
(Par
, Ada_Tags
) then
10233 Install_Private_Declarations
(Par
);
10234 Set_Use
(Private_Declarations
(Spec
));
10238 -- Start of processing for Install_Parent
10241 -- We need to install the parent instance to compile the instantiation
10242 -- of the child, but the child instance must appear in the current
10243 -- scope. Given that we cannot place the parent above the current scope
10244 -- in the scope stack, we duplicate the current scope and unstack both
10245 -- after the instantiation is complete.
10247 -- If the parent is itself the instantiation of a child unit, we must
10248 -- also stack the instantiation of its parent, and so on. Each such
10249 -- ancestor is the prefix of the name in a prior instantiation.
10251 -- If this is a nested instance, the parent unit itself resolves to
10252 -- a renaming of the parent instance, whose declaration we need.
10254 -- Finally, the parent may be a generic (not an instance) when the
10255 -- child unit appears as a formal package.
10259 if Present
(Renamed_Entity
(Inst_Par
)) then
10260 Inst_Par
:= Renamed_Entity
(Inst_Par
);
10263 First_Par
:= Inst_Par
;
10265 Gen_Par
:= Generic_Parent
(Package_Specification
(Inst_Par
));
10267 First_Gen
:= Gen_Par
;
10269 while Present
(Gen_Par
) and then Is_Child_Unit
(Gen_Par
) loop
10271 -- Load grandparent instance as well
10273 Inst_Node
:= Get_Unit_Instantiation_Node
(Inst_Par
);
10275 if Nkind
(Name
(Inst_Node
)) = N_Expanded_Name
then
10276 Inst_Par
:= Entity
(Prefix
(Name
(Inst_Node
)));
10278 if Present
(Renamed_Entity
(Inst_Par
)) then
10279 Inst_Par
:= Renamed_Entity
(Inst_Par
);
10282 Gen_Par
:= Generic_Parent
(Package_Specification
(Inst_Par
));
10284 if Present
(Gen_Par
) then
10285 Prepend_Elmt
(Inst_Par
, Ancestors
);
10288 -- Parent is not the name of an instantiation
10290 Install_Noninstance_Specs
(Inst_Par
);
10301 if Present
(First_Gen
) then
10302 Append_Elmt
(First_Par
, Ancestors
);
10304 Install_Noninstance_Specs
(First_Par
);
10307 if not Is_Empty_Elmt_List
(Ancestors
) then
10308 Elmt
:= First_Elmt
(Ancestors
);
10309 while Present
(Elmt
) loop
10310 Install_Spec
(Node
(Elmt
));
10311 Install_Formal_Packages
(Node
(Elmt
));
10316 if not In_Body
then
10319 end Install_Parent
;
10321 -------------------------------
10322 -- Install_Hidden_Primitives --
10323 -------------------------------
10325 procedure Install_Hidden_Primitives
10326 (Prims_List
: in out Elist_Id
;
10331 List
: Elist_Id
:= No_Elist
;
10332 Prim_G_Elmt
: Elmt_Id
;
10333 Prim_A_Elmt
: Elmt_Id
;
10338 -- No action needed in case of serious errors because we cannot trust
10339 -- in the order of primitives
10341 if Serious_Errors_Detected
> 0 then
10344 -- No action possible if we don't have available the list of primitive
10348 or else not Is_Record_Type
(Gen_T
)
10349 or else not Is_Tagged_Type
(Gen_T
)
10350 or else not Is_Record_Type
(Act_T
)
10351 or else not Is_Tagged_Type
(Act_T
)
10355 -- There is no need to handle interface types since their primitives
10356 -- cannot be hidden
10358 elsif Is_Interface
(Gen_T
) then
10362 Prim_G_Elmt
:= First_Elmt
(Primitive_Operations
(Gen_T
));
10364 if not Is_Class_Wide_Type
(Act_T
) then
10365 Prim_A_Elmt
:= First_Elmt
(Primitive_Operations
(Act_T
));
10367 Prim_A_Elmt
:= First_Elmt
(Primitive_Operations
(Root_Type
(Act_T
)));
10371 -- Skip predefined primitives in the generic formal
10373 while Present
(Prim_G_Elmt
)
10374 and then Is_Predefined_Dispatching_Operation
(Node
(Prim_G_Elmt
))
10376 Next_Elmt
(Prim_G_Elmt
);
10379 -- Skip predefined primitives in the generic actual
10381 while Present
(Prim_A_Elmt
)
10382 and then Is_Predefined_Dispatching_Operation
(Node
(Prim_A_Elmt
))
10384 Next_Elmt
(Prim_A_Elmt
);
10387 exit when No
(Prim_G_Elmt
) or else No
(Prim_A_Elmt
);
10389 Prim_G
:= Node
(Prim_G_Elmt
);
10390 Prim_A
:= Node
(Prim_A_Elmt
);
10392 -- There is no need to handle interface primitives because their
10393 -- primitives are not hidden
10395 exit when Present
(Interface_Alias
(Prim_G
));
10397 -- Here we install one hidden primitive
10399 if Chars
(Prim_G
) /= Chars
(Prim_A
)
10400 and then Has_Suffix
(Prim_A
, 'P')
10401 and then Remove_Suffix
(Prim_A
, 'P') = Chars
(Prim_G
)
10403 Set_Chars
(Prim_A
, Chars
(Prim_G
));
10404 Append_New_Elmt
(Prim_A
, To
=> List
);
10407 Next_Elmt
(Prim_A_Elmt
);
10408 Next_Elmt
(Prim_G_Elmt
);
10411 -- Append the elements to the list of temporarily visible primitives
10412 -- avoiding duplicates.
10414 if Present
(List
) then
10415 if No
(Prims_List
) then
10416 Prims_List
:= New_Elmt_List
;
10419 Elmt
:= First_Elmt
(List
);
10420 while Present
(Elmt
) loop
10421 Append_Unique_Elmt
(Node
(Elmt
), Prims_List
);
10425 end Install_Hidden_Primitives
;
10427 -------------------------------
10428 -- Restore_Hidden_Primitives --
10429 -------------------------------
10431 procedure Restore_Hidden_Primitives
(Prims_List
: in out Elist_Id
) is
10432 Prim_Elmt
: Elmt_Id
;
10436 if Present
(Prims_List
) then
10437 Prim_Elmt
:= First_Elmt
(Prims_List
);
10438 while Present
(Prim_Elmt
) loop
10439 Prim
:= Node
(Prim_Elmt
);
10440 Set_Chars
(Prim
, Add_Suffix
(Prim
, 'P'));
10441 Next_Elmt
(Prim_Elmt
);
10444 Prims_List
:= No_Elist
;
10446 end Restore_Hidden_Primitives
;
10448 --------------------------------
10449 -- Instantiate_Formal_Package --
10450 --------------------------------
10452 function Instantiate_Formal_Package
10455 Analyzed_Formal
: Node_Id
) return List_Id
10457 Loc
: constant Source_Ptr
:= Sloc
(Actual
);
10458 Hidden_Formals
: constant Elist_Id
:= New_Elmt_List
;
10460 Actual_Pack
: Entity_Id
;
10461 Formal_Pack
: Entity_Id
;
10462 Gen_Parent
: Entity_Id
;
10465 Parent_Spec
: Node_Id
;
10467 procedure Find_Matching_Actual
10469 Act
: in out Entity_Id
);
10470 -- We need to associate each formal entity in the formal package with
10471 -- the corresponding entity in the actual package. The actual package
10472 -- has been analyzed and possibly expanded, and as a result there is
10473 -- no one-to-one correspondence between the two lists (for example,
10474 -- the actual may include subtypes, itypes, and inherited primitive
10475 -- operations, interspersed among the renaming declarations for the
10476 -- actuals). We retrieve the corresponding actual by name because each
10477 -- actual has the same name as the formal, and they do appear in the
10480 function Get_Formal_Entity
(N
: Node_Id
) return Entity_Id
;
10481 -- Retrieve entity of defining entity of generic formal parameter.
10482 -- Only the declarations of formals need to be considered when
10483 -- linking them to actuals, but the declarative list may include
10484 -- internal entities generated during analysis, and those are ignored.
10486 procedure Match_Formal_Entity
10487 (Formal_Node
: Node_Id
;
10488 Formal_Ent
: Entity_Id
;
10489 Actual_Ent
: Entity_Id
);
10490 -- Associates the formal entity with the actual. In the case where
10491 -- Formal_Ent is a formal package, this procedure iterates through all
10492 -- of its formals and enters associations between the actuals occurring
10493 -- in the formal package's corresponding actual package (given by
10494 -- Actual_Ent) and the formal package's formal parameters. This
10495 -- procedure recurses if any of the parameters is itself a package.
10497 function Is_Instance_Of
10498 (Act_Spec
: Entity_Id
;
10499 Gen_Anc
: Entity_Id
) return Boolean;
10500 -- The actual can be an instantiation of a generic within another
10501 -- instance, in which case there is no direct link from it to the
10502 -- original generic ancestor. In that case, we recognize that the
10503 -- ultimate ancestor is the same by examining names and scopes.
10505 procedure Process_Nested_Formal
(Formal
: Entity_Id
);
10506 -- If the current formal is declared with a box, its own formals are
10507 -- visible in the instance, as they were in the generic, and their
10508 -- Hidden flag must be reset. If some of these formals are themselves
10509 -- packages declared with a box, the processing must be recursive.
10511 --------------------------
10512 -- Find_Matching_Actual --
10513 --------------------------
10515 procedure Find_Matching_Actual
10517 Act
: in out Entity_Id
)
10519 Formal_Ent
: Entity_Id
;
10522 case Nkind
(Original_Node
(F
)) is
10523 when N_Formal_Object_Declaration
10524 | N_Formal_Type_Declaration
10526 Formal_Ent
:= Defining_Identifier
(F
);
10528 while Present
(Act
)
10529 and then Chars
(Act
) /= Chars
(Formal_Ent
)
10534 when N_Formal_Package_Declaration
10535 | N_Formal_Subprogram_Declaration
10536 | N_Generic_Package_Declaration
10537 | N_Package_Declaration
10539 Formal_Ent
:= Defining_Entity
(F
);
10541 while Present
(Act
)
10542 and then Chars
(Act
) /= Chars
(Formal_Ent
)
10548 raise Program_Error
;
10550 end Find_Matching_Actual
;
10552 -------------------------
10553 -- Match_Formal_Entity --
10554 -------------------------
10556 procedure Match_Formal_Entity
10557 (Formal_Node
: Node_Id
;
10558 Formal_Ent
: Entity_Id
;
10559 Actual_Ent
: Entity_Id
)
10561 Act_Pkg
: Entity_Id
;
10564 Set_Instance_Of
(Formal_Ent
, Actual_Ent
);
10566 if Ekind
(Actual_Ent
) = E_Package
then
10568 -- Record associations for each parameter
10570 Act_Pkg
:= Actual_Ent
;
10573 A_Ent
: Entity_Id
:= First_Entity
(Act_Pkg
);
10577 Gen_Decl
: Node_Id
;
10579 Actual
: Entity_Id
;
10582 -- Retrieve the actual given in the formal package declaration
10584 Actual
:= Entity
(Name
(Original_Node
(Formal_Node
)));
10586 -- The actual in the formal package declaration may be a
10587 -- renamed generic package, in which case we want to retrieve
10588 -- the original generic in order to traverse its formal part.
10590 if Present
(Renamed_Entity
(Actual
)) then
10591 Gen_Decl
:= Unit_Declaration_Node
(Renamed_Entity
(Actual
));
10593 Gen_Decl
:= Unit_Declaration_Node
(Actual
);
10596 Formals
:= Generic_Formal_Declarations
(Gen_Decl
);
10598 if Present
(Formals
) then
10599 F_Node
:= First_Non_Pragma
(Formals
);
10604 while Present
(A_Ent
)
10605 and then Present
(F_Node
)
10606 and then A_Ent
/= First_Private_Entity
(Act_Pkg
)
10608 F_Ent
:= Get_Formal_Entity
(F_Node
);
10610 if Present
(F_Ent
) then
10612 -- This is a formal of the original package. Record
10613 -- association and recurse.
10615 Find_Matching_Actual
(F_Node
, A_Ent
);
10616 Match_Formal_Entity
(F_Node
, F_Ent
, A_Ent
);
10617 Next_Entity
(A_Ent
);
10620 Next_Non_Pragma
(F_Node
);
10624 end Match_Formal_Entity
;
10626 -----------------------
10627 -- Get_Formal_Entity --
10628 -----------------------
10630 function Get_Formal_Entity
(N
: Node_Id
) return Entity_Id
is
10631 Kind
: constant Node_Kind
:= Nkind
(Original_Node
(N
));
10634 when N_Formal_Object_Declaration
=>
10635 return Defining_Identifier
(N
);
10637 when N_Formal_Type_Declaration
=>
10638 return Defining_Identifier
(N
);
10640 when N_Formal_Subprogram_Declaration
=>
10641 return Defining_Unit_Name
(Specification
(N
));
10643 when N_Formal_Package_Declaration
=>
10644 return Defining_Identifier
(Original_Node
(N
));
10646 when N_Generic_Package_Declaration
=>
10647 return Defining_Identifier
(Original_Node
(N
));
10649 -- All other declarations are introduced by semantic analysis and
10650 -- have no match in the actual.
10655 end Get_Formal_Entity
;
10657 --------------------
10658 -- Is_Instance_Of --
10659 --------------------
10661 function Is_Instance_Of
10662 (Act_Spec
: Entity_Id
;
10663 Gen_Anc
: Entity_Id
) return Boolean
10665 Gen_Par
: constant Entity_Id
:= Generic_Parent
(Act_Spec
);
10668 if No
(Gen_Par
) then
10671 -- Simplest case: the generic parent of the actual is the formal
10673 elsif Gen_Par
= Gen_Anc
then
10676 elsif Chars
(Gen_Par
) /= Chars
(Gen_Anc
) then
10679 -- The actual may be obtained through several instantiations. Its
10680 -- scope must itself be an instance of a generic declared in the
10681 -- same scope as the formal. Any other case is detected above.
10683 elsif not Is_Generic_Instance
(Scope
(Gen_Par
)) then
10687 return Generic_Parent
(Parent
(Scope
(Gen_Par
))) = Scope
(Gen_Anc
);
10689 end Is_Instance_Of
;
10691 ---------------------------
10692 -- Process_Nested_Formal --
10693 ---------------------------
10695 procedure Process_Nested_Formal
(Formal
: Entity_Id
) is
10699 if Present
(Associated_Formal_Package
(Formal
))
10700 and then Box_Present
(Parent
(Associated_Formal_Package
(Formal
)))
10702 Ent
:= First_Entity
(Formal
);
10703 while Present
(Ent
) loop
10704 Set_Is_Hidden
(Ent
, False);
10705 Set_Is_Visible_Formal
(Ent
);
10706 Set_Is_Potentially_Use_Visible
10707 (Ent
, Is_Potentially_Use_Visible
(Formal
));
10709 if Ekind
(Ent
) = E_Package
then
10710 exit when Renamed_Entity
(Ent
) = Renamed_Entity
(Formal
);
10711 Process_Nested_Formal
(Ent
);
10717 end Process_Nested_Formal
;
10719 -- Start of processing for Instantiate_Formal_Package
10724 -- The actual must be a package instance, or else a current instance
10725 -- such as a parent generic within the body of a generic child.
10727 if not Is_Entity_Name
(Actual
)
10728 or else not Is_Package_Or_Generic_Package
(Entity
(Actual
))
10731 ("expect package instance to instantiate formal", Actual
);
10732 Abandon_Instantiation
(Actual
);
10735 Actual_Pack
:= Entity
(Actual
);
10736 Set_Is_Instantiated
(Actual_Pack
);
10738 -- The actual may be a renamed package, or an outer generic formal
10739 -- package whose instantiation is converted into a renaming.
10741 if Present
(Renamed_Entity
(Actual_Pack
)) then
10742 Actual_Pack
:= Renamed_Entity
(Actual_Pack
);
10745 -- The analyzed formal is expected to be the result of the rewriting
10746 -- of the formal package into a regular package by analysis.
10748 pragma Assert
(Nkind
(Analyzed_Formal
) = N_Package_Declaration
10749 and then Nkind
(Original_Node
(Analyzed_Formal
)) =
10750 N_Formal_Package_Declaration
);
10752 Gen_Parent
:= Generic_Parent
(Specification
(Analyzed_Formal
));
10753 Formal_Pack
:= Defining_Unit_Name
(Specification
(Analyzed_Formal
));
10755 -- The actual for a ghost generic formal package should be a ghost
10756 -- package (SPARK RM 6.9(14)).
10758 Check_Ghost_Formal_Procedure_Or_Package
10760 Actual
=> Actual_Pack
,
10761 Formal
=> Formal_Pack
);
10763 if Nkind
(Parent
(Actual_Pack
)) = N_Defining_Program_Unit_Name
then
10764 Parent_Spec
:= Package_Specification
(Actual_Pack
);
10766 Parent_Spec
:= Parent
(Actual_Pack
);
10769 if Gen_Parent
= Any_Id
then
10771 ("previous error in declaration of formal package", Actual
);
10772 Abandon_Instantiation
(Actual
);
10774 elsif Is_Instance_Of
(Parent_Spec
, Get_Instance_Of
(Gen_Parent
)) then
10777 -- If this is the current instance of an enclosing generic, that unit
10778 -- is the generic package we need.
10780 elsif In_Open_Scopes
(Actual_Pack
)
10781 and then Ekind
(Actual_Pack
) = E_Generic_Package
10787 ("actual parameter must be instance of&", Actual
, Gen_Parent
);
10788 Abandon_Instantiation
(Actual
);
10791 Set_Instance_Of
(Defining_Identifier
(Formal
), Actual_Pack
);
10792 Map_Formal_Package_Entities
(Formal_Pack
, Actual_Pack
);
10795 Make_Package_Renaming_Declaration
(Loc
,
10796 Defining_Unit_Name
=> New_Copy
(Defining_Identifier
(Formal
)),
10797 Name
=> New_Occurrence_Of
(Actual_Pack
, Loc
));
10799 Set_Associated_Formal_Package
10800 (Defining_Unit_Name
(Nod
), Defining_Identifier
(Formal
));
10801 Decls
:= New_List
(Nod
);
10803 -- If the formal F has a box, then the generic declarations are
10804 -- visible in the generic G. In an instance of G, the corresponding
10805 -- entities in the actual for F (which are the actuals for the
10806 -- instantiation of the generic that F denotes) must also be made
10807 -- visible for analysis of the current instance. On exit from the
10808 -- current instance, those entities are made private again. If the
10809 -- actual is currently in use, these entities are also use-visible.
10811 -- The loop through the actual entities also steps through the formal
10812 -- entities and enters associations from formals to actuals into the
10813 -- renaming map. This is necessary to properly handle checking of
10814 -- actual parameter associations for later formals that depend on
10815 -- actuals declared in the formal package.
10817 -- In Ada 2005, partial parameterization requires that we make
10818 -- visible the actuals corresponding to formals that were defaulted
10819 -- in the formal package. There formals are identified because they
10820 -- remain formal generics within the formal package, rather than
10821 -- being renamings of the actuals supplied.
10824 Gen_Decl
: constant Node_Id
:=
10825 Unit_Declaration_Node
(Gen_Parent
);
10826 Formals
: constant List_Id
:=
10827 Generic_Formal_Declarations
(Gen_Decl
);
10829 Actual_Ent
: Entity_Id
;
10830 Actual_Of_Formal
: Node_Id
;
10831 Formal_Node
: Node_Id
;
10832 Formal_Ent
: Entity_Id
;
10835 if Present
(Formals
) then
10836 Formal_Node
:= First_Non_Pragma
(Formals
);
10838 Formal_Node
:= Empty
;
10841 Actual_Ent
:= First_Entity
(Actual_Pack
);
10842 Actual_Of_Formal
:=
10843 First
(Visible_Declarations
(Specification
(Analyzed_Formal
)));
10844 while Present
(Actual_Ent
)
10845 and then Actual_Ent
/= First_Private_Entity
(Actual_Pack
)
10847 if Present
(Formal_Node
) then
10848 Formal_Ent
:= Get_Formal_Entity
(Formal_Node
);
10850 if Present
(Formal_Ent
) then
10851 Find_Matching_Actual
(Formal_Node
, Actual_Ent
);
10852 Match_Formal_Entity
(Formal_Node
, Formal_Ent
, Actual_Ent
);
10854 -- We iterate at the same time over the actuals of the
10855 -- local package created for the formal, to determine
10856 -- which one of the formals of the original generic were
10857 -- defaulted in the formal. The corresponding actual
10858 -- entities are visible in the enclosing instance.
10860 if Box_Present
(Formal
)
10862 (Present
(Actual_Of_Formal
)
10865 (Get_Formal_Entity
(Actual_Of_Formal
)))
10867 Set_Is_Hidden
(Actual_Ent
, False);
10868 Set_Is_Visible_Formal
(Actual_Ent
);
10869 Set_Is_Potentially_Use_Visible
10870 (Actual_Ent
, In_Use
(Actual_Pack
));
10872 if Ekind
(Actual_Ent
) = E_Package
then
10873 Process_Nested_Formal
(Actual_Ent
);
10877 if not Is_Hidden
(Actual_Ent
) then
10878 Append_Elmt
(Actual_Ent
, Hidden_Formals
);
10881 Set_Is_Hidden
(Actual_Ent
);
10882 Set_Is_Potentially_Use_Visible
(Actual_Ent
, False);
10886 Next_Non_Pragma
(Formal_Node
);
10887 Next
(Actual_Of_Formal
);
10889 -- A formal subprogram may be overloaded, so advance in
10890 -- the list of actuals to make sure we do not match two
10891 -- successive formals to the same actual. This is only
10892 -- relevant for overloadable entities, others have
10895 if Is_Overloadable
(Actual_Ent
) then
10896 Next_Entity
(Actual_Ent
);
10900 -- No further formals to match, but the generic part may
10901 -- contain inherited operation that are not hidden in the
10902 -- enclosing instance.
10904 Next_Entity
(Actual_Ent
);
10908 -- Inherited subprograms generated by formal derived types are
10909 -- also visible if the types are.
10911 Actual_Ent
:= First_Entity
(Actual_Pack
);
10912 while Present
(Actual_Ent
)
10913 and then Actual_Ent
/= First_Private_Entity
(Actual_Pack
)
10915 if Is_Overloadable
(Actual_Ent
)
10917 Nkind
(Parent
(Actual_Ent
)) = N_Subtype_Declaration
10919 not Is_Hidden
(Defining_Identifier
(Parent
(Actual_Ent
)))
10921 Set_Is_Hidden
(Actual_Ent
, False);
10922 Set_Is_Potentially_Use_Visible
10923 (Actual_Ent
, In_Use
(Actual_Pack
));
10926 Next_Entity
(Actual_Ent
);
10930 -- If the formal requires conformance checking, reanalyze it as an
10931 -- abbreviated instantiation, to verify the matching rules of 12.7.
10932 -- The actual checks are performed after the generic associations
10933 -- have been analyzed, to guarantee the same visibility for this
10934 -- instantiation and for the actuals.
10936 -- In Ada 2005, the generic associations for the formal can include
10937 -- defaulted parameters. These are ignored during check. This
10938 -- internal instantiation is removed from the tree after conformance
10939 -- checking, because it contains formal declarations for those
10940 -- defaulted parameters, and those should not reach the back-end.
10942 if Requires_Conformance_Checking
(Formal
) then
10944 I_Pack
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
10949 Set_Is_Internal
(I_Pack
);
10950 Mutate_Ekind
(I_Pack
, E_Package
);
10952 -- Insert the package into the list of its hidden entities so
10953 -- that the list is not empty for Is_Abbreviated_Instance.
10955 Append_Elmt
(I_Pack
, Hidden_Formals
);
10957 Set_Hidden_In_Formal_Instance
(I_Pack
, Hidden_Formals
);
10959 -- If the generic is a child unit, Check_Generic_Child_Unit
10960 -- needs its original name in case it is qualified.
10962 if Is_Child_Unit
(Gen_Parent
) then
10964 New_Copy_Tree
(Name
(Original_Node
(Analyzed_Formal
)));
10965 pragma Assert
(Entity
(I_Nam
) = Gen_Parent
);
10969 New_Occurrence_Of
(Get_Instance_Of
(Gen_Parent
), Loc
);
10973 Make_Package_Instantiation
(Loc
,
10974 Defining_Unit_Name
=> I_Pack
,
10976 Generic_Associations
=> Generic_Associations
(Formal
)));
10982 end Instantiate_Formal_Package
;
10984 -----------------------------------
10985 -- Instantiate_Formal_Subprogram --
10986 -----------------------------------
10988 function Instantiate_Formal_Subprogram
10991 Analyzed_Formal
: Node_Id
) return Node_Id
10993 Analyzed_S
: constant Entity_Id
:=
10994 Defining_Unit_Name
(Specification
(Analyzed_Formal
));
10995 Formal_Sub
: constant Entity_Id
:=
10996 Defining_Unit_Name
(Specification
(Formal
));
10998 function From_Parent_Scope
(Subp
: Entity_Id
) return Boolean;
10999 -- If the generic is a child unit, the parent has been installed on the
11000 -- scope stack, but a default subprogram cannot resolve to something
11001 -- on the parent because that parent is not really part of the visible
11002 -- context (it is there to resolve explicit local entities). If the
11003 -- default has resolved in this way, we remove the entity from immediate
11004 -- visibility and analyze the node again to emit an error message or
11005 -- find another visible candidate.
11007 procedure Valid_Actual_Subprogram
(Act
: Node_Id
);
11008 -- Perform legality check and raise exception on failure
11010 -----------------------
11011 -- From_Parent_Scope --
11012 -----------------------
11014 function From_Parent_Scope
(Subp
: Entity_Id
) return Boolean is
11015 Gen_Scope
: Node_Id
;
11018 Gen_Scope
:= Scope
(Analyzed_S
);
11019 while Present
(Gen_Scope
) and then Is_Child_Unit
(Gen_Scope
) loop
11020 if Scope
(Subp
) = Scope
(Gen_Scope
) then
11024 Gen_Scope
:= Scope
(Gen_Scope
);
11028 end From_Parent_Scope
;
11030 -----------------------------
11031 -- Valid_Actual_Subprogram --
11032 -----------------------------
11034 procedure Valid_Actual_Subprogram
(Act
: Node_Id
) is
11038 if Is_Entity_Name
(Act
) then
11039 Act_E
:= Entity
(Act
);
11041 elsif Nkind
(Act
) = N_Selected_Component
11042 and then Is_Entity_Name
(Selector_Name
(Act
))
11044 Act_E
:= Entity
(Selector_Name
(Act
));
11050 -- The actual for a ghost generic formal procedure should be a ghost
11051 -- procedure (SPARK RM 6.9(14)).
11054 and then Ekind
(Act_E
) = E_Procedure
11056 Check_Ghost_Formal_Procedure_Or_Package
11059 Formal
=> Analyzed_S
);
11062 if (Present
(Act_E
) and then Is_Overloadable
(Act_E
))
11063 or else Nkind
(Act
) in N_Attribute_Reference
11064 | N_Indexed_Component
11065 | N_Character_Literal
11066 | N_Explicit_Dereference
11072 ("expect subprogram or entry name in instantiation of &",
11073 Instantiation_Node
, Formal_Sub
);
11074 Abandon_Instantiation
(Instantiation_Node
);
11075 end Valid_Actual_Subprogram
;
11079 Decl_Node
: Node_Id
;
11082 New_Spec
: Node_Id
;
11083 New_Subp
: Entity_Id
;
11085 -- Start of processing for Instantiate_Formal_Subprogram
11088 New_Spec
:= New_Copy_Tree
(Specification
(Formal
));
11090 -- The tree copy has created the proper instantiation sloc for the
11091 -- new specification. Use this location for all other constructed
11094 Loc
:= Sloc
(Defining_Unit_Name
(New_Spec
));
11096 -- Create new entity for the actual (New_Copy_Tree does not), and
11097 -- indicate that it is an actual.
11099 -- If the actual is not an entity (i.e. an attribute reference)
11100 -- and the formal includes aspect specifications for contracts,
11101 -- we create an internal name for the renaming declaration. The
11102 -- constructed wrapper contains a call to the entity in the renaming.
11103 -- This is an expansion activity, as is the wrapper creation.
11105 if Ada_Version
>= Ada_2022
11106 and then Has_Contracts
(Analyzed_Formal
)
11107 and then not Is_Entity_Name
(Actual
)
11108 and then Expander_Active
11110 New_Subp
:= Make_Temporary
(Sloc
(Actual
), 'S');
11112 New_Subp
:= Make_Defining_Identifier
(Loc
, Chars
(Formal_Sub
));
11115 Mutate_Ekind
(New_Subp
, Ekind
(Analyzed_S
));
11116 Set_Is_Generic_Actual_Subprogram
(New_Subp
);
11117 Set_Defining_Unit_Name
(New_Spec
, New_Subp
);
11119 -- Create new entities for the each of the formals in the specification
11120 -- of the renaming declaration built for the actual.
11122 if Present
(Parameter_Specifications
(New_Spec
)) then
11128 F
:= First
(Parameter_Specifications
(New_Spec
));
11129 while Present
(F
) loop
11130 F_Id
:= Defining_Identifier
(F
);
11132 Set_Defining_Identifier
(F
,
11133 Make_Defining_Identifier
(Sloc
(F_Id
), Chars
(F_Id
)));
11139 -- Find entity of actual. If the actual is an attribute reference, it
11140 -- cannot be resolved here (its formal is missing) but is handled
11141 -- instead in Attribute_Renaming. If the actual is overloaded, it is
11142 -- fully resolved subsequently, when the renaming declaration for the
11143 -- formal is analyzed. If it is an explicit dereference, resolve the
11144 -- prefix but not the actual itself, to prevent interpretation as call.
11146 if Present
(Actual
) then
11147 Loc
:= Sloc
(Actual
);
11148 Set_Sloc
(New_Spec
, Loc
);
11150 if Nkind
(Actual
) = N_Operator_Symbol
then
11151 Find_Direct_Name
(Actual
);
11153 elsif Nkind
(Actual
) = N_Explicit_Dereference
then
11154 Analyze
(Prefix
(Actual
));
11156 elsif Nkind
(Actual
) /= N_Attribute_Reference
then
11160 Valid_Actual_Subprogram
(Actual
);
11163 elsif Present
(Default_Name
(Formal
)) then
11164 if Nkind
(Default_Name
(Formal
)) not in N_Attribute_Reference
11165 | N_Selected_Component
11166 | N_Indexed_Component
11167 | N_Character_Literal
11168 and then Present
(Entity
(Default_Name
(Formal
)))
11170 Nam
:= New_Occurrence_Of
(Entity
(Default_Name
(Formal
)), Loc
);
11172 Nam
:= New_Copy
(Default_Name
(Formal
));
11173 Set_Sloc
(Nam
, Loc
);
11176 elsif Box_Present
(Formal
) then
11178 -- Actual is resolved at the point of instantiation. Create an
11179 -- identifier or operator with the same name as the formal.
11181 if Nkind
(Formal_Sub
) = N_Defining_Operator_Symbol
then
11183 Make_Operator_Symbol
(Loc
,
11184 Chars
=> Chars
(Formal_Sub
),
11185 Strval
=> No_String
);
11187 Nam
:= Make_Identifier
(Loc
, Chars
(Formal_Sub
));
11190 elsif Nkind
(Specification
(Formal
)) = N_Procedure_Specification
11191 and then Null_Present
(Specification
(Formal
))
11193 -- Generate null body for procedure, for use in the instance
11196 Make_Subprogram_Body
(Loc
,
11197 Specification
=> New_Spec
,
11198 Declarations
=> New_List
,
11199 Handled_Statement_Sequence
=>
11200 Make_Handled_Sequence_Of_Statements
(Loc
,
11201 Statements
=> New_List
(Make_Null_Statement
(Loc
))));
11203 -- RM 12.6 (16.2/2): The procedure has convention Intrinsic
11205 Set_Convention
(Defining_Unit_Name
(New_Spec
), Convention_Intrinsic
);
11207 Copy_Ghost_Aspect
(Formal
, To
=> Decl_Node
);
11209 -- Eliminate the calls to it when optimization is enabled
11211 Set_Is_Inlined
(Defining_Unit_Name
(New_Spec
));
11214 -- Handle case of a formal function with an expression default (allowed
11215 -- when extensions are enabled).
11217 elsif Nkind
(Specification
(Formal
)) = N_Function_Specification
11218 and then Present
(Expression
(Formal
))
11220 -- Generate body for function, for use in the instance
11223 Expr
: constant Node_Id
:= New_Copy
(Expression
(Formal
));
11224 Stmt
: constant Node_Id
:= Make_Simple_Return_Statement
(Loc
);
11226 Set_Sloc
(Expr
, Loc
);
11227 Set_Expression
(Stmt
, Expr
);
11230 Make_Subprogram_Body
(Loc
,
11231 Specification
=> New_Spec
,
11232 Declarations
=> New_List
,
11233 Handled_Statement_Sequence
=>
11234 Make_Handled_Sequence_Of_Statements
(Loc
,
11235 Statements
=> New_List
(Stmt
)));
11238 -- RM 12.6 (16.2/2): Like a null procedure default, the function
11239 -- has convention Intrinsic.
11241 Set_Convention
(Defining_Unit_Name
(New_Spec
), Convention_Intrinsic
);
11243 -- Inline calls to it when optimization is enabled
11245 Set_Is_Inlined
(Defining_Unit_Name
(New_Spec
));
11249 Error_Msg_Sloc
:= Sloc
(Scope
(Analyzed_S
));
11251 ("missing actual&", Instantiation_Node
, Formal_Sub
);
11253 ("\in instantiation of & declared#",
11254 Instantiation_Node
, Scope
(Analyzed_S
));
11255 Abandon_Instantiation
(Instantiation_Node
);
11259 Make_Subprogram_Renaming_Declaration
(Loc
,
11260 Specification
=> New_Spec
,
11263 -- If we do not have an actual and the formal specified <> then set to
11264 -- get proper default.
11266 if No
(Actual
) and then Box_Present
(Formal
) then
11267 Set_From_Default
(Decl_Node
);
11270 -- Gather possible interpretations for the actual before analyzing the
11271 -- instance. If overloaded, it will be resolved when analyzing the
11272 -- renaming declaration.
11274 if Box_Present
(Formal
) and then No
(Actual
) then
11277 if Is_Child_Unit
(Scope
(Analyzed_S
))
11278 and then Present
(Entity
(Nam
))
11280 if not Is_Overloaded
(Nam
) then
11281 if From_Parent_Scope
(Entity
(Nam
)) then
11282 Set_Is_Immediately_Visible
(Entity
(Nam
), False);
11283 Set_Entity
(Nam
, Empty
);
11284 Set_Etype
(Nam
, Empty
);
11287 Set_Is_Immediately_Visible
(Entity
(Nam
));
11296 Get_First_Interp
(Nam
, I
, It
);
11297 while Present
(It
.Nam
) loop
11298 if From_Parent_Scope
(It
.Nam
) then
11302 Get_Next_Interp
(I
, It
);
11309 -- The generic instantiation freezes the actual. This can only be done
11310 -- once the actual is resolved, in the analysis of the renaming
11311 -- declaration. To make the formal subprogram entity available, we set
11312 -- Corresponding_Formal_Spec to point to the formal subprogram entity.
11313 -- This is also needed in Analyze_Subprogram_Renaming for the processing
11314 -- of formal abstract subprograms.
11316 Set_Corresponding_Formal_Spec
(Decl_Node
, Analyzed_S
);
11318 -- We cannot analyze the renaming declaration, and thus find the actual,
11319 -- until all the actuals are assembled in the instance. For subsequent
11320 -- checks of other actuals, indicate the node that will hold the
11321 -- instance of this formal.
11323 Set_Instance_Of
(Analyzed_S
, Nam
);
11325 if Nkind
(Actual
) = N_Selected_Component
11326 and then Is_Task_Type
(Etype
(Prefix
(Actual
)))
11327 and then not Is_Frozen
(Etype
(Prefix
(Actual
)))
11329 -- The renaming declaration will create a body, which must appear
11330 -- outside of the instantiation, We move the renaming declaration
11331 -- out of the instance, and create an additional renaming inside,
11332 -- to prevent freezing anomalies.
11335 Anon_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'E');
11338 Set_Defining_Unit_Name
(New_Spec
, Anon_Id
);
11339 Insert_Before
(Instantiation_Node
, Decl_Node
);
11340 Analyze
(Decl_Node
);
11342 -- Now create renaming within the instance
11345 Make_Subprogram_Renaming_Declaration
(Loc
,
11346 Specification
=> New_Copy_Tree
(New_Spec
),
11347 Name
=> New_Occurrence_Of
(Anon_Id
, Loc
));
11349 Set_Defining_Unit_Name
(Specification
(Decl_Node
),
11350 Make_Defining_Identifier
(Loc
, Chars
(Formal_Sub
)));
11355 end Instantiate_Formal_Subprogram
;
11357 ------------------------
11358 -- Instantiate_Object --
11359 ------------------------
11361 function Instantiate_Object
11364 Analyzed_Formal
: Node_Id
) return List_Id
11366 Gen_Obj
: constant Entity_Id
:= Defining_Identifier
(Formal
);
11367 A_Gen_Obj
: constant Entity_Id
:=
11368 Defining_Identifier
(Analyzed_Formal
);
11369 Acc_Def
: Node_Id
:= Empty
;
11370 Act_Assoc
: constant Node_Id
:=
11371 (if No
(Actual
) then Empty
else Parent
(Actual
));
11372 Actual_Decl
: Node_Id
:= Empty
;
11373 Decl_Node
: Node_Id
;
11376 List
: constant List_Id
:= New_List
;
11377 Loc
: constant Source_Ptr
:= Sloc
(Actual
);
11378 Orig_Ftyp
: constant Entity_Id
:= Etype
(A_Gen_Obj
);
11379 Subt_Decl
: Node_Id
:= Empty
;
11380 Subt_Mark
: Node_Id
:= Empty
;
11382 -- Start of processing for Instantiate_Object
11385 -- Formal may be an anonymous access
11387 if Present
(Subtype_Mark
(Formal
)) then
11388 Subt_Mark
:= Subtype_Mark
(Formal
);
11390 Check_Access_Definition
(Formal
);
11391 Acc_Def
:= Access_Definition
(Formal
);
11394 -- Sloc for error message on missing actual
11396 Error_Msg_Sloc
:= Sloc
(Scope
(A_Gen_Obj
));
11398 if Get_Instance_Of
(Gen_Obj
) /= Gen_Obj
then
11399 Error_Msg_N
("duplicate instantiation of generic parameter", Actual
);
11402 Set_Parent
(List
, Act_Assoc
);
11406 if Out_Present
(Formal
) then
11408 -- An IN OUT generic actual must be a name. The instantiation is a
11409 -- renaming declaration. The actual is the name being renamed. We
11410 -- use the actual directly, rather than a copy, because it is not
11411 -- used further in the list of actuals, and because a copy or a use
11412 -- of relocate_node is incorrect if the instance is nested within a
11413 -- generic. In order to simplify e.g. ASIS queries, the
11414 -- Generic_Parent field links the declaration to the generic
11417 if No
(Actual
) then
11419 ("missing actual &",
11420 Instantiation_Node
, Gen_Obj
);
11422 ("\in instantiation of & declared#",
11423 Instantiation_Node
, Scope
(A_Gen_Obj
));
11424 Abandon_Instantiation
(Instantiation_Node
);
11427 if Present
(Subt_Mark
) then
11429 Make_Object_Renaming_Declaration
(Loc
,
11430 Defining_Identifier
=> New_Copy
(Gen_Obj
),
11431 Subtype_Mark
=> New_Copy_Tree
(Subt_Mark
),
11434 else pragma Assert
(Present
(Acc_Def
));
11436 Make_Object_Renaming_Declaration
(Loc
,
11437 Defining_Identifier
=> New_Copy
(Gen_Obj
),
11438 Access_Definition
=> New_Copy_Tree
(Acc_Def
),
11442 Set_Corresponding_Generic_Association
(Decl_Node
, Act_Assoc
);
11444 -- The analysis of the actual may produce Insert_Action nodes, so
11445 -- the declaration must have a context in which to attach them.
11447 Append
(Decl_Node
, List
);
11450 -- Return if the analysis of the actual reported some error
11452 if Etype
(Actual
) = Any_Type
then
11456 -- This check is performed here because Analyze_Object_Renaming will
11457 -- not check it when Comes_From_Source is False. Note though that the
11458 -- check for the actual being the name of an object will be performed
11459 -- in Analyze_Object_Renaming.
11461 if Is_Object_Reference
(Actual
)
11462 and then Is_Dependent_Component_Of_Mutable_Object
(Actual
)
11465 ("illegal discriminant-dependent component for in out parameter",
11469 -- The actual has to be resolved in order to check that it is a
11470 -- variable (due to cases such as F (1), where F returns access to
11471 -- an array, and for overloaded prefixes).
11473 Ftyp
:= Get_Instance_Of
(Etype
(A_Gen_Obj
));
11475 -- If the type of the formal is not itself a formal, and the current
11476 -- unit is a child unit, the formal type must be declared in a
11477 -- parent, and must be retrieved by visibility.
11479 if Ftyp
= Orig_Ftyp
11480 and then Is_Generic_Unit
(Scope
(Ftyp
))
11481 and then Is_Child_Unit
(Scope
(A_Gen_Obj
))
11484 Temp
: constant Node_Id
:=
11485 New_Copy_Tree
(Subtype_Mark
(Analyzed_Formal
));
11487 Set_Entity
(Temp
, Empty
);
11489 Ftyp
:= Entity
(Temp
);
11493 if Is_Private_Type
(Ftyp
)
11494 and then not Is_Private_Type
(Etype
(Actual
))
11495 and then (Base_Type
(Full_View
(Ftyp
)) = Base_Type
(Etype
(Actual
))
11496 or else Base_Type
(Etype
(Actual
)) = Ftyp
)
11498 -- If the actual has the type of the full view of the formal, or
11499 -- else a non-private subtype of the formal, then the visibility
11500 -- of the formal type has changed. Add to the actuals a subtype
11501 -- declaration that will force the exchange of views in the body
11502 -- of the instance as well.
11505 Make_Subtype_Declaration
(Loc
,
11506 Defining_Identifier
=> Make_Temporary
(Loc
, 'P'),
11507 Subtype_Indication
=> New_Occurrence_Of
(Ftyp
, Loc
));
11509 Prepend
(Subt_Decl
, List
);
11511 Prepend_Elmt
(Full_View
(Ftyp
), Exchanged_Views
);
11512 Exchange_Declarations
(Ftyp
);
11515 Resolve
(Actual
, Ftyp
);
11517 if not Denotes_Variable
(Actual
) then
11518 Error_Msg_NE
("actual for& must be a variable", Actual
, Gen_Obj
);
11520 elsif Base_Type
(Ftyp
) /= Base_Type
(Etype
(Actual
)) then
11522 -- Ada 2005 (AI-423): For a generic formal object of mode in out,
11523 -- the type of the actual shall resolve to a specific anonymous
11526 if Ada_Version
< Ada_2005
11527 or else not Is_Anonymous_Access_Type
(Base_Type
(Ftyp
))
11528 or else not Is_Anonymous_Access_Type
(Base_Type
(Etype
(Actual
)))
11531 ("type of actual does not match type of&", Actual
, Gen_Obj
);
11535 Note_Possible_Modification
(Actual
, Sure
=> True);
11537 -- Check for instantiation with atomic/volatile/VFA object actual for
11538 -- nonatomic/nonvolatile/nonVFA formal (RM C.6 (12)).
11540 if Is_Atomic_Object
(Actual
) and then not Is_Atomic
(Orig_Ftyp
) then
11542 ("cannot instantiate nonatomic formal & of mode in out",
11544 Error_Msg_N
("\with atomic object actual (RM C.6(12))", Actual
);
11546 elsif Is_Volatile_Object_Ref
(Actual
)
11547 and then not Is_Volatile
(Orig_Ftyp
)
11550 ("cannot instantiate nonvolatile formal & of mode in out",
11552 Error_Msg_N
("\with volatile object actual (RM C.6(12))", Actual
);
11554 elsif Is_Volatile_Full_Access_Object_Ref
(Actual
)
11555 and then not Is_Volatile_Full_Access
(Orig_Ftyp
)
11558 ("cannot instantiate nonfull access formal & of mode in out",
11561 ("\with full access object actual (RM C.6(12))", Actual
);
11564 -- Check for instantiation on nonatomic subcomponent of a full access
11565 -- object in Ada 2022 (RM C.6 (12)).
11567 if Ada_Version
>= Ada_2022
11568 and then Is_Subcomponent_Of_Full_Access_Object
(Actual
)
11569 and then not Is_Atomic_Object
(Actual
)
11572 ("cannot instantiate formal & of mode in out with actual",
11575 ("\nonatomic subcomponent of full access object (RM C.6(12))",
11579 -- Check actual/formal compatibility with respect to the four
11580 -- volatility refinement aspects.
11583 Actual_Obj
: constant Entity_Id
:=
11584 Get_Enclosing_Deep_Object
(Actual
);
11586 Check_Volatility_Compatibility
11587 (Actual_Obj
, A_Gen_Obj
, "actual object",
11588 "its corresponding formal object of mode in out",
11589 Srcpos_Bearer
=> Actual
);
11592 -- The actual for a ghost generic formal IN OUT parameter should be a
11593 -- ghost object (SPARK RM 6.9(14)).
11595 Check_Ghost_Formal_Variable
11597 Formal
=> A_Gen_Obj
);
11599 -- Formal in-parameter
11602 -- The instantiation of a generic formal in-parameter is constant
11603 -- declaration. The actual is the expression for that declaration.
11604 -- Its type is a full copy of the type of the formal. This may be
11605 -- an access to subprogram, for which we need to generate entities
11606 -- for the formals in the new signature.
11608 if Present
(Actual
) then
11609 if Present
(Subt_Mark
) then
11610 Def
:= New_Copy_Tree
(Subt_Mark
);
11612 pragma Assert
(Present
(Acc_Def
));
11613 Def
:= New_Copy_Tree
(Acc_Def
);
11617 Make_Object_Declaration
(Loc
,
11618 Defining_Identifier
=> New_Copy
(Gen_Obj
),
11619 Constant_Present
=> True,
11620 Null_Exclusion_Present
=> Null_Exclusion_Present
(Formal
),
11621 Object_Definition
=> Def
,
11622 Expression
=> Actual
);
11624 Copy_Ghost_Aspect
(Formal
, To
=> Decl_Node
);
11625 Set_Corresponding_Generic_Association
(Decl_Node
, Act_Assoc
);
11627 -- A generic formal object of a tagged type is defined to be
11628 -- aliased so the new constant must also be treated as aliased.
11630 if Is_Tagged_Type
(Etype
(A_Gen_Obj
)) then
11631 Set_Aliased_Present
(Decl_Node
);
11634 Append
(Decl_Node
, List
);
11636 -- The actual for a ghost generic formal IN parameter of
11637 -- access-to-variable type should be a ghost object (SPARK
11640 if Is_Access_Variable
(Etype
(A_Gen_Obj
)) then
11641 Check_Ghost_Formal_Variable
11643 Formal
=> A_Gen_Obj
);
11646 -- No need to repeat (pre-)analysis of some expression nodes
11647 -- already handled in Preanalyze_Actuals.
11649 if Nkind
(Actual
) /= N_Allocator
then
11652 -- Return if the analysis of the actual reported some error
11654 if Etype
(Actual
) = Any_Type
then
11660 Formal_Type
: constant Entity_Id
:= Etype
(A_Gen_Obj
);
11664 Typ
:= Get_Instance_Of
(Formal_Type
);
11666 -- If the actual appears in the current or an enclosing scope,
11667 -- use its type directly. This is relevant if it has an actual
11668 -- subtype that is distinct from its nominal one. This cannot
11669 -- be done in general because the type of the actual may
11670 -- depend on other actuals, and only be fully determined when
11671 -- the enclosing instance is analyzed.
11673 if Present
(Etype
(Actual
))
11674 and then Is_Constr_Subt_For_U_Nominal
(Etype
(Actual
))
11676 Freeze_Before
(Instantiation_Node
, Etype
(Actual
));
11678 Freeze_Before
(Instantiation_Node
, Typ
);
11681 -- If the actual is an aggregate, perform name resolution on
11682 -- its components (the analysis of an aggregate does not do it)
11683 -- to capture local names that may be hidden if the generic is
11686 if Nkind
(Actual
) = N_Aggregate
then
11687 Preanalyze_And_Resolve
(Actual
, Typ
);
11690 if Is_Limited_Type
(Typ
)
11691 and then not OK_For_Limited_Init
(Typ
, Actual
)
11694 ("initialization not allowed for limited types", Actual
);
11695 Explain_Limited_Type
(Typ
, Actual
);
11699 elsif Present
(Default_Expression
(Formal
)) then
11701 -- Use default to construct declaration
11703 if Present
(Subt_Mark
) then
11704 Def
:= New_Copy_Tree
(Subt_Mark
);
11706 pragma Assert
(Present
(Acc_Def
));
11707 Def
:= New_Copy_Tree
(Acc_Def
);
11711 Make_Object_Declaration
(Sloc
(Formal
),
11712 Defining_Identifier
=> New_Copy
(Gen_Obj
),
11713 Constant_Present
=> True,
11714 Null_Exclusion_Present
=> Null_Exclusion_Present
(Formal
),
11715 Object_Definition
=> Def
,
11716 Expression
=> New_Copy_Tree
11717 (Default_Expression
(Formal
)));
11719 Copy_Ghost_Aspect
(Formal
, To
=> Decl_Node
);
11720 Set_Corresponding_Generic_Association
11721 (Decl_Node
, Expression
(Decl_Node
));
11723 Append
(Decl_Node
, List
);
11724 Set_Analyzed
(Expression
(Decl_Node
), False);
11727 Error_Msg_NE
("missing actual&", Instantiation_Node
, Gen_Obj
);
11728 Error_Msg_NE
("\in instantiation of & declared#",
11729 Instantiation_Node
, Scope
(A_Gen_Obj
));
11731 if Is_Scalar_Type
(Etype
(A_Gen_Obj
)) then
11733 -- Create dummy constant declaration so that instance can be
11734 -- analyzed, to minimize cascaded visibility errors.
11736 if Present
(Subt_Mark
) then
11738 else pragma Assert
(Present
(Acc_Def
));
11743 Make_Object_Declaration
(Loc
,
11744 Defining_Identifier
=> New_Copy
(Gen_Obj
),
11745 Constant_Present
=> True,
11746 Null_Exclusion_Present
=> Null_Exclusion_Present
(Formal
),
11747 Object_Definition
=> New_Copy
(Def
),
11749 Make_Attribute_Reference
(Sloc
(Gen_Obj
),
11750 Attribute_Name
=> Name_First
,
11751 Prefix
=> New_Copy
(Def
)));
11753 Append
(Decl_Node
, List
);
11756 Abandon_Instantiation
(Instantiation_Node
);
11761 if Nkind
(Actual
) in N_Has_Entity
11762 and then Present
(Entity
(Actual
))
11764 Actual_Decl
:= Parent
(Entity
(Actual
));
11767 -- Ada 2005 (AI-423) refined by AI12-0287:
11768 -- For an object_renaming_declaration with a null_exclusion or an
11769 -- access_definition that has a null_exclusion, the subtype of the
11770 -- object_name shall exclude null. In addition, if the
11771 -- object_renaming_declaration occurs within the body of a generic unit
11772 -- G or within the body of a generic unit declared within the
11773 -- declarative region of generic unit G, then:
11774 -- * if the object_name statically denotes a generic formal object of
11775 -- mode in out of G, then the declaration of that object shall have a
11777 -- * if the object_name statically denotes a call of a generic formal
11778 -- function of G, then the declaration of the result of that function
11779 -- shall have a null_exclusion.
11781 if Ada_Version
>= Ada_2005
11782 and then Present
(Actual_Decl
)
11783 and then Nkind
(Actual_Decl
) in N_Formal_Object_Declaration
11784 | N_Object_Declaration
11785 and then Nkind
(Analyzed_Formal
) = N_Formal_Object_Declaration
11786 and then not Has_Null_Exclusion
(Actual_Decl
)
11787 and then Has_Null_Exclusion
(Analyzed_Formal
)
11788 and then Ekind
(Defining_Identifier
(Analyzed_Formal
))
11789 = E_Generic_In_Out_Parameter
11790 and then ((In_Generic_Scope
(Entity
(Actual
))
11791 and then In_Package_Body
(Scope
(Entity
(Actual
))))
11792 or else not Can_Never_Be_Null
(Etype
(Actual
)))
11794 Error_Msg_Sloc
:= Sloc
(Analyzed_Formal
);
11796 ("actual must exclude null to match generic formal#", Actual
);
11799 -- An effectively volatile object cannot be used as an actual in a
11800 -- generic instantiation (SPARK RM 7.1.3(7)). The following check is
11801 -- relevant only when SPARK_Mode is on as it is not a standard Ada
11802 -- legality rule, and also verifies that the actual is an object.
11805 and then Present
(Actual
)
11806 and then Is_Object_Reference
(Actual
)
11807 and then Is_Effectively_Volatile_Object
(Actual
)
11808 and then not Is_Effectively_Volatile
(A_Gen_Obj
)
11811 ("volatile object cannot act as actual in generic instantiation",
11816 end Instantiate_Object
;
11818 ------------------------------
11819 -- Instantiate_Package_Body --
11820 ------------------------------
11822 -- WARNING: This routine manages Ghost and SPARK regions. Return statements
11823 -- must be replaced by gotos which jump to the end of the routine in order
11824 -- to restore the Ghost and SPARK modes.
11826 procedure Instantiate_Package_Body
11827 (Body_Info
: Pending_Body_Info
;
11828 Inlined_Body
: Boolean := False;
11829 Body_Optional
: Boolean := False)
11831 Act_Decl
: constant Node_Id
:= Body_Info
.Act_Decl
;
11832 Act_Decl_Id
: constant Entity_Id
:= Defining_Entity
(Act_Decl
);
11833 Act_Spec
: constant Node_Id
:= Specification
(Act_Decl
);
11834 Ctx_Parents
: Elist_Id
:= No_Elist
;
11835 Ctx_Top
: Int
:= 0;
11836 Inst_Node
: constant Node_Id
:= Body_Info
.Inst_Node
;
11837 Gen_Id
: constant Node_Id
:= Name
(Inst_Node
);
11838 Gen_Unit
: constant Entity_Id
:= Get_Generic_Entity
(Inst_Node
);
11839 Gen_Decl
: constant Node_Id
:= Unit_Declaration_Node
(Gen_Unit
);
11840 Loc
: constant Source_Ptr
:= Sloc
(Inst_Node
);
11842 procedure Check_Initialized_Types
;
11843 -- In a generic package body, an entity of a generic private type may
11844 -- appear uninitialized. This is suspicious, unless the actual is a
11845 -- fully initialized type.
11847 procedure Install_Parents_Of_Generic_Context
11848 (Inst_Scope
: Entity_Id
;
11849 Ctx_Parents
: out Elist_Id
);
11850 -- Inst_Scope is the scope where the instance appears within; when it
11851 -- appears within a generic child package G, this routine collects and
11852 -- installs the enclosing packages of G in the scopes stack; installed
11853 -- packages are returned in Ctx_Parents.
11855 procedure Remove_Parents_Of_Generic_Context
(Ctx_Parents
: Elist_Id
);
11856 -- Reverse effect after instantiation is complete
11858 -----------------------------
11859 -- Check_Initialized_Types --
11860 -----------------------------
11862 procedure Check_Initialized_Types
is
11864 Formal
: Entity_Id
;
11865 Actual
: Entity_Id
;
11866 Uninit_Var
: Entity_Id
;
11869 Decl
:= First
(Generic_Formal_Declarations
(Gen_Decl
));
11870 while Present
(Decl
) loop
11871 Uninit_Var
:= Empty
;
11873 if Nkind
(Decl
) = N_Private_Extension_Declaration
then
11874 Uninit_Var
:= Uninitialized_Variable
(Decl
);
11876 elsif Nkind
(Decl
) = N_Formal_Type_Declaration
11877 and then Nkind
(Formal_Type_Definition
(Decl
)) =
11878 N_Formal_Private_Type_Definition
11881 Uninitialized_Variable
(Formal_Type_Definition
(Decl
));
11884 if Present
(Uninit_Var
) then
11885 Formal
:= Defining_Identifier
(Decl
);
11886 Actual
:= First_Entity
(Act_Decl_Id
);
11888 -- For each formal there is a subtype declaration that renames
11889 -- the actual and has the same name as the formal. Locate the
11890 -- formal for warning message about uninitialized variables
11891 -- in the generic, for which the actual type should be a fully
11892 -- initialized type.
11894 while Present
(Actual
) loop
11895 exit when Ekind
(Actual
) = E_Package
11896 and then Present
(Renamed_Entity
(Actual
));
11898 if Chars
(Actual
) = Chars
(Formal
)
11899 and then not Is_Scalar_Type
(Actual
)
11900 and then not Is_Fully_Initialized_Type
(Actual
)
11901 and then Warn_On_No_Value_Assigned
11903 Error_Msg_Node_2
:= Formal
;
11905 ("generic unit has uninitialized variable& of "
11906 & "formal private type &?v?", Actual
, Uninit_Var
);
11908 ("actual type for& should be fully initialized type?v?",
11913 Next_Entity
(Actual
);
11919 end Check_Initialized_Types
;
11921 ----------------------------------------
11922 -- Install_Parents_Of_Generic_Context --
11923 ----------------------------------------
11925 procedure Install_Parents_Of_Generic_Context
11926 (Inst_Scope
: Entity_Id
;
11927 Ctx_Parents
: out Elist_Id
)
11933 Ctx_Parents
:= New_Elmt_List
;
11935 -- Collect context parents (ie. parents where the instantiation
11936 -- appears within).
11939 while S
/= Standard_Standard
loop
11940 Prepend_Elmt
(S
, Ctx_Parents
);
11944 -- Install enclosing parents
11946 Elmt
:= First_Elmt
(Ctx_Parents
);
11947 while Present
(Elmt
) loop
11948 Push_Scope
(Node
(Elmt
));
11949 Set_Is_Immediately_Visible
(Node
(Elmt
));
11952 end Install_Parents_Of_Generic_Context
;
11954 ---------------------------------------
11955 -- Remove_Parents_Of_Generic_Context --
11956 ---------------------------------------
11958 procedure Remove_Parents_Of_Generic_Context
(Ctx_Parents
: Elist_Id
) is
11962 -- Traverse Ctx_Parents in LIFO order to check the removed scopes
11964 Elmt
:= Last_Elmt
(Ctx_Parents
);
11965 while Present
(Elmt
) loop
11966 pragma Assert
(Current_Scope
= Node
(Elmt
));
11967 Set_Is_Immediately_Visible
(Current_Scope
, False);
11970 Remove_Last_Elmt
(Ctx_Parents
);
11971 Elmt
:= Last_Elmt
(Ctx_Parents
);
11973 end Remove_Parents_Of_Generic_Context
;
11977 -- The following constants capture the context prior to instantiating
11978 -- the package body.
11980 Saved_CS
: constant Config_Switches_Type
:= Save_Config_Switches
;
11981 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
11982 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
11983 Saved_ISMP
: constant Boolean :=
11984 Ignore_SPARK_Mode_Pragmas_In_Instance
;
11985 Saved_LSST
: constant Suppress_Stack_Entry_Ptr
:=
11986 Local_Suppress_Stack_Top
;
11987 Saved_SC
: constant Boolean := Style_Check
;
11988 Saved_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
11989 Saved_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
11990 Saved_SS
: constant Suppress_Record
:= Scope_Suppress
;
11991 Saved_Warn
: constant Warnings_State
:= Save_Warnings
;
11993 Act_Body
: Node_Id
;
11994 Act_Body_Id
: Entity_Id
;
11995 Act_Body_Name
: Node_Id
;
11996 Gen_Body
: Node_Id
;
11997 Gen_Body_Id
: Node_Id
;
11998 Par_Ent
: Entity_Id
:= Empty
;
11999 Par_Installed
: Boolean := False;
12000 Par_Vis
: Boolean := False;
12002 Scope_Check_Id
: Entity_Id
;
12003 Scope_Check_Last
: Nat
;
12004 -- Value of Current_Scope before calls to Install_Parents; used to check
12005 -- that scopes are correctly removed after instantiation.
12007 Vis_Prims_List
: Elist_Id
:= No_Elist
;
12008 -- List of primitives made temporarily visible in the instantiation
12009 -- to match the visibility of the formal type.
12011 -- Start of processing for Instantiate_Package_Body
12014 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
12016 -- The instance body may already have been processed, as the parent of
12017 -- another instance that is inlined (Load_Parent_Of_Generic).
12019 if Present
(Corresponding_Body
(Instance_Spec
(Inst_Node
))) then
12023 Expander_Mode_Save_And_Set
(Body_Info
.Expander_Status
);
12025 -- Re-establish the state of information on which checks are suppressed.
12026 -- This information was set in Body_Info at the point of instantiation,
12027 -- and now we restore it so that the instance is compiled using the
12028 -- check status at the instantiation (RM 11.5(7.2/2), AI95-00224-01).
12030 Local_Suppress_Stack_Top
:= Body_Info
.Local_Suppress_Stack_Top
;
12031 Scope_Suppress
:= Body_Info
.Scope_Suppress
;
12033 Restore_Config_Switches
(Body_Info
.Config_Switches
);
12034 Restore_Warnings
(Body_Info
.Warnings
);
12036 if No
(Gen_Body_Id
) then
12038 -- Do not look for parent of generic body if none is required.
12039 -- This may happen when the routine is called as part of the
12040 -- Pending_Instantiations processing, when nested instances
12041 -- may precede the one generated from the main unit.
12043 if not Unit_Requires_Body
(Defining_Entity
(Gen_Decl
))
12044 and then Body_Optional
12048 Load_Parent_Of_Generic
12049 (Inst_Node
, Specification
(Gen_Decl
), Body_Optional
);
12051 -- Surprisingly enough, loading the body of the parent can cause
12052 -- the body to be instantiated and the double instantiation needs
12053 -- to be prevented in order to avoid giving bogus semantic errors.
12055 -- This case can occur because of the Collect_Previous_Instances
12056 -- machinery of Load_Parent_Of_Generic, which will instantiate
12057 -- bodies that are deemed to be ahead of the body of the parent
12058 -- in the compilation unit. But the relative position of these
12059 -- bodies is computed using the mere comparison of their Sloc.
12061 -- Now suppose that you have two generic packages G and H, with
12062 -- G containing a mere instantiation of H:
12068 -- package Nested_G is
12079 -- package My_H is new H;
12083 -- and a third package Q instantiating G and Nested_G:
12089 -- package My_G is new G;
12091 -- package My_Nested_G is new My_G.My_H.Nested_G;
12095 -- The body to be instantiated is that of My_Nested_G and its
12096 -- parent is the instance My_G.My_H. This latter instantiation
12097 -- is done when My_G is analyzed, i.e. after the declarations
12098 -- of My_G and My_Nested_G have been parsed; as a result, the
12099 -- Sloc of My_G.My_H is greater than the Sloc of My_Nested_G.
12101 -- Therefore loading the body of My_G.My_H will cause the body
12102 -- of My_Nested_G to be instantiated because it is deemed to be
12103 -- ahead of My_G.My_H. This means that Load_Parent_Of_Generic
12104 -- will again be invoked on My_G.My_H, but this time with the
12105 -- Collect_Previous_Instances machinery disabled, so there is
12106 -- no endless mutual recursion and things are done in order.
12108 if Present
(Corresponding_Body
(Instance_Spec
(Inst_Node
))) then
12112 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
12116 -- Establish global variable for sloc adjustment and for error recovery
12117 -- In the case of an instance body for an instantiation with actuals
12118 -- from a limited view, the instance body is placed at the beginning
12119 -- of the enclosing package body: use the body entity as the source
12120 -- location for nodes of the instance body.
12122 if not Is_Empty_Elmt_List
(Incomplete_Actuals
(Act_Decl_Id
)) then
12124 Scop
: constant Entity_Id
:= Scope
(Act_Decl_Id
);
12125 Body_Id
: constant Node_Id
:=
12126 Corresponding_Body
(Unit_Declaration_Node
(Scop
));
12129 Instantiation_Node
:= Body_Id
;
12132 Instantiation_Node
:= Inst_Node
;
12135 -- The package being instantiated may be subject to pragma Ghost. Set
12136 -- the mode now to ensure that any nodes generated during instantiation
12137 -- are properly marked as Ghost.
12139 Set_Ghost_Mode
(Act_Decl_Id
);
12141 if Present
(Gen_Body_Id
) then
12142 Save_Env
(Gen_Unit
, Act_Decl_Id
);
12143 Style_Check
:= False;
12145 -- If the context of the instance is subject to SPARK_Mode "off", the
12146 -- annotation is missing, or the body is instantiated at a later pass
12147 -- and its spec ignored SPARK_Mode pragma, set the global flag which
12148 -- signals Analyze_Pragma to ignore all SPARK_Mode pragmas within the
12151 if SPARK_Mode
/= On
12152 or else Ignore_SPARK_Mode_Pragmas
(Act_Decl_Id
)
12154 Ignore_SPARK_Mode_Pragmas_In_Instance
:= True;
12157 Current_Sem_Unit
:= Body_Info
.Current_Sem_Unit
;
12158 Gen_Body
:= Unit_Declaration_Node
(Gen_Body_Id
);
12160 Create_Instantiation_Source
12161 (Inst_Node
, Gen_Body_Id
, S_Adjustment
);
12165 (Original_Node
(Gen_Body
), Empty
, Instantiating
=> True);
12167 -- Create proper (possibly qualified) defining name for the body, to
12168 -- correspond to the one in the spec.
12171 Make_Defining_Identifier
(Sloc
(Act_Decl_Id
), Chars
(Act_Decl_Id
));
12172 Preserve_Comes_From_Source
(Act_Body_Id
, Act_Decl_Id
);
12174 -- Some attributes of spec entity are not inherited by body entity
12176 Set_Handler_Records
(Act_Body_Id
, No_List
);
12178 if Nkind
(Defining_Unit_Name
(Act_Spec
)) =
12179 N_Defining_Program_Unit_Name
12182 Make_Defining_Program_Unit_Name
(Loc
,
12184 New_Copy_Tree
(Name
(Defining_Unit_Name
(Act_Spec
))),
12185 Defining_Identifier
=> Act_Body_Id
);
12187 Act_Body_Name
:= Act_Body_Id
;
12190 Set_Defining_Unit_Name
(Act_Body
, Act_Body_Name
);
12192 Set_Corresponding_Spec
(Act_Body
, Act_Decl_Id
);
12193 Check_Generic_Actuals
(Act_Decl_Id
, False);
12194 Check_Initialized_Types
;
12196 -- Install primitives hidden at the point of the instantiation but
12197 -- visible when processing the generic formals
12203 E
:= First_Entity
(Act_Decl_Id
);
12204 while Present
(E
) loop
12206 and then not Is_Itype
(E
)
12207 and then Is_Generic_Actual_Type
(E
)
12208 and then Is_Tagged_Type
(E
)
12210 Install_Hidden_Primitives
12211 (Prims_List
=> Vis_Prims_List
,
12212 Gen_T
=> Generic_Parent_Type
(Parent
(E
)),
12220 Scope_Check_Id
:= Current_Scope
;
12221 Scope_Check_Last
:= Scope_Stack
.Last
;
12223 -- If the instantiation appears within a generic child some actual
12224 -- parameter may be the current instance of the enclosing generic
12228 Inst_Scope
: constant Entity_Id
:= Scope
(Act_Decl_Id
);
12231 if Is_Child_Unit
(Inst_Scope
)
12232 and then Ekind
(Inst_Scope
) = E_Generic_Package
12233 and then Present
(Generic_Associations
(Inst_Node
))
12235 Install_Parents_Of_Generic_Context
(Inst_Scope
, Ctx_Parents
);
12237 -- Hide them from visibility; required to avoid conflicts
12238 -- installing the parent instance.
12240 if Present
(Ctx_Parents
) then
12241 Push_Scope
(Standard_Standard
);
12242 Ctx_Top
:= Scope_Stack
.Last
;
12243 Scope_Stack
.Table
(Ctx_Top
).Is_Active_Stack_Base
:= True;
12248 -- If it is a child unit, make the parent instance (which is an
12249 -- instance of the parent of the generic) visible.
12251 -- 1) The child unit's parent is an explicit parent instance (the
12252 -- prefix of the name of the generic unit):
12254 -- package Child_Package is new Parent_Instance.Child_Unit;
12256 -- 2) The child unit's parent is an implicit parent instance (e.g.
12257 -- when instantiating a sibling package):
12260 -- package Parent.Second_Child is
12264 -- package Parent.First_Child is
12265 -- package Sibling_Package is new Second_Child;
12267 -- 3) The child unit's parent is not an instance, so the scope is
12268 -- simply the one of the unit.
12270 if Ekind
(Scope
(Gen_Unit
)) = E_Generic_Package
12271 and then Nkind
(Gen_Id
) = N_Expanded_Name
12273 Par_Ent
:= Entity
(Prefix
(Gen_Id
));
12275 elsif Ekind
(Scope
(Gen_Unit
)) = E_Generic_Package
12276 and then Ekind
(Scope
(Act_Decl_Id
)) = E_Package
12277 and then Is_Generic_Instance
(Scope
(Act_Decl_Id
))
12279 (Name
(Get_Unit_Instantiation_Node
12280 (Scope
(Act_Decl_Id
)))) = N_Expanded_Name
12283 (Prefix
(Name
(Get_Unit_Instantiation_Node
12284 (Scope
(Act_Decl_Id
)))));
12286 elsif Is_Child_Unit
(Gen_Unit
) then
12287 Par_Ent
:= Scope
(Gen_Unit
);
12290 if Present
(Par_Ent
) then
12291 Par_Vis
:= Is_Immediately_Visible
(Par_Ent
);
12292 Install_Parent
(Par_Ent
, In_Body
=> True);
12293 Par_Installed
:= True;
12296 -- If the instantiation is a library unit, and this is the main unit,
12297 -- then build the resulting compilation unit nodes for the instance.
12298 -- If this is a compilation unit but it is not the main unit, then it
12299 -- is the body of a unit in the context, that is being compiled
12300 -- because it is encloses some inlined unit or another generic unit
12301 -- being instantiated. In that case, this body is not part of the
12302 -- current compilation, and is not attached to the tree, but its
12303 -- parent must be set for analysis.
12305 if Nkind
(Parent
(Inst_Node
)) = N_Compilation_Unit
then
12307 -- Replace instance node with body of instance, and create new
12308 -- node for corresponding instance declaration.
12310 Build_Instance_Compilation_Unit_Nodes
12311 (Inst_Node
, Act_Body
, Act_Decl
);
12313 -- If the instantiation appears within a generic child package
12314 -- enable visibility of current instance of enclosing generic
12317 if Present
(Ctx_Parents
) then
12318 Scope_Stack
.Table
(Ctx_Top
).Is_Active_Stack_Base
:= False;
12319 Analyze
(Inst_Node
);
12320 Scope_Stack
.Table
(Ctx_Top
).Is_Active_Stack_Base
:= True;
12322 Analyze
(Inst_Node
);
12325 if Parent
(Inst_Node
) = Cunit
(Main_Unit
) then
12327 -- If the instance is a child unit itself, then set the scope
12328 -- of the expanded body to be the parent of the instantiation
12329 -- (ensuring that the fully qualified name will be generated
12330 -- for the elaboration subprogram).
12332 if Nkind
(Defining_Unit_Name
(Act_Spec
)) =
12333 N_Defining_Program_Unit_Name
12335 Set_Scope
(Defining_Entity
(Inst_Node
), Scope
(Act_Decl_Id
));
12339 -- Case where instantiation is not a library unit
12342 -- Handle the case of an instance with incomplete actual types.
12343 -- The instance body cannot be placed just after the declaration
12344 -- because full views have not been seen yet. Any use of the non-
12345 -- limited views in the instance body requires the presence of a
12346 -- regular with_clause in the enclosing unit. Therefore we place
12347 -- the instance body at the beginning of the enclosing body, and
12348 -- the freeze node for the instance is then placed after the body.
12350 if not Is_Empty_Elmt_List
(Incomplete_Actuals
(Act_Decl_Id
))
12351 and then Ekind
(Scope
(Act_Decl_Id
)) = E_Package
12354 Scop
: constant Entity_Id
:= Scope
(Act_Decl_Id
);
12355 Body_Id
: constant Node_Id
:=
12356 Corresponding_Body
(Unit_Declaration_Node
(Scop
));
12361 pragma Assert
(Present
(Body_Id
));
12363 Prepend
(Act_Body
, Declarations
(Parent
(Body_Id
)));
12365 if Expander_Active
then
12366 Ensure_Freeze_Node
(Act_Decl_Id
);
12367 F_Node
:= Freeze_Node
(Act_Decl_Id
);
12368 Set_Is_Frozen
(Act_Decl_Id
, False);
12369 if Is_List_Member
(F_Node
) then
12373 Insert_After
(Act_Body
, F_Node
);
12378 Insert_Before
(Inst_Node
, Act_Body
);
12379 Mark_Rewrite_Insertion
(Act_Body
);
12381 -- Insert the freeze node for the instance if need be
12383 if Expander_Active
then
12384 Freeze_Package_Instance
12385 (Inst_Node
, Gen_Body
, Gen_Decl
, Act_Decl_Id
);
12386 Set_Is_Frozen
(Act_Decl_Id
);
12390 -- If the instantiation appears within a generic child package
12391 -- enable visibility of current instance of enclosing generic
12394 if Present
(Ctx_Parents
) then
12395 Scope_Stack
.Table
(Ctx_Top
).Is_Active_Stack_Base
:= False;
12396 Analyze
(Act_Body
);
12397 Scope_Stack
.Table
(Ctx_Top
).Is_Active_Stack_Base
:= True;
12399 Analyze
(Act_Body
);
12403 Inherit_Context
(Gen_Body
, Inst_Node
);
12405 if Par_Installed
then
12406 Remove_Parent
(In_Body
=> True);
12408 -- Restore the previous visibility of the parent
12410 Set_Is_Immediately_Visible
(Par_Ent
, Par_Vis
);
12413 -- Remove the parent instances if they have been placed on the scope
12414 -- stack to compile the body.
12416 if Present
(Ctx_Parents
) then
12417 pragma Assert
(Scope_Stack
.Last
= Ctx_Top
12418 and then Current_Scope
= Standard_Standard
);
12421 Remove_Parents_Of_Generic_Context
(Ctx_Parents
);
12424 pragma Assert
(Current_Scope
= Scope_Check_Id
);
12425 pragma Assert
(Scope_Stack
.Last
= Scope_Check_Last
);
12427 Restore_Hidden_Primitives
(Vis_Prims_List
);
12429 -- Restore the private views that were made visible when the body of
12430 -- the instantiation was created. Note that, in the case where one of
12431 -- these private views is declared in the parent, there is a nesting
12432 -- issue with the calls to Install_Parent and Remove_Parent made in
12433 -- between above with In_Body set to True, because these calls also
12434 -- want to swap and restore this private view respectively. In this
12435 -- case, the call to Install_Parent does nothing, but the call to
12436 -- Remove_Parent does restore the private view, thus undercutting the
12437 -- call to Restore_Private_Views. That's OK under the condition that
12438 -- the two mechanisms swap exactly the same entities, in particular
12439 -- the private entities dependent on the primary private entities.
12441 Restore_Private_Views
(Act_Decl_Id
);
12443 -- Remove the current unit from visibility if this is an instance
12444 -- that is not elaborated on the fly for inlining purposes.
12446 if not Inlined_Body
then
12447 Set_Is_Immediately_Visible
(Act_Decl_Id
, False);
12452 -- If we have no body, and the unit requires a body, then complain. This
12453 -- complaint is suppressed if we have detected other errors (since a
12454 -- common reason for missing the body is that it had errors).
12455 -- In CodePeer mode, a warning has been emitted already, no need for
12456 -- further messages.
12458 elsif Unit_Requires_Body
(Gen_Unit
)
12459 and then not Body_Optional
12461 if CodePeer_Mode
then
12464 elsif Serious_Errors_Detected
= 0 then
12466 ("cannot find body of generic package &", Inst_Node
, Gen_Unit
);
12468 -- Don't attempt to perform any cleanup actions if some other error
12469 -- was already detected, since this can cause blowups.
12475 -- Case of package that does not need a body
12478 -- If the instantiation of the declaration is a library unit, rewrite
12479 -- the original package instantiation as a package declaration in the
12480 -- compilation unit node.
12482 if Nkind
(Parent
(Inst_Node
)) = N_Compilation_Unit
then
12483 Set_Parent_Spec
(Act_Decl
, Parent_Spec
(Inst_Node
));
12484 Rewrite
(Inst_Node
, Act_Decl
);
12486 -- Generate elaboration entity, in case spec has elaboration code.
12487 -- This cannot be done when the instance is analyzed, because it
12488 -- is not known yet whether the body exists.
12490 Set_Elaboration_Entity_Required
(Act_Decl_Id
, False);
12491 Build_Elaboration_Entity
(Parent
(Inst_Node
), Act_Decl_Id
);
12493 -- If the instantiation is not a library unit, then append the
12494 -- declaration to the list of implicitly generated entities, unless
12495 -- it is already a list member which means that it was already
12498 elsif not Is_List_Member
(Act_Decl
) then
12499 Mark_Rewrite_Insertion
(Act_Decl
);
12500 Insert_Before
(Inst_Node
, Act_Decl
);
12506 -- Restore the context that was in effect prior to instantiating the
12509 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Saved_ISMP
;
12510 Local_Suppress_Stack_Top
:= Saved_LSST
;
12511 Scope_Suppress
:= Saved_SS
;
12512 Style_Check
:= Saved_SC
;
12514 Expander_Mode_Restore
;
12515 Restore_Config_Switches
(Saved_CS
);
12516 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
12517 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
12518 Restore_Warnings
(Saved_Warn
);
12519 end Instantiate_Package_Body
;
12521 ---------------------------------
12522 -- Instantiate_Subprogram_Body --
12523 ---------------------------------
12525 -- WARNING: This routine manages Ghost and SPARK regions. Return statements
12526 -- must be replaced by gotos which jump to the end of the routine in order
12527 -- to restore the Ghost and SPARK modes.
12529 procedure Instantiate_Subprogram_Body
12530 (Body_Info
: Pending_Body_Info
;
12531 Body_Optional
: Boolean := False)
12533 Act_Decl
: constant Node_Id
:= Body_Info
.Act_Decl
;
12534 Act_Decl_Id
: constant Entity_Id
:= Defining_Entity
(Act_Decl
);
12535 Inst_Node
: constant Node_Id
:= Body_Info
.Inst_Node
;
12536 Gen_Id
: constant Node_Id
:= Name
(Inst_Node
);
12537 Gen_Unit
: constant Entity_Id
:= Get_Generic_Entity
(Inst_Node
);
12538 Gen_Decl
: constant Node_Id
:= Unit_Declaration_Node
(Gen_Unit
);
12539 Loc
: constant Source_Ptr
:= Sloc
(Inst_Node
);
12540 Pack_Id
: constant Entity_Id
:=
12541 Defining_Unit_Name
(Parent
(Act_Decl
));
12543 -- The following constants capture the context prior to instantiating
12544 -- the subprogram body.
12546 Saved_CS
: constant Config_Switches_Type
:= Save_Config_Switches
;
12547 Saved_GM
: constant Ghost_Mode_Type
:= Ghost_Mode
;
12548 Saved_IGR
: constant Node_Id
:= Ignored_Ghost_Region
;
12549 Saved_ISMP
: constant Boolean :=
12550 Ignore_SPARK_Mode_Pragmas_In_Instance
;
12551 Saved_LSST
: constant Suppress_Stack_Entry_Ptr
:=
12552 Local_Suppress_Stack_Top
;
12553 Saved_SC
: constant Boolean := Style_Check
;
12554 Saved_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
12555 Saved_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
12556 Saved_SS
: constant Suppress_Record
:= Scope_Suppress
;
12557 Saved_Warn
: constant Warnings_State
:= Save_Warnings
;
12559 Act_Body
: Node_Id
;
12560 Act_Body_Id
: Entity_Id
;
12561 Gen_Body
: Node_Id
;
12562 Gen_Body_Id
: Node_Id
;
12563 Pack_Body
: Node_Id
;
12564 Par_Ent
: Entity_Id
:= Empty
;
12565 Par_Installed
: Boolean := False;
12566 Par_Vis
: Boolean := False;
12567 Ret_Expr
: Node_Id
;
12570 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
12572 -- Subprogram body may have been created already because of an inline
12573 -- pragma, or because of multiple elaborations of the enclosing package
12574 -- when several instances of the subprogram appear in the main unit.
12576 if Present
(Corresponding_Body
(Act_Decl
)) then
12580 Expander_Mode_Save_And_Set
(Body_Info
.Expander_Status
);
12582 -- Re-establish the state of information on which checks are suppressed.
12583 -- This information was set in Body_Info at the point of instantiation,
12584 -- and now we restore it so that the instance is compiled using the
12585 -- check status at the instantiation (RM 11.5(7.2/2), AI95-00224-01).
12587 Local_Suppress_Stack_Top
:= Body_Info
.Local_Suppress_Stack_Top
;
12588 Scope_Suppress
:= Body_Info
.Scope_Suppress
;
12590 Restore_Config_Switches
(Body_Info
.Config_Switches
);
12591 Restore_Warnings
(Body_Info
.Warnings
);
12593 if No
(Gen_Body_Id
) then
12595 -- For imported generic subprogram, no body to compile, complete
12596 -- the spec entity appropriately.
12598 if Is_Imported
(Gen_Unit
) then
12599 Set_Is_Imported
(Act_Decl_Id
);
12600 Set_First_Rep_Item
(Act_Decl_Id
, First_Rep_Item
(Gen_Unit
));
12601 Set_Interface_Name
(Act_Decl_Id
, Interface_Name
(Gen_Unit
));
12602 Set_Convention
(Act_Decl_Id
, Convention
(Gen_Unit
));
12603 Set_Has_Completion
(Act_Decl_Id
);
12606 -- For other cases, compile the body
12609 Load_Parent_Of_Generic
12610 (Inst_Node
, Specification
(Gen_Decl
), Body_Optional
);
12611 Gen_Body_Id
:= Corresponding_Body
(Gen_Decl
);
12615 Instantiation_Node
:= Inst_Node
;
12617 -- The subprogram being instantiated may be subject to pragma Ghost. Set
12618 -- the mode now to ensure that any nodes generated during instantiation
12619 -- are properly marked as Ghost.
12621 Set_Ghost_Mode
(Act_Decl_Id
);
12623 if Present
(Gen_Body_Id
) then
12624 Gen_Body
:= Unit_Declaration_Node
(Gen_Body_Id
);
12626 if Nkind
(Gen_Body
) = N_Subprogram_Body_Stub
then
12628 -- Either body is not present, or context is non-expanding, as
12629 -- when compiling a subunit. Mark the instance as completed, and
12630 -- diagnose a missing body when needed.
12633 and then Operating_Mode
= Generate_Code
12635 Error_Msg_N
("missing proper body for instantiation", Gen_Body
);
12638 Set_Has_Completion
(Act_Decl_Id
);
12642 Save_Env
(Gen_Unit
, Act_Decl_Id
);
12643 Style_Check
:= False;
12645 -- If the context of the instance is subject to SPARK_Mode "off", the
12646 -- annotation is missing, or the body is instantiated at a later pass
12647 -- and its spec ignored SPARK_Mode pragma, set the global flag which
12648 -- signals Analyze_Pragma to ignore all SPARK_Mode pragmas within the
12651 if SPARK_Mode
/= On
12652 or else Ignore_SPARK_Mode_Pragmas
(Act_Decl_Id
)
12654 Ignore_SPARK_Mode_Pragmas_In_Instance
:= True;
12657 -- If the context of an instance is not subject to SPARK_Mode "off",
12658 -- and the generic body is subject to an explicit SPARK_Mode pragma,
12659 -- the latter should be the one applicable to the instance.
12661 if not Ignore_SPARK_Mode_Pragmas_In_Instance
12662 and then SPARK_Mode
/= Off
12663 and then Present
(SPARK_Pragma
(Gen_Body_Id
))
12665 Set_SPARK_Mode
(Gen_Body_Id
);
12668 Current_Sem_Unit
:= Body_Info
.Current_Sem_Unit
;
12669 Create_Instantiation_Source
12676 (Original_Node
(Gen_Body
), Empty
, Instantiating
=> True);
12678 -- Create proper defining name for the body, to correspond to the one
12682 Make_Defining_Identifier
(Sloc
(Act_Decl_Id
), Chars
(Act_Decl_Id
));
12684 Preserve_Comes_From_Source
(Act_Body_Id
, Act_Decl_Id
);
12685 Set_Defining_Unit_Name
(Specification
(Act_Body
), Act_Body_Id
);
12687 Set_Corresponding_Spec
(Act_Body
, Act_Decl_Id
);
12688 Set_Has_Completion
(Act_Decl_Id
);
12689 Check_Generic_Actuals
(Pack_Id
, False);
12691 -- Generate a reference to link the visible subprogram instance to
12692 -- the generic body, which for navigation purposes is the only
12693 -- available source for the instance.
12696 (Related_Instance
(Pack_Id
),
12697 Gen_Body_Id
, 'b', Set_Ref
=> False, Force
=> True);
12699 -- If it is a child unit, make the parent instance (which is an
12700 -- instance of the parent of the generic) visible. The parent
12701 -- instance is the prefix of the name of the generic unit.
12703 if Ekind
(Scope
(Gen_Unit
)) = E_Generic_Package
12704 and then Nkind
(Gen_Id
) = N_Expanded_Name
12706 Par_Ent
:= Entity
(Prefix
(Gen_Id
));
12707 elsif Is_Child_Unit
(Gen_Unit
) then
12708 Par_Ent
:= Scope
(Gen_Unit
);
12711 if Present
(Par_Ent
) then
12712 Par_Vis
:= Is_Immediately_Visible
(Par_Ent
);
12713 Install_Parent
(Par_Ent
, In_Body
=> True);
12714 Par_Installed
:= True;
12717 -- Subprogram body is placed in the body of wrapper package,
12718 -- whose spec contains the subprogram declaration as well as
12719 -- the renaming declarations for the generic parameters.
12722 Make_Package_Body
(Loc
,
12723 Defining_Unit_Name
=> New_Copy
(Pack_Id
),
12724 Declarations
=> New_List
(Act_Body
));
12726 Set_Corresponding_Spec
(Pack_Body
, Pack_Id
);
12728 -- If the instantiation is a library unit, then build resulting
12729 -- compilation unit nodes for the instance. The declaration of
12730 -- the enclosing package is the grandparent of the subprogram
12731 -- declaration. First replace the instantiation node as the unit
12732 -- of the corresponding compilation.
12734 if Nkind
(Parent
(Inst_Node
)) = N_Compilation_Unit
then
12735 if Parent
(Inst_Node
) = Cunit
(Main_Unit
) then
12736 Set_Unit
(Parent
(Inst_Node
), Inst_Node
);
12737 Build_Instance_Compilation_Unit_Nodes
12738 (Inst_Node
, Pack_Body
, Parent
(Parent
(Act_Decl
)));
12739 Analyze
(Inst_Node
);
12741 Set_Parent
(Pack_Body
, Parent
(Inst_Node
));
12742 Analyze
(Pack_Body
);
12746 Insert_Before
(Inst_Node
, Pack_Body
);
12747 Mark_Rewrite_Insertion
(Pack_Body
);
12749 -- Insert the freeze node for the instance if need be
12751 if Expander_Active
then
12752 Freeze_Subprogram_Instance
(Inst_Node
, Gen_Body
, Pack_Id
);
12755 Analyze
(Pack_Body
);
12758 Inherit_Context
(Gen_Body
, Inst_Node
);
12760 Restore_Private_Views
(Pack_Id
, False);
12762 if Par_Installed
then
12763 Remove_Parent
(In_Body
=> True);
12765 -- Restore the previous visibility of the parent
12767 Set_Is_Immediately_Visible
(Par_Ent
, Par_Vis
);
12772 -- Body not found. Error was emitted already. If there were no previous
12773 -- errors, this may be an instance whose scope is a premature instance.
12774 -- In that case we must insure that the (legal) program does raise
12775 -- program error if executed. We generate a subprogram body for this
12778 elsif Serious_Errors_Detected
= 0
12779 and then Nkind
(Parent
(Inst_Node
)) /= N_Compilation_Unit
12781 if Body_Optional
then
12784 elsif Ekind
(Act_Decl_Id
) = E_Procedure
then
12786 Make_Subprogram_Body
(Loc
,
12788 Make_Procedure_Specification
(Loc
,
12789 Defining_Unit_Name
=>
12790 Make_Defining_Identifier
(Loc
, Chars
(Act_Decl_Id
)),
12791 Parameter_Specifications
=>
12793 (Parameter_Specifications
(Parent
(Act_Decl_Id
)))),
12795 Declarations
=> Empty_List
,
12796 Handled_Statement_Sequence
=>
12797 Make_Handled_Sequence_Of_Statements
(Loc
,
12798 Statements
=> New_List
(
12799 Make_Raise_Program_Error
(Loc
,
12800 Reason
=> PE_Access_Before_Elaboration
))));
12804 Make_Raise_Program_Error
(Loc
,
12805 Reason
=> PE_Access_Before_Elaboration
);
12807 Set_Etype
(Ret_Expr
, (Etype
(Act_Decl_Id
)));
12808 Set_Analyzed
(Ret_Expr
);
12811 Make_Subprogram_Body
(Loc
,
12813 Make_Function_Specification
(Loc
,
12814 Defining_Unit_Name
=>
12815 Make_Defining_Identifier
(Loc
, Chars
(Act_Decl_Id
)),
12816 Parameter_Specifications
=>
12818 (Parameter_Specifications
(Parent
(Act_Decl_Id
))),
12819 Result_Definition
=>
12820 New_Occurrence_Of
(Etype
(Act_Decl_Id
), Loc
)),
12822 Declarations
=> Empty_List
,
12823 Handled_Statement_Sequence
=>
12824 Make_Handled_Sequence_Of_Statements
(Loc
,
12825 Statements
=> New_List
(
12826 Make_Simple_Return_Statement
(Loc
, Ret_Expr
))));
12830 Make_Package_Body
(Loc
,
12831 Defining_Unit_Name
=> New_Copy
(Pack_Id
),
12832 Declarations
=> New_List
(Act_Body
));
12834 Insert_After
(Inst_Node
, Pack_Body
);
12835 Set_Corresponding_Spec
(Pack_Body
, Pack_Id
);
12836 Analyze
(Pack_Body
);
12841 -- Restore the context that was in effect prior to instantiating the
12842 -- subprogram body.
12844 Ignore_SPARK_Mode_Pragmas_In_Instance
:= Saved_ISMP
;
12845 Local_Suppress_Stack_Top
:= Saved_LSST
;
12846 Scope_Suppress
:= Saved_SS
;
12847 Style_Check
:= Saved_SC
;
12849 Expander_Mode_Restore
;
12850 Restore_Config_Switches
(Saved_CS
);
12851 Restore_Ghost_Region
(Saved_GM
, Saved_IGR
);
12852 Restore_SPARK_Mode
(Saved_SM
, Saved_SMP
);
12853 Restore_Warnings
(Saved_Warn
);
12854 end Instantiate_Subprogram_Body
;
12856 ----------------------
12857 -- Instantiate_Type --
12858 ----------------------
12860 function Instantiate_Type
12863 Analyzed_Formal
: Node_Id
;
12864 Actual_Decls
: List_Id
) return List_Id
12866 A_Gen_T
: constant Entity_Id
:=
12867 Defining_Identifier
(Analyzed_Formal
);
12868 Def
: constant Node_Id
:= Formal_Type_Definition
(Formal
);
12869 Gen_T
: constant Entity_Id
:= Defining_Identifier
(Formal
);
12871 Ancestor
: Entity_Id
:= Empty
;
12872 Decl_Node
: Node_Id
;
12873 Decl_Nodes
: List_Id
;
12877 procedure Check_Shared_Variable_Control_Aspects
;
12878 -- Ada 2022: Verify that shared variable control aspects (RM C.6)
12879 -- that may be specified for a formal type are obeyed by the actual.
12881 procedure Diagnose_Predicated_Actual
;
12882 -- There are a number of constructs in which a discrete type with
12883 -- predicates is illegal, e.g. as an index in an array type declaration.
12884 -- If a generic type is used is such a construct in a generic package
12885 -- declaration, it carries the flag No_Predicate_On_Actual. it is part
12886 -- of the generic contract that the actual cannot have predicates.
12888 function Subtypes_Match
(Gen_T
, Act_T
: Entity_Id
) return Boolean;
12889 -- Check that base types are the same and that the subtypes match
12890 -- statically. Used in several of the validation subprograms for
12891 -- actuals in instantiations.
12893 procedure Validate_Array_Type_Instance
;
12894 procedure Validate_Access_Subprogram_Instance
;
12895 procedure Validate_Access_Type_Instance
;
12896 procedure Validate_Derived_Type_Instance
;
12897 procedure Validate_Derived_Interface_Type_Instance
;
12898 procedure Validate_Discriminated_Formal_Type
;
12899 procedure Validate_Interface_Type_Instance
;
12900 procedure Validate_Private_Type_Instance
;
12901 procedure Validate_Incomplete_Type_Instance
;
12902 -- These procedures perform validation tests for the named case.
12903 -- Validate_Discriminated_Formal_Type is shared by formal private
12904 -- types and Ada 2012 formal incomplete types.
12906 --------------------------------------------
12907 -- Check_Shared_Variable_Control_Aspects --
12908 --------------------------------------------
12910 -- Ada 2022: Verify that shared variable control aspects (RM C.6)
12911 -- that may be specified for the formal are obeyed by the actual.
12912 -- If the formal is a derived type the aspect specifications must match.
12913 -- NOTE: AI12-0282 implies that matching of aspects is required between
12914 -- formal and actual in all cases, but this is too restrictive.
12915 -- In particular it violates a language design rule: a limited private
12916 -- indefinite formal can be matched by any actual. The current code
12917 -- reflects an older and more permissive version of RM C.6 (12/5).
12919 procedure Check_Shared_Variable_Control_Aspects
is
12921 if Ada_Version
>= Ada_2022
then
12922 if Is_Atomic
(A_Gen_T
) and then not Is_Atomic
(Act_T
) then
12924 ("actual for& must have Atomic aspect", Actual
, A_Gen_T
);
12926 elsif Is_Derived_Type
(A_Gen_T
)
12927 and then Is_Atomic
(A_Gen_T
) /= Is_Atomic
(Act_T
)
12930 ("actual for& has different Atomic aspect", Actual
, A_Gen_T
);
12933 if Is_Volatile
(A_Gen_T
) and then not Is_Volatile
(Act_T
) then
12935 ("actual for& must have Volatile aspect",
12938 elsif Is_Derived_Type
(A_Gen_T
)
12939 and then Is_Volatile
(A_Gen_T
) /= Is_Volatile
(Act_T
)
12942 ("actual for& has different Volatile aspect",
12946 -- We assume that an array type whose atomic component type
12947 -- is Atomic is equivalent to an array type with the explicit
12948 -- aspect Has_Atomic_Components. This is a reasonable inference
12949 -- from the intent of AI12-0282, and makes it legal to use an
12950 -- actual that does not have the identical aspect as the formal.
12951 -- Ditto for volatile components.
12954 Actual_Atomic_Comp
: constant Boolean :=
12955 Has_Atomic_Components
(Act_T
)
12956 or else (Is_Array_Type
(Act_T
)
12957 and then Is_Atomic
(Component_Type
(Act_T
)));
12959 if Has_Atomic_Components
(A_Gen_T
) /= Actual_Atomic_Comp
then
12961 ("formal and actual for& must agree on atomic components",
12967 Actual_Volatile_Comp
: constant Boolean :=
12968 Has_Volatile_Components
(Act_T
)
12969 or else (Is_Array_Type
(Act_T
)
12970 and then Is_Volatile
(Component_Type
(Act_T
)));
12972 if Has_Volatile_Components
(A_Gen_T
) /= Actual_Volatile_Comp
12975 ("actual for& must have volatile components",
12980 -- The following two aspects do not require exact matching,
12981 -- but only one-way agreement. See RM C.6.
12983 if Is_Independent
(A_Gen_T
) and then not Is_Independent
(Act_T
)
12986 ("actual for& must have Independent aspect specified",
12990 if Has_Independent_Components
(A_Gen_T
)
12991 and then not Has_Independent_Components
(Act_T
)
12994 ("actual for& must have Independent_Components specified",
12998 -- Check actual/formal compatibility with respect to the four
12999 -- volatility refinement aspects.
13001 Check_Volatility_Compatibility
13003 "actual type", "its corresponding formal type",
13004 Srcpos_Bearer
=> Actual
);
13006 end Check_Shared_Variable_Control_Aspects
;
13008 ---------------------------------
13009 -- Diagnose_Predicated_Actual --
13010 ---------------------------------
13012 procedure Diagnose_Predicated_Actual
is
13014 if No_Predicate_On_Actual
(A_Gen_T
)
13015 and then Has_Predicates
(Act_T
)
13018 ("actual for& cannot be a type with predicate",
13019 Instantiation_Node
, A_Gen_T
);
13021 elsif No_Dynamic_Predicate_On_Actual
(A_Gen_T
)
13022 and then Has_Predicates
(Act_T
)
13023 and then not Has_Static_Predicate_Aspect
(Act_T
)
13026 ("actual for& cannot be a type with a dynamic predicate",
13027 Instantiation_Node
, A_Gen_T
);
13029 end Diagnose_Predicated_Actual
;
13031 --------------------
13032 -- Subtypes_Match --
13033 --------------------
13035 function Subtypes_Match
(Gen_T
, Act_T
: Entity_Id
) return Boolean is
13036 T
: constant Entity_Id
:= Get_Instance_Of
(Gen_T
);
13039 -- Check that the base types, root types (when dealing with class
13040 -- wide types), or designated types (when dealing with anonymous
13041 -- access types) of Gen_T and Act_T are statically matching subtypes.
13043 return ((Base_Type
(T
) = Act_T
13044 or else Base_Type
(T
) = Base_Type
(Act_T
))
13045 and then Subtypes_Statically_Match
(T
, Act_T
))
13047 or else (Is_Class_Wide_Type
(Gen_T
)
13048 and then Is_Class_Wide_Type
(Act_T
)
13049 and then Subtypes_Match
13050 (Get_Instance_Of
(Root_Type
(Gen_T
)),
13051 Root_Type
(Act_T
)))
13053 or else (Is_Anonymous_Access_Type
(Gen_T
)
13054 and then Ekind
(Act_T
) = Ekind
(Gen_T
)
13055 and then Subtypes_Statically_Match
13056 (Designated_Type
(Gen_T
), Designated_Type
(Act_T
)));
13057 end Subtypes_Match
;
13059 -----------------------------------------
13060 -- Validate_Access_Subprogram_Instance --
13061 -----------------------------------------
13063 procedure Validate_Access_Subprogram_Instance
is
13065 if not Is_Access_Type
(Act_T
)
13066 or else Ekind
(Designated_Type
(Act_T
)) /= E_Subprogram_Type
13069 ("expect access type in instantiation of &", Actual
, Gen_T
);
13070 Abandon_Instantiation
(Actual
);
13073 -- According to AI05-288, actuals for access_to_subprograms must be
13074 -- subtype conformant with the generic formal. Previous to AI05-288
13075 -- only mode conformance was required.
13077 -- This is a binding interpretation that applies to previous versions
13078 -- of the language, no need to maintain previous weaker checks.
13080 Check_Subtype_Conformant
13081 (Designated_Type
(Act_T
),
13082 Designated_Type
(A_Gen_T
),
13086 if Ekind
(Base_Type
(Act_T
)) = E_Access_Protected_Subprogram_Type
then
13087 if Ekind
(A_Gen_T
) = E_Access_Subprogram_Type
then
13089 ("protected access type not allowed for formal &",
13093 elsif Ekind
(A_Gen_T
) = E_Access_Protected_Subprogram_Type
then
13095 ("expect protected access type for formal &",
13099 -- If the formal has a specified convention (which in most cases
13100 -- will be StdCall) verify that the actual has the same convention.
13102 if Has_Convention_Pragma
(A_Gen_T
)
13103 and then Convention
(A_Gen_T
) /= Convention
(Act_T
)
13105 Error_Msg_Name_1
:= Get_Convention_Name
(Convention
(A_Gen_T
));
13107 ("actual for formal & must have convention %", Actual
, Gen_T
);
13110 if Can_Never_Be_Null
(A_Gen_T
) /= Can_Never_Be_Null
(Act_T
) then
13112 ("non null exclusion of actual and formal & do not match",
13115 end Validate_Access_Subprogram_Instance
;
13117 -----------------------------------
13118 -- Validate_Access_Type_Instance --
13119 -----------------------------------
13121 procedure Validate_Access_Type_Instance
is
13122 Desig_Type
: constant Entity_Id
:=
13123 Find_Actual_Type
(Designated_Type
(A_Gen_T
), A_Gen_T
);
13124 Desig_Act
: Entity_Id
;
13127 if not Is_Access_Type
(Act_T
) then
13129 ("expect access type in instantiation of &", Actual
, Gen_T
);
13130 Abandon_Instantiation
(Actual
);
13133 if Is_Access_Constant
(A_Gen_T
) then
13134 if not Is_Access_Constant
(Act_T
) then
13136 ("actual type must be access-to-constant type", Actual
);
13137 Abandon_Instantiation
(Actual
);
13140 if Is_Access_Constant
(Act_T
) then
13142 ("actual type must be access-to-variable type", Actual
);
13143 Abandon_Instantiation
(Actual
);
13145 elsif Ekind
(A_Gen_T
) = E_General_Access_Type
13146 and then Ekind
(Base_Type
(Act_T
)) /= E_General_Access_Type
13149 ("actual must be general access type!", Actual
);
13150 Error_Msg_NE
-- CODEFIX
13151 ("\add ALL to }!", Actual
, Act_T
);
13152 Abandon_Instantiation
(Actual
);
13156 -- The designated subtypes, that is to say the subtypes introduced
13157 -- by an access type declaration (and not by a subtype declaration)
13160 Desig_Act
:= Designated_Type
(Base_Type
(Act_T
));
13162 -- The designated type may have been introduced through a limited_
13163 -- with clause, in which case retrieve the non-limited view. This
13164 -- applies to incomplete types as well as to class-wide types.
13166 if From_Limited_With
(Desig_Act
) then
13167 Desig_Act
:= Available_View
(Desig_Act
);
13170 if not Subtypes_Match
(Desig_Type
, Desig_Act
) then
13172 ("designated type of actual does not match that of formal &",
13175 if not Predicates_Match
(Desig_Type
, Desig_Act
) then
13176 Error_Msg_N
("\predicates do not match", Actual
);
13179 Abandon_Instantiation
(Actual
);
13182 -- Ada 2005: null-exclusion indicators of the two types must agree
13184 if Can_Never_Be_Null
(A_Gen_T
) /= Can_Never_Be_Null
(Act_T
) then
13186 ("non null exclusion of actual and formal & do not match",
13189 end Validate_Access_Type_Instance
;
13191 ----------------------------------
13192 -- Validate_Array_Type_Instance --
13193 ----------------------------------
13195 procedure Validate_Array_Type_Instance
is
13200 function Formal_Dimensions
return Nat
;
13201 -- Count number of dimensions in array type formal
13203 -----------------------
13204 -- Formal_Dimensions --
13205 -----------------------
13207 function Formal_Dimensions
return Nat
is
13212 if Nkind
(Def
) = N_Constrained_Array_Definition
then
13213 Index
:= First
(Discrete_Subtype_Definitions
(Def
));
13215 Index
:= First
(Subtype_Marks
(Def
));
13218 while Present
(Index
) loop
13224 end Formal_Dimensions
;
13226 -- Start of processing for Validate_Array_Type_Instance
13229 if not Is_Array_Type
(Act_T
) then
13231 ("expect array type in instantiation of &", Actual
, Gen_T
);
13232 Abandon_Instantiation
(Actual
);
13234 elsif Nkind
(Def
) = N_Constrained_Array_Definition
then
13235 if not (Is_Constrained
(Act_T
)) then
13237 ("expect constrained array in instantiation of &",
13239 Abandon_Instantiation
(Actual
);
13243 if Is_Constrained
(Act_T
) then
13245 ("expect unconstrained array in instantiation of &",
13247 Abandon_Instantiation
(Actual
);
13251 if Formal_Dimensions
/= Number_Dimensions
(Act_T
) then
13253 ("dimensions of actual do not match formal &", Actual
, Gen_T
);
13254 Abandon_Instantiation
(Actual
);
13257 I1
:= First_Index
(A_Gen_T
);
13258 I2
:= First_Index
(Act_T
);
13259 for J
in 1 .. Formal_Dimensions
loop
13261 -- If the indexes of the actual were given by a subtype_mark,
13262 -- the index was transformed into a range attribute. Retrieve
13263 -- the original type mark for checking.
13265 if Is_Entity_Name
(Original_Node
(I2
)) then
13266 T2
:= Entity
(Original_Node
(I2
));
13271 if not Subtypes_Match
13272 (Find_Actual_Type
(Etype
(I1
), A_Gen_T
), T2
)
13275 ("index types of actual do not match those of formal &",
13277 Abandon_Instantiation
(Actual
);
13284 -- Check matching subtypes. Note that there are complex visibility
13285 -- issues when the generic is a child unit and some aspect of the
13286 -- generic type is declared in a parent unit of the generic. We do
13287 -- the test to handle this special case only after a direct check
13288 -- for static matching has failed. The case where both the component
13289 -- type and the array type are separate formals, and the component
13290 -- type is a private view may also require special checking in
13291 -- Subtypes_Match. Finally, we assume that a child instance where
13292 -- the component type comes from a formal of a parent instance is
13293 -- correct because the generic was correct. A more precise check
13294 -- seems too complex to install???
13297 (Component_Type
(A_Gen_T
), Component_Type
(Act_T
))
13300 (Find_Actual_Type
(Component_Type
(A_Gen_T
), A_Gen_T
),
13301 Component_Type
(Act_T
))
13303 (not Inside_A_Generic
13304 and then Is_Child_Unit
(Scope
(Component_Type
(A_Gen_T
))))
13309 ("component subtype of actual does not match that of formal &",
13311 Abandon_Instantiation
(Actual
);
13314 if Has_Aliased_Components
(A_Gen_T
)
13315 and then not Has_Aliased_Components
(Act_T
)
13318 ("actual must have aliased components to match formal type &",
13321 end Validate_Array_Type_Instance
;
13323 -----------------------------------------------
13324 -- Validate_Derived_Interface_Type_Instance --
13325 -----------------------------------------------
13327 procedure Validate_Derived_Interface_Type_Instance
is
13328 Par
: constant Entity_Id
:= Entity
(Subtype_Indication
(Def
));
13332 -- First apply interface instance checks
13334 Validate_Interface_Type_Instance
;
13336 -- Verify that immediate parent interface is an ancestor of
13340 and then not Interface_Present_In_Ancestor
(Act_T
, Par
)
13343 ("interface actual must include progenitor&", Actual
, Par
);
13346 -- Now verify that the actual includes all other ancestors of
13349 Elmt
:= First_Elmt
(Interfaces
(A_Gen_T
));
13350 while Present
(Elmt
) loop
13351 if not Interface_Present_In_Ancestor
13352 (Act_T
, Get_Instance_Of
(Node
(Elmt
)))
13355 ("interface actual must include progenitor&",
13356 Actual
, Node
(Elmt
));
13361 end Validate_Derived_Interface_Type_Instance
;
13363 ------------------------------------
13364 -- Validate_Derived_Type_Instance --
13365 ------------------------------------
13367 procedure Validate_Derived_Type_Instance
is
13368 Actual_Discr
: Entity_Id
;
13369 Ancestor_Discr
: Entity_Id
;
13372 -- Verify that the actual includes the progenitors of the formal,
13373 -- if any. The formal may depend on previous formals and their
13374 -- instance, so we must examine instance of interfaces if present.
13375 -- The actual may be an extension of an interface, in which case
13376 -- it does not appear in the interface list, so this must be
13377 -- checked separately.
13379 if Present
(Interface_List
(Def
)) then
13380 if not Has_Interfaces
(Act_T
) then
13382 ("actual must implement all interfaces of formal&",
13387 Act_Iface_List
: Elist_Id
;
13389 Iface_Ent
: Entity_Id
;
13391 function Instance_Exists
(I
: Entity_Id
) return Boolean;
13392 -- If the interface entity is declared in a generic unit,
13393 -- this can only be legal if we are within an instantiation
13394 -- of a child of that generic. There is currently no
13395 -- mechanism to relate an interface declared within a
13396 -- generic to the corresponding interface in an instance,
13397 -- so we traverse the list of interfaces of the actual,
13398 -- looking for a name match.
13400 ---------------------
13401 -- Instance_Exists --
13402 ---------------------
13404 function Instance_Exists
(I
: Entity_Id
) return Boolean is
13405 Iface_Elmt
: Elmt_Id
;
13408 Iface_Elmt
:= First_Elmt
(Act_Iface_List
);
13409 while Present
(Iface_Elmt
) loop
13410 if Is_Generic_Instance
(Scope
(Node
(Iface_Elmt
)))
13411 and then Chars
(Node
(Iface_Elmt
)) = Chars
(I
)
13416 Next_Elmt
(Iface_Elmt
);
13420 end Instance_Exists
;
13423 Iface
:= First
(Abstract_Interface_List
(A_Gen_T
));
13424 Collect_Interfaces
(Act_T
, Act_Iface_List
);
13426 while Present
(Iface
) loop
13427 Iface_Ent
:= Get_Instance_Of
(Entity
(Iface
));
13429 if Is_Ancestor
(Iface_Ent
, Act_T
)
13430 or else Is_Progenitor
(Iface_Ent
, Act_T
)
13434 elsif Ekind
(Scope
(Iface_Ent
)) = E_Generic_Package
13435 and then Instance_Exists
(Iface_Ent
)
13440 Error_Msg_Name_1
:= Chars
(Act_T
);
13442 ("actual% must implement interface&",
13443 Actual
, Etype
(Iface
));
13452 -- If the parent type in the generic declaration is itself a previous
13453 -- formal type, then it is local to the generic and absent from the
13454 -- analyzed generic definition. In that case the ancestor is the
13455 -- instance of the formal (which must have been instantiated
13456 -- previously), unless the ancestor is itself a formal derived type.
13457 -- In this latter case (which is the subject of Corrigendum 8652/0038
13458 -- (AI-202) the ancestor of the formals is the ancestor of its
13459 -- parent. Otherwise, the analyzed generic carries the parent type.
13460 -- If the parent type is defined in a previous formal package, then
13461 -- the scope of that formal package is that of the generic type
13462 -- itself, and it has already been mapped into the corresponding type
13463 -- in the actual package.
13465 -- Common case: parent type defined outside of the generic
13467 if Is_Entity_Name
(Subtype_Mark
(Def
))
13468 and then Present
(Entity
(Subtype_Mark
(Def
)))
13470 Ancestor
:= Get_Instance_Of
(Entity
(Subtype_Mark
(Def
)));
13472 -- Check whether parent is defined in a previous formal package
13475 Scope
(Scope
(Base_Type
(Etype
(A_Gen_T
)))) = Scope
(A_Gen_T
)
13478 Get_Instance_Of
(Base_Type
(Etype
(A_Gen_T
)));
13480 -- The type may be a local derivation, or a type extension of a
13481 -- previous formal, or of a formal of a parent package.
13483 elsif Is_Derived_Type
(Get_Instance_Of
(A_Gen_T
))
13485 Ekind
(Get_Instance_Of
(A_Gen_T
)) = E_Record_Type_With_Private
13487 -- Check whether the parent is another derived formal type in the
13488 -- same generic unit.
13490 if Etype
(A_Gen_T
) /= A_Gen_T
13491 and then Is_Generic_Type
(Etype
(A_Gen_T
))
13492 and then Scope
(Etype
(A_Gen_T
)) = Scope
(A_Gen_T
)
13493 and then Etype
(Etype
(A_Gen_T
)) /= Etype
(A_Gen_T
)
13495 -- Locate ancestor of parent from the subtype declaration
13496 -- created for the actual.
13502 Decl
:= First
(Actual_Decls
);
13503 while Present
(Decl
) loop
13504 if Nkind
(Decl
) = N_Subtype_Declaration
13505 and then Chars
(Defining_Identifier
(Decl
)) =
13506 Chars
(Etype
(A_Gen_T
))
13508 Ancestor
:= Generic_Parent_Type
(Decl
);
13516 pragma Assert
(Present
(Ancestor
));
13518 -- The ancestor itself may be a previous formal that has been
13521 Ancestor
:= Get_Instance_Of
(Ancestor
);
13525 Get_Instance_Of
(Base_Type
(Get_Instance_Of
(A_Gen_T
)));
13528 -- Check whether parent is a previous formal of the current generic
13530 elsif Is_Derived_Type
(A_Gen_T
)
13531 and then Is_Generic_Type
(Etype
(A_Gen_T
))
13532 and then Scope
(A_Gen_T
) = Scope
(Etype
(A_Gen_T
))
13534 Ancestor
:= Get_Instance_Of
(First_Subtype
(Etype
(A_Gen_T
)));
13536 -- An unusual case: the actual is a type declared in a parent unit,
13537 -- but is not a formal type so there is no instance_of for it.
13538 -- Retrieve it by analyzing the record extension.
13540 elsif Is_Child_Unit
(Scope
(A_Gen_T
))
13541 and then In_Open_Scopes
(Scope
(Act_T
))
13542 and then Is_Generic_Instance
(Scope
(Act_T
))
13544 Analyze
(Subtype_Mark
(Def
));
13545 Ancestor
:= Entity
(Subtype_Mark
(Def
));
13548 Ancestor
:= Get_Instance_Of
(Etype
(Base_Type
(A_Gen_T
)));
13551 -- If the formal derived type has pragma Preelaborable_Initialization
13552 -- then the actual type must have preelaborable initialization.
13554 if Known_To_Have_Preelab_Init
(A_Gen_T
)
13555 and then not Has_Preelaborable_Initialization
(Act_T
)
13558 ("actual for & must have preelaborable initialization",
13562 -- Ada 2005 (AI-251)
13564 if Ada_Version
>= Ada_2005
and then Is_Interface
(Ancestor
) then
13565 if not Interface_Present_In_Ancestor
(Act_T
, Ancestor
) then
13567 ("(Ada 2005) expected type implementing & in instantiation",
13571 -- Finally verify that the (instance of) the ancestor is an ancestor
13574 elsif not Is_Ancestor
(Base_Type
(Ancestor
), Act_T
) then
13576 ("expect type derived from & in instantiation",
13577 Actual
, First_Subtype
(Ancestor
));
13578 Abandon_Instantiation
(Actual
);
13581 -- Ada 2005 (AI-443): Synchronized formal derived type checks. Note
13582 -- that the formal type declaration has been rewritten as a private
13585 if Ada_Version
>= Ada_2005
13586 and then Nkind
(Parent
(A_Gen_T
)) = N_Private_Extension_Declaration
13587 and then Synchronized_Present
(Parent
(A_Gen_T
))
13589 -- The actual must be a synchronized tagged type
13591 if not Is_Tagged_Type
(Act_T
) then
13593 ("actual of synchronized type must be tagged", Actual
);
13594 Abandon_Instantiation
(Actual
);
13596 elsif Nkind
(Parent
(Act_T
)) = N_Full_Type_Declaration
13597 and then Nkind
(Type_Definition
(Parent
(Act_T
))) =
13598 N_Derived_Type_Definition
13599 and then not Synchronized_Present
13600 (Type_Definition
(Parent
(Act_T
)))
13603 ("actual of synchronized type must be synchronized", Actual
);
13604 Abandon_Instantiation
(Actual
);
13608 -- Perform atomic/volatile checks (RM C.6(12)). Note that AI05-0218-1
13609 -- removes the second instance of the phrase "or allow pass by copy".
13611 -- For Ada 2022, the aspect may be specified explicitly for the
13612 -- formal regardless of whether an ancestor obeys it.
13614 if Is_Atomic
(Act_T
)
13615 and then not Is_Atomic
(Ancestor
)
13616 and then not Is_Atomic
(A_Gen_T
)
13619 ("cannot have atomic actual type for non-atomic formal type",
13622 elsif Is_Volatile
(Act_T
)
13623 and then not Is_Volatile
(Ancestor
)
13624 and then not Is_Volatile
(A_Gen_T
)
13627 ("cannot have volatile actual type for non-volatile formal type",
13631 -- It should not be necessary to check for unknown discriminants on
13632 -- Formal, but for some reason Has_Unknown_Discriminants is false for
13633 -- A_Gen_T, so Is_Definite_Subtype incorrectly returns True. This
13634 -- needs fixing. ???
13636 if Is_Definite_Subtype
(A_Gen_T
)
13637 and then not Unknown_Discriminants_Present
(Formal
)
13638 and then not Is_Definite_Subtype
(Act_T
)
13640 Error_Msg_N
("actual subtype must be constrained", Actual
);
13641 Abandon_Instantiation
(Actual
);
13644 if not Unknown_Discriminants_Present
(Formal
) then
13645 if Is_Constrained
(Ancestor
) then
13646 if not Is_Constrained
(Act_T
) then
13647 Error_Msg_N
("actual subtype must be constrained", Actual
);
13648 Abandon_Instantiation
(Actual
);
13651 -- Ancestor is unconstrained, Check if generic formal and actual
13652 -- agree on constrainedness. The check only applies to array types
13653 -- and discriminated types.
13655 elsif Is_Constrained
(Act_T
) then
13656 if Ekind
(Ancestor
) = E_Access_Type
13657 or else (not Is_Constrained
(A_Gen_T
)
13658 and then Is_Composite_Type
(A_Gen_T
))
13660 Error_Msg_N
("actual subtype must be unconstrained", Actual
);
13661 Abandon_Instantiation
(Actual
);
13664 -- A class-wide type is only allowed if the formal has unknown
13667 elsif Is_Class_Wide_Type
(Act_T
)
13668 and then not Has_Unknown_Discriminants
(Ancestor
)
13671 ("actual for & cannot be a class-wide type", Actual
, Gen_T
);
13672 Abandon_Instantiation
(Actual
);
13674 -- Otherwise, the formal and actual must have the same number
13675 -- of discriminants and each discriminant of the actual must
13676 -- correspond to a discriminant of the formal.
13678 elsif Has_Discriminants
(Act_T
)
13679 and then not Has_Unknown_Discriminants
(Act_T
)
13680 and then Has_Discriminants
(Ancestor
)
13682 Actual_Discr
:= First_Discriminant
(Act_T
);
13683 Ancestor_Discr
:= First_Discriminant
(Ancestor
);
13684 while Present
(Actual_Discr
)
13685 and then Present
(Ancestor_Discr
)
13687 if Base_Type
(Act_T
) /= Base_Type
(Ancestor
) and then
13688 No
(Corresponding_Discriminant
(Actual_Discr
))
13691 ("discriminant & does not correspond "
13692 & "to ancestor discriminant", Actual
, Actual_Discr
);
13693 Abandon_Instantiation
(Actual
);
13696 Next_Discriminant
(Actual_Discr
);
13697 Next_Discriminant
(Ancestor_Discr
);
13700 if Present
(Actual_Discr
) or else Present
(Ancestor_Discr
) then
13702 ("actual for & must have same number of discriminants",
13704 Abandon_Instantiation
(Actual
);
13707 -- This case should be caught by the earlier check for
13708 -- constrainedness, but the check here is added for completeness.
13710 elsif Has_Discriminants
(Act_T
)
13711 and then not Has_Unknown_Discriminants
(Act_T
)
13714 ("actual for & must not have discriminants", Actual
, Gen_T
);
13715 Abandon_Instantiation
(Actual
);
13717 elsif Has_Discriminants
(Ancestor
) then
13719 ("actual for & must have known discriminants", Actual
, Gen_T
);
13720 Abandon_Instantiation
(Actual
);
13723 if not Subtypes_Statically_Compatible
13724 (Act_T
, Ancestor
, Formal_Derived_Matching
=> True)
13727 ("actual for & must be statically compatible with ancestor",
13730 if not Predicates_Compatible
(Act_T
, Ancestor
) then
13732 ("\predicate on actual is not compatible with ancestor",
13736 Abandon_Instantiation
(Actual
);
13740 -- If the formal and actual types are abstract, check that there
13741 -- are no abstract primitives of the actual type that correspond to
13742 -- nonabstract primitives of the formal type (second sentence of
13745 if Is_Abstract_Type
(A_Gen_T
) and then Is_Abstract_Type
(Act_T
) then
13746 Check_Abstract_Primitives
: declare
13747 Gen_Prims
: constant Elist_Id
:=
13748 Primitive_Operations
(A_Gen_T
);
13749 Gen_Elmt
: Elmt_Id
;
13750 Gen_Subp
: Entity_Id
;
13751 Anc_Subp
: Entity_Id
;
13752 Anc_Formal
: Entity_Id
;
13753 Anc_F_Type
: Entity_Id
;
13755 Act_Prims
: constant Elist_Id
:= Primitive_Operations
(Act_T
);
13756 Act_Elmt
: Elmt_Id
;
13757 Act_Subp
: Entity_Id
;
13758 Act_Formal
: Entity_Id
;
13759 Act_F_Type
: Entity_Id
;
13761 Subprograms_Correspond
: Boolean;
13763 function Is_Tagged_Ancestor
(T1
, T2
: Entity_Id
) return Boolean;
13764 -- Returns true if T2 is derived directly or indirectly from
13765 -- T1, including derivations from interfaces. T1 and T2 are
13766 -- required to be specific tagged base types.
13768 ------------------------
13769 -- Is_Tagged_Ancestor --
13770 ------------------------
13772 function Is_Tagged_Ancestor
(T1
, T2
: Entity_Id
) return Boolean
13774 Intfc_Elmt
: Elmt_Id
;
13777 -- The predicate is satisfied if the types are the same
13782 -- If we've reached the top of the derivation chain then
13783 -- we know that T1 is not an ancestor of T2.
13785 elsif Etype
(T2
) = T2
then
13788 -- Proceed to check T2's immediate parent
13790 elsif Is_Ancestor
(T1
, Base_Type
(Etype
(T2
))) then
13793 -- Finally, check to see if T1 is an ancestor of any of T2's
13797 Intfc_Elmt
:= First_Elmt
(Interfaces
(T2
));
13798 while Present
(Intfc_Elmt
) loop
13799 if Is_Ancestor
(T1
, Node
(Intfc_Elmt
)) then
13803 Next_Elmt
(Intfc_Elmt
);
13808 end Is_Tagged_Ancestor
;
13810 -- Start of processing for Check_Abstract_Primitives
13813 -- Loop over all of the formal derived type's primitives
13815 Gen_Elmt
:= First_Elmt
(Gen_Prims
);
13816 while Present
(Gen_Elmt
) loop
13817 Gen_Subp
:= Node
(Gen_Elmt
);
13819 -- If the primitive of the formal is not abstract, then
13820 -- determine whether there is a corresponding primitive of
13821 -- the actual type that's abstract.
13823 if not Is_Abstract_Subprogram
(Gen_Subp
) then
13824 Act_Elmt
:= First_Elmt
(Act_Prims
);
13825 while Present
(Act_Elmt
) loop
13826 Act_Subp
:= Node
(Act_Elmt
);
13828 -- If we find an abstract primitive of the actual,
13829 -- then we need to test whether it corresponds to the
13830 -- subprogram from which the generic formal primitive
13833 if Is_Abstract_Subprogram
(Act_Subp
) then
13834 Anc_Subp
:= Alias
(Gen_Subp
);
13836 -- Test whether we have a corresponding primitive
13837 -- by comparing names, kinds, formal types, and
13840 if Chars
(Anc_Subp
) = Chars
(Act_Subp
)
13841 and then Ekind
(Anc_Subp
) = Ekind
(Act_Subp
)
13843 Anc_Formal
:= First_Formal
(Anc_Subp
);
13844 Act_Formal
:= First_Formal
(Act_Subp
);
13845 while Present
(Anc_Formal
)
13846 and then Present
(Act_Formal
)
13848 Anc_F_Type
:= Etype
(Anc_Formal
);
13849 Act_F_Type
:= Etype
(Act_Formal
);
13851 if Ekind
(Anc_F_Type
) =
13852 E_Anonymous_Access_Type
13854 Anc_F_Type
:= Designated_Type
(Anc_F_Type
);
13856 if Ekind
(Act_F_Type
) =
13857 E_Anonymous_Access_Type
13860 Designated_Type
(Act_F_Type
);
13866 Ekind
(Act_F_Type
) = E_Anonymous_Access_Type
13871 Anc_F_Type
:= Base_Type
(Anc_F_Type
);
13872 Act_F_Type
:= Base_Type
(Act_F_Type
);
13874 -- If the formal is controlling, then the
13875 -- the type of the actual primitive's formal
13876 -- must be derived directly or indirectly
13877 -- from the type of the ancestor primitive's
13880 if Is_Controlling_Formal
(Anc_Formal
) then
13881 if not Is_Tagged_Ancestor
13882 (Anc_F_Type
, Act_F_Type
)
13887 -- Otherwise the types of the formals must
13890 elsif Anc_F_Type
/= Act_F_Type
then
13894 Next_Formal
(Anc_Formal
);
13895 Next_Formal
(Act_Formal
);
13898 -- If we traversed through all of the formals
13899 -- then so far the subprograms correspond, so
13900 -- now check that any result types correspond.
13902 if No
(Anc_Formal
) and then No
(Act_Formal
) then
13903 Subprograms_Correspond
:= True;
13905 if Ekind
(Act_Subp
) = E_Function
then
13906 Anc_F_Type
:= Etype
(Anc_Subp
);
13907 Act_F_Type
:= Etype
(Act_Subp
);
13909 if Ekind
(Anc_F_Type
) =
13910 E_Anonymous_Access_Type
13913 Designated_Type
(Anc_F_Type
);
13915 if Ekind
(Act_F_Type
) =
13916 E_Anonymous_Access_Type
13919 Designated_Type
(Act_F_Type
);
13921 Subprograms_Correspond
:= False;
13926 = E_Anonymous_Access_Type
13928 Subprograms_Correspond
:= False;
13931 Anc_F_Type
:= Base_Type
(Anc_F_Type
);
13932 Act_F_Type
:= Base_Type
(Act_F_Type
);
13934 -- Now either the result types must be
13935 -- the same or, if the result type is
13936 -- controlling, the result type of the
13937 -- actual primitive must descend from the
13938 -- result type of the ancestor primitive.
13940 if Subprograms_Correspond
13941 and then Anc_F_Type
/= Act_F_Type
13943 Has_Controlling_Result
(Anc_Subp
)
13944 and then not Is_Tagged_Ancestor
13945 (Anc_F_Type
, Act_F_Type
)
13947 Subprograms_Correspond
:= False;
13951 -- Found a matching subprogram belonging to
13952 -- formal ancestor type, so actual subprogram
13953 -- corresponds and this violates 3.9.3(9).
13955 if Subprograms_Correspond
then
13957 ("abstract subprogram & overrides "
13958 & "nonabstract subprogram of ancestor",
13965 Next_Elmt
(Act_Elmt
);
13969 Next_Elmt
(Gen_Elmt
);
13971 end Check_Abstract_Primitives
;
13974 -- Verify that limitedness matches. If parent is a limited
13975 -- interface then the generic formal is not unless declared
13976 -- explicitly so. If not declared limited, the actual cannot be
13977 -- limited (see AI05-0087).
13979 if Is_Limited_Type
(Act_T
) and then not Is_Limited_Type
(A_Gen_T
) then
13980 if not In_Instance
then
13982 ("actual for non-limited & cannot be a limited type",
13984 Explain_Limited_Type
(Act_T
, Actual
);
13985 Abandon_Instantiation
(Actual
);
13989 -- Check for AI12-0036
13992 Formal_Is_Private_Extension
: constant Boolean :=
13993 Nkind
(Parent
(A_Gen_T
)) = N_Private_Extension_Declaration
;
13995 Actual_Is_Tagged
: constant Boolean := Is_Tagged_Type
(Act_T
);
13998 if Actual_Is_Tagged
/= Formal_Is_Private_Extension
then
13999 if not In_Instance
then
14000 if Actual_Is_Tagged
then
14002 ("actual for & cannot be a tagged type", Actual
, Gen_T
);
14005 ("actual for & must be a tagged type", Actual
, Gen_T
);
14008 Abandon_Instantiation
(Actual
);
14012 end Validate_Derived_Type_Instance
;
14014 ----------------------------------------
14015 -- Validate_Discriminated_Formal_Type --
14016 ----------------------------------------
14018 procedure Validate_Discriminated_Formal_Type
is
14019 Formal_Discr
: Entity_Id
;
14020 Actual_Discr
: Entity_Id
;
14021 Formal_Subt
: Entity_Id
;
14024 if Has_Discriminants
(A_Gen_T
) then
14025 if not Has_Discriminants
(Act_T
) then
14027 ("actual for & must have discriminants", Actual
, Gen_T
);
14028 Abandon_Instantiation
(Actual
);
14030 elsif Is_Constrained
(Act_T
) then
14032 ("actual for & must be unconstrained", Actual
, Gen_T
);
14033 Abandon_Instantiation
(Actual
);
14036 Formal_Discr
:= First_Discriminant
(A_Gen_T
);
14037 Actual_Discr
:= First_Discriminant
(Act_T
);
14038 while Formal_Discr
/= Empty
loop
14039 if Actual_Discr
= Empty
then
14041 ("discriminants on actual do not match formal",
14043 Abandon_Instantiation
(Actual
);
14046 Formal_Subt
:= Get_Instance_Of
(Etype
(Formal_Discr
));
14048 -- Access discriminants match if designated types do
14050 if Ekind
(Base_Type
(Formal_Subt
)) = E_Anonymous_Access_Type
14051 and then (Ekind
(Base_Type
(Etype
(Actual_Discr
)))) =
14052 E_Anonymous_Access_Type
14055 (Designated_Type
(Base_Type
(Formal_Subt
))) =
14056 Designated_Type
(Base_Type
(Etype
(Actual_Discr
)))
14060 elsif Base_Type
(Formal_Subt
) /=
14061 Base_Type
(Etype
(Actual_Discr
))
14064 ("types of actual discriminants must match formal",
14066 Abandon_Instantiation
(Actual
);
14068 elsif not Subtypes_Statically_Match
14069 (Formal_Subt
, Etype
(Actual_Discr
))
14070 and then Ada_Version
>= Ada_95
14073 ("subtypes of actual discriminants must match formal",
14075 Abandon_Instantiation
(Actual
);
14078 Next_Discriminant
(Formal_Discr
);
14079 Next_Discriminant
(Actual_Discr
);
14082 if Actual_Discr
/= Empty
then
14084 ("discriminants on actual do not match formal",
14086 Abandon_Instantiation
(Actual
);
14090 end Validate_Discriminated_Formal_Type
;
14092 ---------------------------------------
14093 -- Validate_Incomplete_Type_Instance --
14094 ---------------------------------------
14096 procedure Validate_Incomplete_Type_Instance
is
14098 if not Is_Tagged_Type
(Act_T
)
14099 and then Is_Tagged_Type
(A_Gen_T
)
14102 ("actual for & must be a tagged type", Actual
, Gen_T
);
14105 Validate_Discriminated_Formal_Type
;
14106 end Validate_Incomplete_Type_Instance
;
14108 --------------------------------------
14109 -- Validate_Interface_Type_Instance --
14110 --------------------------------------
14112 procedure Validate_Interface_Type_Instance
is
14114 if not Is_Interface
(Act_T
) then
14116 ("actual for formal interface type must be an interface",
14119 elsif Is_Limited_Type
(Act_T
) /= Is_Limited_Type
(A_Gen_T
)
14120 or else Is_Task_Interface
(A_Gen_T
) /= Is_Task_Interface
(Act_T
)
14121 or else Is_Protected_Interface
(A_Gen_T
) /=
14122 Is_Protected_Interface
(Act_T
)
14123 or else Is_Synchronized_Interface
(A_Gen_T
) /=
14124 Is_Synchronized_Interface
(Act_T
)
14127 ("actual for interface& does not match (RM 12.5.5(4))",
14130 end Validate_Interface_Type_Instance
;
14132 ------------------------------------
14133 -- Validate_Private_Type_Instance --
14134 ------------------------------------
14136 procedure Validate_Private_Type_Instance
is
14138 if Is_Limited_Type
(Act_T
)
14139 and then not Is_Limited_Type
(A_Gen_T
)
14141 if In_Instance
then
14145 ("actual for non-limited & cannot be a limited type", Actual
,
14147 Explain_Limited_Type
(Act_T
, Actual
);
14148 Abandon_Instantiation
(Actual
);
14151 elsif Known_To_Have_Preelab_Init
(A_Gen_T
)
14152 and then not Has_Preelaborable_Initialization
(Act_T
)
14155 ("actual for & must have preelaborable initialization", Actual
,
14158 elsif not Is_Definite_Subtype
(Act_T
)
14159 and then Is_Definite_Subtype
(A_Gen_T
)
14160 and then Ada_Version
>= Ada_95
14163 ("actual for & must be a definite subtype", Actual
, Gen_T
);
14165 elsif not Is_Tagged_Type
(Act_T
)
14166 and then Is_Tagged_Type
(A_Gen_T
)
14169 ("actual for & must be a tagged type", Actual
, Gen_T
);
14172 Validate_Discriminated_Formal_Type
;
14174 end Validate_Private_Type_Instance
;
14176 -- Start of processing for Instantiate_Type
14179 if Get_Instance_Of
(A_Gen_T
) /= A_Gen_T
then
14180 Error_Msg_N
("duplicate instantiation of generic type", Actual
);
14181 return New_List
(Error
);
14183 elsif not Is_Entity_Name
(Actual
)
14184 or else not Is_Type
(Entity
(Actual
))
14187 ("expect valid subtype mark to instantiate &", Actual
, Gen_T
);
14188 Abandon_Instantiation
(Actual
);
14191 Act_T
:= Entity
(Actual
);
14193 -- Ada 2005 (AI-216): An Unchecked_Union subtype shall only be passed
14194 -- as a generic actual parameter if the corresponding formal type
14195 -- does not have a known_discriminant_part, or is a formal derived
14196 -- type that is an Unchecked_Union type.
14198 if Is_Unchecked_Union
(Base_Type
(Act_T
)) then
14199 if not Has_Discriminants
(A_Gen_T
)
14200 or else (Is_Derived_Type
(A_Gen_T
)
14201 and then Is_Unchecked_Union
(A_Gen_T
))
14205 Error_Msg_N
("unchecked union cannot be the actual for a "
14206 & "discriminated formal type", Act_T
);
14211 -- Deal with fixed/floating restrictions
14213 if Is_Floating_Point_Type
(Act_T
) then
14214 Check_Restriction
(No_Floating_Point
, Actual
);
14215 elsif Is_Fixed_Point_Type
(Act_T
) then
14216 Check_Restriction
(No_Fixed_Point
, Actual
);
14219 -- Deal with error of using incomplete type as generic actual.
14220 -- This includes limited views of a type, even if the non-limited
14221 -- view may be available.
14223 if Ekind
(Act_T
) = E_Incomplete_Type
14224 or else (Is_Class_Wide_Type
(Act_T
)
14225 and then Ekind
(Root_Type
(Act_T
)) = E_Incomplete_Type
)
14227 -- If the formal is an incomplete type, the actual can be
14228 -- incomplete as well, but if an actual incomplete type has
14229 -- a full view, then we'll retrieve that.
14231 if Ekind
(A_Gen_T
) = E_Incomplete_Type
14232 and then No
(Full_View
(Act_T
))
14236 elsif Is_Class_Wide_Type
(Act_T
)
14237 or else No
(Full_View
(Act_T
))
14239 Error_Msg_N
("premature use of incomplete type", Actual
);
14240 Abandon_Instantiation
(Actual
);
14243 Act_T
:= Full_View
(Act_T
);
14244 Set_Entity
(Actual
, Act_T
);
14246 if Has_Private_Component
(Act_T
) then
14248 ("premature use of type with private component", Actual
);
14252 -- Deal with error of premature use of private type as generic actual
14254 elsif Is_Private_Type
(Act_T
)
14255 and then Is_Private_Type
(Base_Type
(Act_T
))
14256 and then not Is_Generic_Type
(Act_T
)
14257 and then not Is_Derived_Type
(Act_T
)
14258 and then No
(Full_View
(Root_Type
(Act_T
)))
14260 -- If the formal is an incomplete type, the actual can be
14261 -- private or incomplete as well.
14263 if Ekind
(A_Gen_T
) = E_Incomplete_Type
then
14266 Error_Msg_N
("premature use of private type", Actual
);
14269 elsif Has_Private_Component
(Act_T
) then
14271 ("premature use of type with private component", Actual
);
14274 Set_Instance_Of
(A_Gen_T
, Act_T
);
14276 -- If the type is generic, the class-wide type may also be used
14278 if Is_Tagged_Type
(A_Gen_T
)
14279 and then Is_Tagged_Type
(Act_T
)
14280 and then not Is_Class_Wide_Type
(A_Gen_T
)
14282 Set_Instance_Of
(Class_Wide_Type
(A_Gen_T
),
14283 Class_Wide_Type
(Act_T
));
14286 if not Is_Abstract_Type
(A_Gen_T
)
14287 and then Is_Abstract_Type
(Act_T
)
14290 ("actual of non-abstract formal cannot be abstract", Actual
);
14293 -- A generic scalar type is a first subtype for which we generate
14294 -- an anonymous base type. Indicate that the instance of this base
14295 -- is the base type of the actual.
14297 if Is_Scalar_Type
(A_Gen_T
) then
14298 Set_Instance_Of
(Etype
(A_Gen_T
), Etype
(Act_T
));
14302 Check_Shared_Variable_Control_Aspects
;
14304 if Error_Posted
(Act_T
) then
14307 case Nkind
(Def
) is
14308 when N_Formal_Private_Type_Definition
=>
14309 Validate_Private_Type_Instance
;
14311 when N_Formal_Incomplete_Type_Definition
=>
14312 Validate_Incomplete_Type_Instance
;
14314 when N_Formal_Derived_Type_Definition
=>
14315 Validate_Derived_Type_Instance
;
14317 when N_Formal_Discrete_Type_Definition
=>
14318 if not Is_Discrete_Type
(Act_T
) then
14320 ("expect discrete type in instantiation of&",
14322 Abandon_Instantiation
(Actual
);
14325 Diagnose_Predicated_Actual
;
14327 when N_Formal_Signed_Integer_Type_Definition
=>
14328 if not Is_Signed_Integer_Type
(Act_T
) then
14330 ("expect signed integer type in instantiation of&",
14332 Abandon_Instantiation
(Actual
);
14335 Diagnose_Predicated_Actual
;
14337 when N_Formal_Modular_Type_Definition
=>
14338 if not Is_Modular_Integer_Type
(Act_T
) then
14340 ("expect modular type in instantiation of &",
14342 Abandon_Instantiation
(Actual
);
14345 Diagnose_Predicated_Actual
;
14347 when N_Formal_Floating_Point_Definition
=>
14348 if not Is_Floating_Point_Type
(Act_T
) then
14350 ("expect float type in instantiation of &", Actual
, Gen_T
);
14351 Abandon_Instantiation
(Actual
);
14354 when N_Formal_Ordinary_Fixed_Point_Definition
=>
14355 if not Is_Ordinary_Fixed_Point_Type
(Act_T
) then
14357 ("expect ordinary fixed point type in instantiation of &",
14359 Abandon_Instantiation
(Actual
);
14362 when N_Formal_Decimal_Fixed_Point_Definition
=>
14363 if not Is_Decimal_Fixed_Point_Type
(Act_T
) then
14365 ("expect decimal type in instantiation of &",
14367 Abandon_Instantiation
(Actual
);
14370 when N_Array_Type_Definition
=>
14371 Validate_Array_Type_Instance
;
14373 when N_Access_To_Object_Definition
=>
14374 Validate_Access_Type_Instance
;
14376 when N_Access_Function_Definition
14377 | N_Access_Procedure_Definition
14379 Validate_Access_Subprogram_Instance
;
14381 when N_Record_Definition
=>
14382 Validate_Interface_Type_Instance
;
14384 when N_Derived_Type_Definition
=>
14385 Validate_Derived_Interface_Type_Instance
;
14388 raise Program_Error
;
14392 Subt
:= New_Copy
(Gen_T
);
14394 -- Use adjusted sloc of subtype name as the location for other nodes in
14395 -- the subtype declaration.
14397 Loc
:= Sloc
(Subt
);
14400 Make_Subtype_Declaration
(Loc
,
14401 Defining_Identifier
=> Subt
,
14402 Subtype_Indication
=> New_Occurrence_Of
(Act_T
, Loc
));
14404 Copy_Ghost_Aspect
(Formal
, To
=> Decl_Node
);
14406 -- Record whether the actual is private at this point, so that
14407 -- Check_Generic_Actuals can restore its proper view before the
14408 -- semantic analysis of the instance.
14410 if Is_Private_Type
(Act_T
) then
14411 Set_Has_Private_View
(Subtype_Indication
(Decl_Node
));
14413 elsif (Is_Access_Type
(Act_T
)
14414 and then Is_Private_Type
(Designated_Type
(Act_T
)))
14415 or else (Is_Array_Type
(Act_T
)
14417 Is_Private_Type
(Component_Type_For_Private_View
(Act_T
)))
14419 Set_Has_Secondary_Private_View
(Subtype_Indication
(Decl_Node
));
14422 -- In Ada 2012 the actual may be a limited view. Indicate that
14423 -- the local subtype must be treated as such.
14425 if From_Limited_With
(Act_T
) then
14426 Mutate_Ekind
(Subt
, E_Incomplete_Subtype
);
14427 Set_From_Limited_With
(Subt
);
14430 Decl_Nodes
:= New_List
(Decl_Node
);
14432 -- Flag actual derived types so their elaboration produces the
14433 -- appropriate renamings for the primitive operations of the ancestor.
14434 -- Flag actual for formal private types as well, to determine whether
14435 -- operations in the private part may override inherited operations.
14436 -- If the formal has an interface list, the ancestor is not the
14437 -- parent, but the analyzed formal that includes the interface
14438 -- operations of all its progenitors.
14440 -- Same treatment for formal private types, so we can check whether the
14441 -- type is tagged limited when validating derivations in the private
14442 -- part. (See AI05-096).
14444 if Nkind
(Def
) = N_Formal_Derived_Type_Definition
then
14445 if Present
(Interface_List
(Def
)) then
14446 Set_Generic_Parent_Type
(Decl_Node
, A_Gen_T
);
14448 Set_Generic_Parent_Type
(Decl_Node
, Ancestor
);
14451 elsif Nkind
(Def
) in N_Formal_Private_Type_Definition
14452 | N_Formal_Incomplete_Type_Definition
14454 Set_Generic_Parent_Type
(Decl_Node
, A_Gen_T
);
14457 -- If the actual is a synchronized type that implements an interface,
14458 -- the primitive operations are attached to the corresponding record,
14459 -- and we have to treat it as an additional generic actual, so that its
14460 -- primitive operations become visible in the instance. The task or
14461 -- protected type itself does not carry primitive operations.
14463 if Is_Concurrent_Type
(Act_T
)
14464 and then Is_Tagged_Type
(Act_T
)
14465 and then Present
(Corresponding_Record_Type
(Act_T
))
14466 and then Present
(Ancestor
)
14467 and then Is_Interface
(Ancestor
)
14470 Corr_Rec
: constant Entity_Id
:=
14471 Corresponding_Record_Type
(Act_T
);
14472 New_Corr
: Entity_Id
;
14473 Corr_Decl
: Node_Id
;
14476 New_Corr
:= Make_Temporary
(Loc
, 'S');
14478 Make_Subtype_Declaration
(Loc
,
14479 Defining_Identifier
=> New_Corr
,
14480 Subtype_Indication
=>
14481 New_Occurrence_Of
(Corr_Rec
, Loc
));
14482 Append_To
(Decl_Nodes
, Corr_Decl
);
14484 if Ekind
(Act_T
) = E_Task_Type
then
14485 Mutate_Ekind
(Subt
, E_Task_Subtype
);
14487 Mutate_Ekind
(Subt
, E_Protected_Subtype
);
14490 Set_Corresponding_Record_Type
(Subt
, Corr_Rec
);
14491 Set_Generic_Parent_Type
(Corr_Decl
, Ancestor
);
14492 Set_Generic_Parent_Type
(Decl_Node
, Empty
);
14496 -- For a floating-point type, capture dimension info if any, because
14497 -- the generated subtype declaration does not come from source and
14498 -- will not process dimensions.
14500 if Is_Floating_Point_Type
(Act_T
) then
14501 Copy_Dimensions
(Act_T
, Subt
);
14505 end Instantiate_Type
;
14507 -----------------------------
14508 -- Is_Abbreviated_Instance --
14509 -----------------------------
14511 function Is_Abbreviated_Instance
(E
: Entity_Id
) return Boolean is
14513 return Ekind
(E
) = E_Package
14514 and then Present
(Hidden_In_Formal_Instance
(E
));
14515 end Is_Abbreviated_Instance
;
14517 ---------------------
14518 -- Is_In_Main_Unit --
14519 ---------------------
14521 function Is_In_Main_Unit
(N
: Node_Id
) return Boolean is
14522 Unum
: constant Unit_Number_Type
:= Get_Source_Unit
(N
);
14523 Current_Unit
: Node_Id
;
14526 if Unum
= Main_Unit
then
14529 -- If the current unit is a subunit then it is either the main unit or
14530 -- is being compiled as part of the main unit.
14532 elsif Nkind
(N
) = N_Compilation_Unit
then
14533 return Nkind
(Unit
(N
)) = N_Subunit
;
14536 Current_Unit
:= Parent
(N
);
14537 while Present
(Current_Unit
)
14538 and then Nkind
(Current_Unit
) /= N_Compilation_Unit
14540 Current_Unit
:= Parent
(Current_Unit
);
14543 -- The instantiation node is in the main unit, or else the current node
14544 -- (perhaps as the result of nested instantiations) is in the main unit,
14545 -- or in the declaration of the main unit, which in this last case must
14549 Current_Unit
= Cunit
(Main_Unit
)
14550 or else Current_Unit
= Library_Unit
(Cunit
(Main_Unit
))
14551 or else (Present
(Current_Unit
)
14552 and then Present
(Library_Unit
(Current_Unit
))
14553 and then Is_In_Main_Unit
(Library_Unit
(Current_Unit
)));
14554 end Is_In_Main_Unit
;
14556 ----------------------------
14557 -- Load_Parent_Of_Generic --
14558 ----------------------------
14560 procedure Load_Parent_Of_Generic
14563 Body_Optional
: Boolean := False)
14565 Comp_Unit
: constant Node_Id
:= Cunit
(Get_Source_Unit
(Spec
));
14566 Saved_Style_Check
: constant Boolean := Style_Check
;
14567 Saved_Warn
: constant Warnings_State
:= Save_Warnings
;
14568 True_Parent
: Node_Id
;
14569 Inst_Node
: Node_Id
;
14571 Previous_Instances
: constant Elist_Id
:= New_Elmt_List
;
14573 procedure Collect_Previous_Instances
(Decls
: List_Id
);
14574 -- Collect all instantiations in the given list of declarations, that
14575 -- precede the generic that we need to load. If the bodies of these
14576 -- instantiations are available, we must analyze them, to ensure that
14577 -- the public symbols generated are the same when the unit is compiled
14578 -- to generate code, and when it is compiled in the context of a unit
14579 -- that needs a particular nested instance. This process is applied to
14580 -- both package and subprogram instances.
14582 --------------------------------
14583 -- Collect_Previous_Instances --
14584 --------------------------------
14586 procedure Collect_Previous_Instances
(Decls
: List_Id
) is
14590 Decl
:= First
(Decls
);
14591 while Present
(Decl
) loop
14592 if Sloc
(Decl
) >= Sloc
(Inst_Node
) then
14595 -- If Decl is an instantiation, then record it as requiring
14596 -- instantiation of the corresponding body, except if it is an
14597 -- abbreviated instantiation generated internally for conformance
14598 -- checking purposes only for the case of a formal package
14599 -- declared without a box (see Instantiate_Formal_Package). Such
14600 -- an instantiation does not generate any code (the actual code
14601 -- comes from actual) and thus does not need to be analyzed here.
14602 -- If the instantiation appears with a generic package body it is
14603 -- not analyzed here either.
14605 elsif Nkind
(Decl
) = N_Package_Instantiation
14606 and then not Is_Abbreviated_Instance
(Defining_Entity
(Decl
))
14608 Append_Elmt
(Decl
, Previous_Instances
);
14610 -- For a subprogram instantiation, omit instantiations intrinsic
14611 -- operations (Unchecked_Conversions, etc.) that have no bodies.
14613 elsif Nkind
(Decl
) in N_Function_Instantiation
14614 | N_Procedure_Instantiation
14615 and then not Is_Intrinsic_Subprogram
(Entity
(Name
(Decl
)))
14617 Append_Elmt
(Decl
, Previous_Instances
);
14619 elsif Nkind
(Decl
) = N_Package_Declaration
then
14620 Collect_Previous_Instances
14621 (Visible_Declarations
(Specification
(Decl
)));
14622 Collect_Previous_Instances
14623 (Private_Declarations
(Specification
(Decl
)));
14625 -- Previous non-generic bodies may contain instances as well
14627 elsif Nkind
(Decl
) = N_Package_Body
14628 and then Ekind
(Corresponding_Spec
(Decl
)) /= E_Generic_Package
14630 Collect_Previous_Instances
(Declarations
(Decl
));
14632 elsif Nkind
(Decl
) = N_Subprogram_Body
14633 and then not Acts_As_Spec
(Decl
)
14634 and then not Is_Generic_Subprogram
(Corresponding_Spec
(Decl
))
14636 Collect_Previous_Instances
(Declarations
(Decl
));
14641 end Collect_Previous_Instances
;
14643 -- Start of processing for Load_Parent_Of_Generic
14646 if not In_Same_Source_Unit
(N
, Spec
)
14647 or else Nkind
(Unit
(Comp_Unit
)) = N_Package_Declaration
14648 or else (Nkind
(Unit
(Comp_Unit
)) = N_Package_Body
14649 and then not Is_In_Main_Unit
(Spec
))
14651 -- Find body of parent of spec, and analyze it. A special case arises
14652 -- when the parent is an instantiation, that is to say when we are
14653 -- currently instantiating a nested generic. In that case, there is
14654 -- no separate file for the body of the enclosing instance. Instead,
14655 -- the enclosing body must be instantiated as if it were a pending
14656 -- instantiation, in order to produce the body for the nested generic
14657 -- we require now. Note that in that case the generic may be defined
14658 -- in a package body, the instance defined in the same package body,
14659 -- and the original enclosing body may not be in the main unit.
14661 Inst_Node
:= Empty
;
14663 True_Parent
:= Parent
(Spec
);
14664 while Present
(True_Parent
)
14665 and then Nkind
(True_Parent
) /= N_Compilation_Unit
14667 if Nkind
(True_Parent
) = N_Package_Declaration
14669 Nkind
(Original_Node
(True_Parent
)) = N_Package_Instantiation
14671 -- Parent is a compilation unit that is an instantiation, and
14672 -- instantiation node has been replaced with package decl.
14674 Inst_Node
:= Original_Node
(True_Parent
);
14677 elsif Nkind
(True_Parent
) = N_Package_Declaration
14678 and then Nkind
(Parent
(True_Parent
)) = N_Compilation_Unit
14680 Nkind
(Unit
(Parent
(True_Parent
))) = N_Package_Instantiation
14682 -- Parent is a compilation unit that is an instantiation, but
14683 -- instantiation node has not been replaced with package decl.
14685 Inst_Node
:= Unit
(Parent
(True_Parent
));
14688 elsif Nkind
(True_Parent
) = N_Package_Declaration
14689 and then Nkind
(Parent
(True_Parent
)) /= N_Compilation_Unit
14690 and then Present
(Generic_Parent
(Specification
(True_Parent
)))
14692 -- Parent is an instantiation within another specification.
14693 -- Declaration for instance has been inserted before original
14694 -- instantiation node. A direct link would be preferable?
14696 Inst_Node
:= Next
(True_Parent
);
14697 while Present
(Inst_Node
)
14698 and then Nkind
(Inst_Node
) /= N_Package_Instantiation
14703 -- If the instance appears within a generic, and the generic
14704 -- unit is defined within a formal package of the enclosing
14705 -- generic, there is no generic body available, and none
14706 -- needed. A more precise test should be used ???
14708 if No
(Inst_Node
) then
14714 -- If an ancestor of the generic comes from a formal package
14715 -- there is no source for the ancestor body. This is detected
14716 -- by examining the scope of the ancestor and its declaration.
14717 -- The body, if any is needed, will be available when the
14718 -- current unit (containing a formal package) is instantiated.
14720 elsif Nkind
(True_Parent
) = N_Package_Specification
14721 and then Present
(Generic_Parent
(True_Parent
))
14723 (Original_Node
(Unit_Declaration_Node
14724 (Scope
(Generic_Parent
(True_Parent
)))))
14725 = N_Formal_Package_Declaration
14730 True_Parent
:= Parent
(True_Parent
);
14734 -- Case where we are currently instantiating a nested generic
14736 if Present
(Inst_Node
) then
14737 if Nkind
(Parent
(True_Parent
)) = N_Compilation_Unit
then
14739 -- Instantiation node and declaration of instantiated package
14740 -- were exchanged when only the declaration was needed.
14741 -- Restore instantiation node before proceeding with body.
14743 Set_Unit
(Parent
(True_Parent
), Inst_Node
);
14746 -- Now complete instantiation of enclosing body, if it appears in
14747 -- some other unit. If it appears in the current unit, the body
14748 -- will have been instantiated already.
14750 if No
(Corresponding_Body
(Instance_Spec
(Inst_Node
))) then
14752 -- We need to determine the expander mode to instantiate the
14753 -- enclosing body. Because the generic body we need may use
14754 -- global entities declared in the enclosing package (including
14755 -- aggregates) it is in general necessary to compile this body
14756 -- with expansion enabled, except if we are within a generic
14757 -- package, in which case the usual generic rule applies.
14760 Exp_Status
: Boolean := True;
14764 -- Loop through scopes looking for generic package
14766 Scop
:= Scope
(Defining_Entity
(Instance_Spec
(Inst_Node
)));
14767 while Present
(Scop
)
14768 and then Scop
/= Standard_Standard
14770 if Ekind
(Scop
) = E_Generic_Package
then
14771 Exp_Status
:= False;
14775 Scop
:= Scope
(Scop
);
14778 -- Collect previous instantiations in the unit that contains
14779 -- the desired generic.
14781 if Nkind
(Parent
(True_Parent
)) /= N_Compilation_Unit
14782 and then not Body_Optional
14786 Info
: Pending_Body_Info
;
14790 Par
:= Parent
(Inst_Node
);
14791 while Present
(Par
) loop
14792 exit when Nkind
(Parent
(Par
)) = N_Compilation_Unit
;
14793 Par
:= Parent
(Par
);
14796 pragma Assert
(Present
(Par
));
14798 if Nkind
(Par
) = N_Package_Body
then
14799 Collect_Previous_Instances
(Declarations
(Par
));
14801 elsif Nkind
(Par
) = N_Package_Declaration
then
14802 Collect_Previous_Instances
14803 (Visible_Declarations
(Specification
(Par
)));
14804 Collect_Previous_Instances
14805 (Private_Declarations
(Specification
(Par
)));
14808 -- Enclosing unit is a subprogram body. In this
14809 -- case all instance bodies are processed in order
14810 -- and there is no need to collect them separately.
14815 Decl
:= First_Elmt
(Previous_Instances
);
14816 while Present
(Decl
) loop
14818 (Inst_Node
=> Node
(Decl
),
14820 Instance_Spec
(Node
(Decl
)),
14822 Config_Switches
=> Save_Config_Switches
,
14823 Current_Sem_Unit
=>
14824 Get_Code_Unit
(Sloc
(Node
(Decl
))),
14825 Expander_Status
=> Exp_Status
,
14826 Local_Suppress_Stack_Top
=>
14827 Local_Suppress_Stack_Top
,
14828 Scope_Suppress
=> Scope_Suppress
,
14829 Warnings
=> Save_Warnings
);
14831 -- Package instance
14833 if Nkind
(Node
(Decl
)) = N_Package_Instantiation
14835 Instantiate_Package_Body
14836 (Info
, Body_Optional
=> True);
14838 -- Subprogram instance
14841 -- The instance_spec is in the wrapper package,
14842 -- usually followed by its local renaming
14843 -- declaration. See Build_Subprogram_Renaming
14844 -- for details. If the instance carries aspects,
14845 -- these result in the corresponding pragmas,
14846 -- inserted after the subprogram declaration.
14847 -- They must be skipped as well when retrieving
14848 -- the desired spec. Some of them may have been
14849 -- rewritten as null statements.
14850 -- A direct link would be more robust ???
14854 (Last
(Visible_Declarations
14855 (Specification
(Info
.Act_Decl
))));
14857 while Nkind
(Decl
) in
14860 N_Subprogram_Renaming_Declaration
14862 Decl
:= Prev
(Decl
);
14865 Info
.Act_Decl
:= Decl
;
14868 Instantiate_Subprogram_Body
14869 (Info
, Body_Optional
=> True);
14877 Instantiate_Package_Body
14879 ((Inst_Node
=> Inst_Node
,
14880 Act_Decl
=> True_Parent
,
14882 Config_Switches
=> Save_Config_Switches
,
14883 Current_Sem_Unit
=>
14884 Get_Code_Unit
(Sloc
(Inst_Node
)),
14885 Expander_Status
=> Exp_Status
,
14886 Local_Suppress_Stack_Top
=> Local_Suppress_Stack_Top
,
14887 Scope_Suppress
=> Scope_Suppress
,
14888 Warnings
=> Save_Warnings
)),
14889 Body_Optional
=> Body_Optional
);
14893 -- Case where we are not instantiating a nested generic
14896 Opt
.Style_Check
:= False;
14897 Expander_Mode_Save_And_Set
(True);
14898 Load_Needed_Body
(Comp_Unit
, OK
);
14899 Opt
.Style_Check
:= Saved_Style_Check
;
14900 Restore_Warnings
(Saved_Warn
);
14901 Expander_Mode_Restore
;
14904 and then Unit_Requires_Body
(Defining_Entity
(Spec
))
14905 and then not Body_Optional
14908 Bname
: constant Unit_Name_Type
:=
14909 Get_Body_Name
(Get_Unit_Name
(Unit
(Comp_Unit
)));
14912 -- In CodePeer mode, the missing body may make the analysis
14913 -- incomplete, but we do not treat it as fatal.
14915 if CodePeer_Mode
then
14919 Error_Msg_Unit_1
:= Bname
;
14920 Error_Msg_N
("this instantiation requires$!", N
);
14921 Error_Msg_File_1
:=
14922 Get_File_Name
(Bname
, Subunit
=> False);
14923 Error_Msg_N
("\but file{ was not found!", N
);
14924 raise Unrecoverable_Error
;
14931 -- If loading parent of the generic caused an instantiation circularity,
14932 -- we abandon compilation at this point, because otherwise in some cases
14933 -- we get into trouble with infinite recursions after this point.
14935 if Circularity_Detected
then
14936 raise Unrecoverable_Error
;
14938 end Load_Parent_Of_Generic
;
14940 ---------------------------------
14941 -- Map_Formal_Package_Entities --
14942 ---------------------------------
14944 procedure Map_Formal_Package_Entities
(Form
: Entity_Id
; Act
: Entity_Id
) is
14949 Set_Instance_Of
(Form
, Act
);
14951 -- Traverse formal and actual package to map the corresponding entities.
14952 -- We skip over internal entities that may be generated during semantic
14953 -- analysis, and find the matching entities by name, given that they
14954 -- must appear in the same order.
14956 E1
:= First_Entity
(Form
);
14957 E2
:= First_Entity
(Act
);
14958 while Present
(E1
) and then E1
/= First_Private_Entity
(Form
) loop
14959 -- Could this test be a single condition??? Seems like it could, and
14960 -- isn't FPE (Form) a constant anyway???
14962 if not Is_Internal
(E1
)
14963 and then Present
(Parent
(E1
))
14964 and then not Is_Class_Wide_Type
(E1
)
14965 and then not Is_Internal_Name
(Chars
(E1
))
14967 while Present
(E2
) and then Chars
(E2
) /= Chars
(E1
) loop
14974 Set_Instance_Of
(E1
, E2
);
14976 if Is_Type
(E1
) and then Is_Tagged_Type
(E2
) then
14977 Set_Instance_Of
(Class_Wide_Type
(E1
), Class_Wide_Type
(E2
));
14980 if Is_Constrained
(E1
) then
14981 Set_Instance_Of
(Base_Type
(E1
), Base_Type
(E2
));
14984 if Ekind
(E1
) = E_Package
and then No
(Renamed_Entity
(E1
)) then
14985 Map_Formal_Package_Entities
(E1
, E2
);
14992 end Map_Formal_Package_Entities
;
14994 -----------------------
14995 -- Move_Freeze_Nodes --
14996 -----------------------
14998 procedure Move_Freeze_Nodes
14999 (Out_Of
: Entity_Id
;
15004 Next_Decl
: Node_Id
;
15005 Next_Node
: Node_Id
:= After
;
15008 function Is_Outer_Type
(T
: Entity_Id
) return Boolean;
15009 -- Check whether entity is declared in a scope external to that of the
15012 -------------------
15013 -- Is_Outer_Type --
15014 -------------------
15016 function Is_Outer_Type
(T
: Entity_Id
) return Boolean is
15017 Scop
: Entity_Id
:= Scope
(T
);
15020 if Scope_Depth
(Scop
) < Scope_Depth
(Out_Of
) then
15024 while Scop
/= Standard_Standard
loop
15025 if Scop
= Out_Of
then
15028 Scop
:= Scope
(Scop
);
15036 -- Start of processing for Move_Freeze_Nodes
15043 -- First remove the freeze nodes that may appear before all other
15047 while Present
(Decl
)
15048 and then Nkind
(Decl
) = N_Freeze_Entity
15049 and then Is_Outer_Type
(Entity
(Decl
))
15051 Decl
:= Remove_Head
(L
);
15052 Insert_After
(Next_Node
, Decl
);
15053 Set_Analyzed
(Decl
, False);
15058 -- Next scan the list of declarations and remove each freeze node that
15059 -- appears ahead of the current node.
15061 while Present
(Decl
) loop
15062 while Present
(Next
(Decl
))
15063 and then Nkind
(Next
(Decl
)) = N_Freeze_Entity
15064 and then Is_Outer_Type
(Entity
(Next
(Decl
)))
15066 Next_Decl
:= Remove_Next
(Decl
);
15067 Insert_After
(Next_Node
, Next_Decl
);
15068 Set_Analyzed
(Next_Decl
, False);
15069 Next_Node
:= Next_Decl
;
15072 -- If the declaration is a nested package or concurrent type, then
15073 -- recurse. Nested generic packages will have been processed from the
15076 case Nkind
(Decl
) is
15077 when N_Package_Declaration
=>
15078 Spec
:= Specification
(Decl
);
15080 when N_Task_Type_Declaration
=>
15081 Spec
:= Task_Definition
(Decl
);
15083 when N_Protected_Type_Declaration
=>
15084 Spec
:= Protected_Definition
(Decl
);
15090 if Present
(Spec
) then
15091 Move_Freeze_Nodes
(Out_Of
, Next_Node
, Visible_Declarations
(Spec
));
15092 Move_Freeze_Nodes
(Out_Of
, Next_Node
, Private_Declarations
(Spec
));
15097 end Move_Freeze_Nodes
;
15103 function Next_Assoc
(E
: Assoc_Ptr
) return Assoc_Ptr
is
15105 return Generic_Renamings
.Table
(E
).Next_In_HTable
;
15108 ------------------------
15109 -- Preanalyze_Actuals --
15110 ------------------------
15112 procedure Preanalyze_Actuals
(N
: Node_Id
; Inst
: Entity_Id
:= Empty
) is
15113 procedure Perform_Appropriate_Analysis
(N
: Node_Id
);
15114 -- Determine if the actuals we are analyzing come from a generic
15115 -- instantiation that is a library unit and dispatch accordingly.
15117 ----------------------------------
15118 -- Perform_Appropriate_Analysis --
15119 ----------------------------------
15121 procedure Perform_Appropriate_Analysis
(N
: Node_Id
) is
15123 -- When we have a library instantiation we cannot allow any expansion
15124 -- to occur, since there may be no place to put it. Instead, in that
15125 -- case we perform a preanalysis of the actual.
15127 if Present
(Inst
) and then Is_Compilation_Unit
(Inst
) then
15132 end Perform_Appropriate_Analysis
;
15136 Errs
: constant Nat
:= Serious_Errors_Detected
;
15141 Cur
: Entity_Id
:= Empty
;
15142 -- Current homograph of the instance name
15144 Vis
: Boolean := False;
15145 -- Saved visibility status of the current homograph
15147 -- Start of processing for Preanalyze_Actuals
15150 Assoc
:= First
(Generic_Associations
(N
));
15152 -- If the instance is a child unit, its name may hide an outer homonym,
15153 -- so make it invisible to perform name resolution on the actuals.
15155 if Nkind
(Defining_Unit_Name
(N
)) = N_Defining_Program_Unit_Name
15157 (Current_Entity
(Defining_Identifier
(Defining_Unit_Name
(N
))))
15159 Cur
:= Current_Entity
(Defining_Identifier
(Defining_Unit_Name
(N
)));
15161 if Is_Compilation_Unit
(Cur
) then
15162 Vis
:= Is_Immediately_Visible
(Cur
);
15163 Set_Is_Immediately_Visible
(Cur
, False);
15169 while Present
(Assoc
) loop
15170 if Nkind
(Assoc
) /= N_Others_Choice
then
15171 Act
:= Explicit_Generic_Actual_Parameter
(Assoc
);
15173 -- Within a nested instantiation, a defaulted actual is an empty
15174 -- association, so nothing to analyze. If the subprogram actual
15175 -- is an attribute, analyze prefix only, because actual is not a
15176 -- complete attribute reference.
15178 -- If actual is an allocator, analyze expression only. The full
15179 -- analysis can generate code, and if instance is a compilation
15180 -- unit we have to wait until the package instance is installed
15181 -- to have a proper place to insert this code.
15183 -- String literals may be operators, but at this point we do not
15184 -- know whether the actual is a formal subprogram or a string.
15189 elsif Nkind
(Act
) = N_Attribute_Reference
then
15190 Perform_Appropriate_Analysis
(Prefix
(Act
));
15192 elsif Nkind
(Act
) = N_Explicit_Dereference
then
15193 Perform_Appropriate_Analysis
(Prefix
(Act
));
15195 elsif Nkind
(Act
) = N_Allocator
then
15197 Expr
: constant Node_Id
:= Expression
(Act
);
15200 if Nkind
(Expr
) = N_Subtype_Indication
then
15201 Perform_Appropriate_Analysis
(Subtype_Mark
(Expr
));
15203 -- Analyze separately each discriminant constraint, when
15204 -- given with a named association.
15210 Constr
:= First
(Constraints
(Constraint
(Expr
)));
15211 while Present
(Constr
) loop
15212 if Nkind
(Constr
) = N_Discriminant_Association
then
15213 Perform_Appropriate_Analysis
15214 (Expression
(Constr
));
15216 Perform_Appropriate_Analysis
(Constr
);
15224 Perform_Appropriate_Analysis
(Expr
);
15228 elsif Nkind
(Act
) /= N_Operator_Symbol
then
15229 Perform_Appropriate_Analysis
(Act
);
15231 -- Within a package instance, mark actuals that are limited
15232 -- views, so their use can be moved to the body of the
15235 if Is_Entity_Name
(Act
)
15236 and then Is_Type
(Entity
(Act
))
15237 and then From_Limited_With
(Entity
(Act
))
15238 and then Present
(Inst
)
15240 Append_Elmt
(Entity
(Act
), Incomplete_Actuals
(Inst
));
15244 if Errs
/= Serious_Errors_Detected
then
15246 -- Do a minimal analysis of the generic, to prevent spurious
15247 -- warnings complaining about the generic being unreferenced,
15248 -- before abandoning the instantiation.
15250 Perform_Appropriate_Analysis
(Name
(N
));
15252 if Is_Entity_Name
(Name
(N
))
15253 and then Etype
(Name
(N
)) /= Any_Type
15255 Generate_Reference
(Entity
(Name
(N
)), Name
(N
));
15256 Set_Is_Instantiated
(Entity
(Name
(N
)));
15259 if Present
(Cur
) then
15261 -- For the case of a child instance hiding an outer homonym,
15262 -- provide additional warning which might explain the error.
15264 Set_Is_Immediately_Visible
(Cur
, Vis
);
15266 ("& hides outer unit with the same name??",
15267 N
, Defining_Unit_Name
(N
));
15270 Abandon_Instantiation
(Act
);
15277 if Present
(Cur
) then
15278 Set_Is_Immediately_Visible
(Cur
, Vis
);
15280 end Preanalyze_Actuals
;
15282 -------------------------------
15283 -- Provide_Completing_Bodies --
15284 -------------------------------
15286 procedure Provide_Completing_Bodies
(N
: Node_Id
) is
15287 procedure Build_Completing_Body
(Subp_Decl
: Node_Id
);
15288 -- Generate the completing body for subprogram declaration Subp_Decl
15290 procedure Provide_Completing_Bodies_In
(Decls
: List_Id
);
15291 -- Generating completing bodies for all subprograms found in declarative
15294 ---------------------------
15295 -- Build_Completing_Body --
15296 ---------------------------
15298 procedure Build_Completing_Body
(Subp_Decl
: Node_Id
) is
15299 Loc
: constant Source_Ptr
:= Sloc
(Subp_Decl
);
15300 Subp_Id
: constant Entity_Id
:= Defining_Entity
(Subp_Decl
);
15304 -- Nothing to do if the subprogram already has a completing body
15306 if Present
(Corresponding_Body
(Subp_Decl
)) then
15309 -- Mark the function as having a valid return statement even though
15310 -- the body contains a single raise statement.
15312 elsif Ekind
(Subp_Id
) = E_Function
then
15313 Set_Return_Present
(Subp_Id
);
15316 -- Clone the specification to obtain new entities and reset the only
15319 Spec
:= Copy_Subprogram_Spec
(Specification
(Subp_Decl
));
15320 Set_Generic_Parent
(Spec
, Empty
);
15323 -- function Func ... return ... is
15325 -- procedure Proc ... is
15327 -- raise Program_Error with "access before elaboration";
15330 Insert_After_And_Analyze
(Subp_Decl
,
15331 Make_Subprogram_Body
(Loc
,
15332 Specification
=> Spec
,
15333 Declarations
=> New_List
,
15334 Handled_Statement_Sequence
=>
15335 Make_Handled_Sequence_Of_Statements
(Loc
,
15336 Statements
=> New_List
(
15337 Make_Raise_Program_Error
(Loc
,
15338 Reason
=> PE_Access_Before_Elaboration
)))));
15339 end Build_Completing_Body
;
15341 ----------------------------------
15342 -- Provide_Completing_Bodies_In --
15343 ----------------------------------
15345 procedure Provide_Completing_Bodies_In
(Decls
: List_Id
) is
15349 if Present
(Decls
) then
15350 Decl
:= First
(Decls
);
15351 while Present
(Decl
) loop
15352 Provide_Completing_Bodies
(Decl
);
15356 end Provide_Completing_Bodies_In
;
15362 -- Start of processing for Provide_Completing_Bodies
15365 if Nkind
(N
) = N_Package_Declaration
then
15366 Spec
:= Specification
(N
);
15368 Push_Scope
(Defining_Entity
(N
));
15369 Provide_Completing_Bodies_In
(Visible_Declarations
(Spec
));
15370 Provide_Completing_Bodies_In
(Private_Declarations
(Spec
));
15373 elsif Nkind
(N
) = N_Subprogram_Declaration
then
15374 Build_Completing_Body
(N
);
15376 end Provide_Completing_Bodies
;
15378 -------------------
15379 -- Remove_Parent --
15380 -------------------
15382 procedure Remove_Parent
(In_Body
: Boolean := False) is
15383 S
: Entity_Id
:= Current_Scope
;
15384 -- S is the scope containing the instantiation just completed. The scope
15385 -- stack contains the parent instances of the instantiation, followed by
15394 -- After child instantiation is complete, remove from scope stack the
15395 -- extra copy of the current scope, and then remove parent instances.
15397 if not In_Body
then
15400 while Current_Scope
/= S
loop
15401 P
:= Current_Scope
;
15402 End_Package_Scope
(Current_Scope
);
15404 if In_Open_Scopes
(P
) then
15405 E
:= First_Entity
(P
);
15406 while Present
(E
) loop
15407 Set_Is_Immediately_Visible
(E
, True);
15411 -- If instantiation is declared in a block, it is the enclosing
15412 -- scope that might be a parent instance. Note that only one
15413 -- block can be involved, because the parent instances have
15414 -- been installed within it.
15416 if Ekind
(P
) = E_Block
then
15417 Cur_P
:= Scope
(P
);
15422 if Is_Generic_Instance
(Cur_P
) and then P
/= Current_Scope
then
15423 -- We are within an instance of some sibling. Retain
15424 -- visibility of parent, for proper subsequent cleanup, and
15425 -- reinstall private declarations as well.
15427 Set_In_Private_Part
(P
);
15428 Install_Private_Declarations
(P
);
15431 -- If the ultimate parent is a top-level unit recorded in
15432 -- Instance_Parent_Unit, then reset its visibility to what it was
15433 -- before instantiation. (It's not clear what the purpose is of
15434 -- testing whether Scope (P) is In_Open_Scopes, but that test was
15435 -- present before the ultimate parent test was added.???)
15437 elsif not In_Open_Scopes
(Scope
(P
))
15438 or else (P
= Instance_Parent_Unit
15439 and then not Parent_Unit_Visible
)
15441 Set_Is_Immediately_Visible
(P
, False);
15443 -- If the current scope is itself an instantiation of a generic
15444 -- nested within P, and we are in the private part of body of this
15445 -- instantiation, restore the full views of P, that were removed
15446 -- in End_Package_Scope above. This obscure case can occur when a
15447 -- subunit of a generic contains an instance of a child unit of
15448 -- its generic parent unit.
15450 elsif S
= Current_Scope
and then Is_Generic_Instance
(S
)
15451 and then (In_Package_Body
(S
) or else In_Private_Part
(S
))
15454 Par
: constant Entity_Id
:=
15455 Generic_Parent
(Package_Specification
(S
));
15458 and then P
= Scope
(Par
)
15460 Set_In_Private_Part
(P
);
15461 Install_Private_Declarations
(P
);
15467 -- Reset visibility of entities in the enclosing scope
15469 Set_Is_Hidden_Open_Scope
(Current_Scope
, False);
15471 Hidden
:= First_Elmt
(Hidden_Entities
);
15472 while Present
(Hidden
) loop
15473 Set_Is_Immediately_Visible
(Node
(Hidden
), True);
15474 Next_Elmt
(Hidden
);
15478 -- Each body is analyzed separately, and there is no context that
15479 -- needs preserving from one body instance to the next, so remove all
15480 -- parent scopes that have been installed.
15482 while Present
(S
) loop
15483 End_Package_Scope
(S
);
15484 Set_Is_Immediately_Visible
(S
, False);
15485 S
:= Current_Scope
;
15486 exit when S
= Standard_Standard
;
15491 -----------------------------------
15492 -- Requires_Conformance_Checking --
15493 -----------------------------------
15495 function Requires_Conformance_Checking
(N
: Node_Id
) return Boolean is
15497 -- No conformance checking required if the generic actual part is empty,
15498 -- or is a box or an others_clause (necessarily with a box).
15500 return Present
(Generic_Associations
(N
))
15501 and then not Box_Present
(N
)
15502 and then Nkind
(First
(Generic_Associations
(N
))) /= N_Others_Choice
;
15503 end Requires_Conformance_Checking
;
15509 procedure Restore_Env
is
15510 Saved
: Instance_Env
renames Instance_Envs
.Table
(Instance_Envs
.Last
);
15513 if No
(Current_Instantiated_Parent
.Act_Id
) then
15514 -- Restore environment after subprogram inlining
15516 Restore_Private_Views
(Empty
);
15519 Current_Instantiated_Parent
:= Saved
.Instantiated_Parent
;
15520 Exchanged_Views
:= Saved
.Exchanged_Views
;
15521 Hidden_Entities
:= Saved
.Hidden_Entities
;
15522 Current_Sem_Unit
:= Saved
.Current_Sem_Unit
;
15523 Parent_Unit_Visible
:= Saved
.Parent_Unit_Visible
;
15524 Instance_Parent_Unit
:= Saved
.Instance_Parent_Unit
;
15526 Restore_Config_Switches
(Saved
.Switches
);
15528 Instance_Envs
.Decrement_Last
;
15531 ---------------------------
15532 -- Restore_Private_Views --
15533 ---------------------------
15535 procedure Restore_Private_Views
15536 (Pack_Id
: Entity_Id
;
15537 Is_Package
: Boolean := True)
15542 Dep_Elmt
: Elmt_Id
;
15545 procedure Restore_Nested_Formal
(Formal
: Entity_Id
);
15546 -- Hide the generic formals of formal packages declared with box which
15547 -- were reachable in the current instantiation.
15549 ---------------------------
15550 -- Restore_Nested_Formal --
15551 ---------------------------
15553 procedure Restore_Nested_Formal
(Formal
: Entity_Id
) is
15554 pragma Assert
(Ekind
(Formal
) = E_Package
);
15557 if Present
(Renamed_Entity
(Formal
))
15558 and then Denotes_Formal_Package
(Renamed_Entity
(Formal
), True)
15562 elsif Present
(Associated_Formal_Package
(Formal
)) then
15563 Ent
:= First_Entity
(Formal
);
15564 while Present
(Ent
) loop
15565 exit when Ekind
(Ent
) = E_Package
15566 and then Renamed_Entity
(Ent
) = Renamed_Entity
(Formal
);
15568 Set_Is_Hidden
(Ent
);
15569 Set_Is_Potentially_Use_Visible
(Ent
, False);
15571 -- If package, then recurse
15573 if Ekind
(Ent
) = E_Package
then
15574 Restore_Nested_Formal
(Ent
);
15580 end Restore_Nested_Formal
;
15582 -- Start of processing for Restore_Private_Views
15585 M
:= First_Elmt
(Exchanged_Views
);
15586 while Present
(M
) loop
15589 -- Subtypes of types whose views have been exchanged, and that are
15590 -- defined within the instance, were not on the Private_Dependents
15591 -- list on entry to the instance, so they have to be exchanged
15592 -- explicitly now, in order to remain consistent with the view of the
15595 if Ekind
(Typ
) in E_Private_Type
15596 | E_Limited_Private_Type
15597 | E_Record_Type_With_Private
15599 Dep_Elmt
:= First_Elmt
(Private_Dependents
(Typ
));
15600 while Present
(Dep_Elmt
) loop
15601 Dep_Typ
:= Node
(Dep_Elmt
);
15603 if Scope
(Dep_Typ
) = Pack_Id
15604 and then Present
(Full_View
(Dep_Typ
))
15606 Replace_Elmt
(Dep_Elmt
, Full_View
(Dep_Typ
));
15607 Exchange_Declarations
(Dep_Typ
);
15610 Next_Elmt
(Dep_Elmt
);
15614 Exchange_Declarations
(Typ
);
15618 if No
(Pack_Id
) then
15622 -- Make the generic formal parameters private, and make the formal types
15623 -- into subtypes of the actuals again.
15625 E
:= First_Entity
(Pack_Id
);
15626 while Present
(E
) loop
15627 Set_Is_Hidden
(E
, True);
15630 and then Nkind
(Parent
(E
)) = N_Subtype_Declaration
15632 -- Always preserve the flag Is_Generic_Actual_Type for GNATprove,
15633 -- as it is needed to identify the subtype with the type it
15634 -- renames, when there are conversions between access types
15637 if GNATprove_Mode
then
15640 -- If the actual for E is itself a generic actual type from
15641 -- an enclosing instance, E is still a generic actual type
15642 -- outside of the current instance. This matter when resolving
15643 -- an overloaded call that may be ambiguous in the enclosing
15644 -- instance, when two of its actuals coincide.
15646 elsif Is_Entity_Name
(Subtype_Indication
(Parent
(E
)))
15647 and then Is_Generic_Actual_Type
15648 (Entity
(Subtype_Indication
(Parent
(E
))))
15652 Set_Is_Generic_Actual_Type
(E
, False);
15654 -- It might seem reasonable to clear the Is_Generic_Actual_Type
15655 -- flag also on the Full_View if the type is private, since it
15656 -- was set also on this Full_View. However, this flag is relied
15657 -- upon by Covers to spot "types exported from instantiations"
15658 -- which are implicit Full_Views built for instantiations made
15659 -- on private types and we get type mismatches if we do it when
15660 -- the block exchanging the declarations below triggers ???
15662 -- if Is_Private_Type (E) and then Present (Full_View (E)) then
15663 -- Set_Is_Generic_Actual_Type (Full_View (E), False);
15667 -- An unusual case of aliasing: the actual may also be directly
15668 -- visible in the generic, and be private there, while it is fully
15669 -- visible in the context of the instance. The internal subtype
15670 -- is private in the instance but has full visibility like its
15671 -- parent in the enclosing scope. This enforces the invariant that
15672 -- the privacy status of all private dependents of a type coincide
15673 -- with that of the parent type. This can only happen when a
15674 -- generic child unit is instantiated within a sibling.
15676 if Is_Private_Type
(E
)
15677 and then not Is_Private_Type
(Etype
(E
))
15679 Exchange_Declarations
(E
);
15682 elsif Ekind
(E
) = E_Package
then
15684 -- The end of the renaming list is the renaming of the generic
15685 -- package itself. If the instance is a subprogram, all entities
15686 -- in the corresponding package are renamings. If this entity is
15687 -- a formal package, make its own formals private as well. The
15688 -- actual in this case is itself the renaming of an instantiation.
15689 -- If the entity is not a package renaming, it is the entity
15690 -- created to validate formal package actuals: ignore it.
15692 -- If the actual is itself a formal package for the enclosing
15693 -- generic, or the actual for such a formal package, it remains
15694 -- visible on exit from the instance, and therefore nothing needs
15695 -- to be done either, except to keep it accessible.
15697 if Is_Package
and then Renamed_Entity
(E
) = Pack_Id
then
15700 elsif Nkind
(Parent
(E
)) /= N_Package_Renaming_Declaration
then
15704 Denotes_Formal_Package
(Renamed_Entity
(E
), True, Pack_Id
)
15706 Set_Is_Hidden
(E
, False);
15710 Act_P
: constant Entity_Id
:= Renamed_Entity
(E
);
15714 Id
:= First_Entity
(Act_P
);
15716 and then Id
/= First_Private_Entity
(Act_P
)
15718 exit when Ekind
(Id
) = E_Package
15719 and then Renamed_Entity
(Id
) = Act_P
;
15721 Set_Is_Hidden
(Id
, True);
15722 Set_Is_Potentially_Use_Visible
(Id
, In_Use
(Act_P
));
15724 if Ekind
(Id
) = E_Package
then
15725 Restore_Nested_Formal
(Id
);
15736 end Restore_Private_Views
;
15743 (Gen_Unit
: Entity_Id
;
15744 Act_Unit
: Entity_Id
)
15748 Set_Instance_Env
(Gen_Unit
, Act_Unit
);
15751 ----------------------------
15752 -- Save_Global_References --
15753 ----------------------------
15755 procedure Save_Global_References
(Templ
: Node_Id
) is
15757 -- ??? it is horrible to use global variables in highly recursive code
15760 -- The entity of the current associated node
15762 Gen_Scope
: Entity_Id
;
15763 -- The scope of the generic for which references are being saved
15766 -- The current associated node
15768 function Is_Global
(E
: Entity_Id
) return Boolean;
15769 -- Check whether entity is defined outside of generic unit. Examine the
15770 -- scope of an entity, and the scope of the scope, etc, until we find
15771 -- either Standard, in which case the entity is global, or the generic
15772 -- unit itself, which indicates that the entity is local. If the entity
15773 -- is the generic unit itself, as in the case of a recursive call, or
15774 -- the enclosing generic unit, if different from the current scope, then
15775 -- it is local as well, because it will be replaced at the point of
15776 -- instantiation. On the other hand, if it is a reference to a child
15777 -- unit of a common ancestor, which appears in an instantiation, it is
15778 -- global because it is used to denote a specific compilation unit at
15779 -- the time the instantiations will be analyzed.
15781 procedure Qualify_Universal_Operands
15783 Func_Call
: Node_Id
);
15784 -- Op denotes a binary or unary operator in generic template Templ. Node
15785 -- Func_Call is the function call alternative of the operator within the
15786 -- the analyzed copy of the template. Change each operand which yields a
15787 -- universal type by wrapping it into a qualified expression
15789 -- Actual_Typ'(Operand)
15791 -- where Actual_Typ is the type of corresponding actual parameter of
15792 -- Operand in Func_Call.
15794 procedure Reset_Entity
(N
: Node_Id
);
15795 -- Save semantic information on global entity so that it is not resolved
15796 -- again at instantiation time.
15798 procedure Save_Entity_Descendants
(N
: Node_Id
);
15799 -- Apply Save_Global_References to the two syntactic descendants of
15800 -- non-terminal nodes that carry an Associated_Node and are processed
15801 -- through Reset_Entity. Once the global entity (if any) has been
15802 -- captured together with its type, only two syntactic descendants need
15803 -- to be traversed to complete the processing of the tree rooted at N.
15804 -- This applies to Selected_Components, Expanded_Names, and to Operator
15805 -- nodes. N can also be a character literal, identifier, or operator
15806 -- symbol node, but the call has no effect in these cases.
15808 procedure Save_Global_Defaults
(N1
: Node_Id
; N2
: Node_Id
);
15809 -- Default actuals in nested instances must be handled specially
15810 -- because there is no link to them from the original tree. When an
15811 -- actual subprogram is given by a default, we add an explicit generic
15812 -- association for it in the instantiation node. When we save the
15813 -- global references on the name of the instance, we recover the list
15814 -- of generic associations, and add an explicit one to the original
15815 -- generic tree, through which a global actual can be preserved.
15816 -- Similarly, if a child unit is instantiated within a sibling, in the
15817 -- context of the parent, we must preserve the identifier of the parent
15818 -- so that it can be properly resolved in a subsequent instantiation.
15820 procedure Save_Global_Descendant
(D
: Union_Id
);
15821 -- Apply Save_References recursively to the descendants of node D
15823 procedure Save_References
(N
: Node_Id
);
15824 -- This is the recursive procedure that does the work, once the
15825 -- enclosing generic scope has been established.
15827 procedure Set_Global_Type
(N
: Node_Id
; N2
: Node_Id
);
15828 -- If the type of N2 is global to the generic unit, save the type in
15829 -- the generic node. Just as we perform name capture for explicit
15830 -- references within the generic, we must capture the global types
15831 -- of local entities because they may participate in resolution in
15838 function Is_Global
(E
: Entity_Id
) return Boolean is
15841 function Is_Instance_Node
(Decl
: Node_Id
) return Boolean;
15842 -- Determine whether the parent node of a reference to a child unit
15843 -- denotes an instantiation or a formal package, in which case the
15844 -- reference to the child unit is global, even if it appears within
15845 -- the current scope (e.g. when the instance appears within the body
15846 -- of an ancestor).
15848 ----------------------
15849 -- Is_Instance_Node --
15850 ----------------------
15852 function Is_Instance_Node
(Decl
: Node_Id
) return Boolean is
15854 return Nkind
(Decl
) in N_Generic_Instantiation
15856 Nkind
(Original_Node
(Decl
)) = N_Formal_Package_Declaration
;
15857 end Is_Instance_Node
;
15859 -- Start of processing for Is_Global
15862 if E
= Gen_Scope
then
15865 elsif E
= Standard_Standard
then
15868 -- E should be an entity, but it is not always
15870 elsif Nkind
(E
) not in N_Entity
then
15873 elsif Nkind
(E
) /= N_Expanded_Name
15874 and then Is_Child_Unit
(E
)
15875 and then (Is_Instance_Node
(Parent
(N2
))
15876 or else (Nkind
(Parent
(N2
)) = N_Expanded_Name
15877 and then N2
= Selector_Name
(Parent
(N2
))
15879 Is_Instance_Node
(Parent
(Parent
(N2
)))))
15884 -- E may be an expanded name - typically an operator - in which
15885 -- case we must find its enclosing scope since expanded names
15886 -- don't have corresponding scopes.
15888 if Nkind
(E
) = N_Expanded_Name
then
15889 Se
:= Find_Enclosing_Scope
(E
);
15891 -- Otherwise, E is an entity and will have Scope set
15897 while Se
/= Gen_Scope
loop
15898 if Se
= Standard_Standard
then
15909 --------------------------------
15910 -- Qualify_Universal_Operands --
15911 --------------------------------
15913 procedure Qualify_Universal_Operands
15915 Func_Call
: Node_Id
)
15917 procedure Qualify_Operand
(Opnd
: Node_Id
; Actual
: Node_Id
);
15918 -- Rewrite operand Opnd as a qualified expression of the form
15920 -- Actual_Typ'(Opnd)
15922 -- where Actual is the corresponding actual parameter of Opnd in
15923 -- function call Func_Call.
15925 function Qualify_Type
15927 Typ
: Entity_Id
) return Node_Id
;
15928 -- Qualify type Typ by creating a selected component of the form
15930 -- Scope_Of_Typ.Typ
15932 ---------------------
15933 -- Qualify_Operand --
15934 ---------------------
15936 procedure Qualify_Operand
(Opnd
: Node_Id
; Actual
: Node_Id
) is
15937 Loc
: constant Source_Ptr
:= Sloc
(Opnd
);
15938 Typ
: constant Entity_Id
:= Etype
(Actual
);
15943 -- Qualify the operand when it is of a universal type. Note that
15944 -- the template is unanalyzed and it is not possible to directly
15945 -- query the type. This transformation is not done when the type
15946 -- of the actual is internally generated because the type will be
15947 -- regenerated in the instance.
15949 if Yields_Universal_Type
(Opnd
)
15950 and then Comes_From_Source
(Typ
)
15951 and then not Is_Hidden
(Typ
)
15953 -- The type of the actual may be a global reference. Save this
15954 -- information by creating a reference to it.
15956 if Is_Global
(Typ
) then
15957 Mark
:= New_Occurrence_Of
(Typ
, Loc
);
15959 -- Otherwise rely on resolution to find the proper type within
15963 Mark
:= Qualify_Type
(Loc
, Typ
);
15967 Make_Qualified_Expression
(Loc
,
15968 Subtype_Mark
=> Mark
,
15969 Expression
=> Relocate_Node
(Opnd
));
15971 -- Mark the qualification to distinguish it from other source
15972 -- constructs and signal the instantiation mechanism that this
15973 -- node requires special processing. See Copy_Generic_Node for
15976 Set_Is_Qualified_Universal_Literal
(Qual
);
15978 Rewrite
(Opnd
, Qual
);
15980 end Qualify_Operand
;
15986 function Qualify_Type
15988 Typ
: Entity_Id
) return Node_Id
15990 Scop
: constant Entity_Id
:= Scope
(Typ
);
15994 Result
:= Make_Identifier
(Loc
, Chars
(Typ
));
15996 if Present
(Scop
) and then not Is_Generic_Unit
(Scop
) then
15998 Make_Selected_Component
(Loc
,
15999 Prefix
=> Make_Identifier
(Loc
, Chars
(Scop
)),
16000 Selector_Name
=> Result
);
16008 Actuals
: constant List_Id
:= Parameter_Associations
(Func_Call
);
16010 -- Start of processing for Qualify_Universal_Operands
16013 if Nkind
(Op
) in N_Binary_Op
then
16014 Qualify_Operand
(Left_Opnd
(Op
), First
(Actuals
));
16015 Qualify_Operand
(Right_Opnd
(Op
), Next
(First
(Actuals
)));
16017 elsif Nkind
(Op
) in N_Unary_Op
then
16018 Qualify_Operand
(Right_Opnd
(Op
), First
(Actuals
));
16020 end Qualify_Universal_Operands
;
16026 procedure Reset_Entity
(N
: Node_Id
) is
16027 function Top_Ancestor
(E
: Entity_Id
) return Entity_Id
;
16028 -- Find the ultimate ancestor of the current unit. If it is not a
16029 -- generic unit, then the name of the current unit in the prefix of
16030 -- an expanded name must be replaced with its generic homonym to
16031 -- ensure that it will be properly resolved in an instance.
16037 function Top_Ancestor
(E
: Entity_Id
) return Entity_Id
is
16042 while Is_Child_Unit
(Par
) loop
16043 Par
:= Scope
(Par
);
16049 -- Start of processing for Reset_Entity
16052 N2
:= Get_Associated_Node
(N
);
16055 if Present
(E
) then
16057 -- If the node is an entry call to an entry in an enclosing task,
16058 -- it is rewritten as a selected component. No global entity to
16059 -- preserve in this case, since the expansion will be redone in
16062 if Nkind
(E
) not in N_Entity
then
16063 Set_Associated_Node
(N
, Empty
);
16064 Set_Etype
(N
, Empty
);
16068 -- If the entity is an itype created as a subtype of an access
16069 -- type with a null exclusion restore source entity for proper
16070 -- visibility. The itype will be created anew in the instance.
16073 and then Ekind
(E
) = E_Access_Subtype
16074 and then Is_Entity_Name
(N
)
16075 and then Chars
(Etype
(E
)) = Chars
(N
)
16078 Set_Entity
(N2
, E
);
16082 if Is_Global
(E
) then
16083 Set_Global_Type
(N
, N2
);
16085 elsif Nkind
(N
) = N_Op_Concat
16086 and then Is_Generic_Type
(Etype
(N2
))
16087 and then (Base_Type
(Etype
(Right_Opnd
(N2
))) = Etype
(N2
)
16089 Base_Type
(Etype
(Left_Opnd
(N2
))) = Etype
(N2
))
16090 and then Is_Intrinsic_Subprogram
(E
)
16094 -- Entity is local. Mark generic node as unresolved. Note that now
16095 -- it does not have an entity.
16098 Set_Associated_Node
(N
, Empty
);
16099 Set_Etype
(N
, Empty
);
16102 if Nkind
(Parent
(N
)) in N_Generic_Instantiation
16103 and then N
= Name
(Parent
(N
))
16105 Save_Global_Defaults
(Parent
(N
), Parent
(N2
));
16108 elsif Nkind
(Parent
(N
)) = N_Selected_Component
16109 and then Nkind
(Parent
(N2
)) = N_Expanded_Name
16111 -- In case of previous errors, the tree might be malformed
16113 if No
(Entity
(Parent
(N2
))) then
16116 elsif Is_Global
(Entity
(Parent
(N2
))) then
16117 Change_Selected_Component_To_Expanded_Name
(Parent
(N
));
16118 Set_Associated_Node
(Parent
(N
), Parent
(N2
));
16119 Set_Global_Type
(Parent
(N
), Parent
(N2
));
16120 Save_Entity_Descendants
(N
);
16122 -- If this is a reference to the current generic entity, replace
16123 -- by the name of the generic homonym of the current package. This
16124 -- is because in an instantiation Par.P.Q will not resolve to the
16125 -- name of the instance, whose enclosing scope is not necessarily
16126 -- Par. We use the generic homonym rather that the name of the
16127 -- generic itself because it may be hidden by a local declaration.
16129 elsif In_Open_Scopes
(Entity
(Parent
(N2
)))
16131 Is_Generic_Unit
(Top_Ancestor
(Entity
(Prefix
(Parent
(N2
)))))
16133 if Ekind
(Entity
(Parent
(N2
))) = E_Generic_Package
then
16134 Rewrite
(Parent
(N
),
16135 Make_Identifier
(Sloc
(N
),
16137 Chars
(Generic_Homonym
(Entity
(Parent
(N2
))))));
16139 Rewrite
(Parent
(N
),
16140 Make_Identifier
(Sloc
(N
),
16141 Chars
=> Chars
(Selector_Name
(Parent
(N2
)))));
16145 if Nkind
(Parent
(Parent
(N
))) in N_Generic_Instantiation
16146 and then Parent
(N
) = Name
(Parent
(Parent
(N
)))
16148 Save_Global_Defaults
16149 (Parent
(Parent
(N
)), Parent
(Parent
(N2
)));
16152 -- A selected component may denote a static constant that has been
16153 -- folded. If the static constant is global to the generic, capture
16154 -- its value. Otherwise the folding will happen in any instantiation.
16156 elsif Nkind
(Parent
(N
)) = N_Selected_Component
16157 and then Nkind
(Parent
(N2
)) in N_Integer_Literal | N_Real_Literal
16159 if Present
(Entity
(Original_Node
(Parent
(N2
))))
16160 and then Is_Global
(Entity
(Original_Node
(Parent
(N2
))))
16162 Rewrite
(Parent
(N
), New_Copy
(Parent
(N2
)));
16163 Set_Analyzed
(Parent
(N
), False);
16166 -- A selected component may be transformed into a parameterless
16167 -- function call. If the called entity is global, rewrite the node
16168 -- appropriately, i.e. as an extended name for the global entity.
16170 elsif Nkind
(Parent
(N
)) = N_Selected_Component
16171 and then Nkind
(Parent
(N2
)) = N_Function_Call
16172 and then N
= Selector_Name
(Parent
(N
))
16174 if No
(Parameter_Associations
(Parent
(N2
))) then
16175 if Is_Global
(Entity
(Name
(Parent
(N2
)))) then
16176 Change_Selected_Component_To_Expanded_Name
(Parent
(N
));
16177 Set_Associated_Node
(Parent
(N
), Name
(Parent
(N2
)));
16178 Set_Global_Type
(Parent
(N
), Name
(Parent
(N2
)));
16179 Save_Entity_Descendants
(N
);
16182 Set_Is_Prefixed_Call
(Parent
(N
));
16183 Set_Associated_Node
(N
, Empty
);
16184 Set_Etype
(N
, Empty
);
16187 -- In Ada 2005, X.F may be a call to a primitive operation,
16188 -- rewritten as F (X). This rewriting will be done again in an
16189 -- instance, so keep the original node. Global entities will be
16190 -- captured as for other constructs. Indicate that this must
16191 -- resolve as a call, to prevent accidental overloading in the
16192 -- instance, if both a component and a primitive operation appear
16196 Set_Is_Prefixed_Call
(Parent
(N
));
16199 -- Entity is local. Reset in generic unit, so that node is resolved
16200 -- anew at the point of instantiation.
16203 Set_Associated_Node
(N
, Empty
);
16204 Set_Etype
(N
, Empty
);
16208 -----------------------------
16209 -- Save_Entity_Descendants --
16210 -----------------------------
16212 procedure Save_Entity_Descendants
(N
: Node_Id
) is
16215 when N_Binary_Op
=>
16216 Save_Global_Descendant
(Union_Id
(Left_Opnd
(N
)));
16217 Save_Global_Descendant
(Union_Id
(Right_Opnd
(N
)));
16220 Save_Global_Descendant
(Union_Id
(Right_Opnd
(N
)));
16222 when N_Expanded_Name
16223 | N_Selected_Component
16225 Save_Global_Descendant
(Union_Id
(Prefix
(N
)));
16226 Save_Global_Descendant
(Union_Id
(Selector_Name
(N
)));
16228 when N_Character_Literal
16230 | N_Operator_Symbol
16235 raise Program_Error
;
16237 end Save_Entity_Descendants
;
16239 --------------------------
16240 -- Save_Global_Defaults --
16241 --------------------------
16243 procedure Save_Global_Defaults
(N1
: Node_Id
; N2
: Node_Id
) is
16244 Loc
: constant Source_Ptr
:= Sloc
(N1
);
16245 Assoc2
: constant List_Id
:= Generic_Associations
(N2
);
16246 Gen_Id
: constant Entity_Id
:= Get_Generic_Entity
(N2
);
16253 Actual
: Entity_Id
;
16256 Assoc1
:= Generic_Associations
(N1
);
16258 if Present
(Assoc1
) then
16259 Act1
:= First
(Assoc1
);
16262 Set_Generic_Associations
(N1
, New_List
);
16263 Assoc1
:= Generic_Associations
(N1
);
16266 if Present
(Assoc2
) then
16267 Act2
:= First
(Assoc2
);
16272 while Present
(Act1
) and then Present
(Act2
) loop
16277 -- Find the associations added for default subprograms
16279 if Present
(Act2
) then
16280 while Nkind
(Act2
) /= N_Generic_Association
16281 or else No
(Entity
(Selector_Name
(Act2
)))
16282 or else not Is_Overloadable
(Entity
(Selector_Name
(Act2
)))
16287 -- Add a similar association if the default is global. The
16288 -- renaming declaration for the actual has been analyzed, and
16289 -- its alias is the program it renames. Link the actual in the
16290 -- original generic tree with the node in the analyzed tree.
16292 while Present
(Act2
) loop
16293 Subp
:= Entity
(Selector_Name
(Act2
));
16294 Def
:= Explicit_Generic_Actual_Parameter
(Act2
);
16296 -- Following test is defence against rubbish errors
16298 if No
(Alias
(Subp
)) then
16302 -- Retrieve the resolved actual from the renaming declaration
16303 -- created for the instantiated formal.
16305 Actual
:= Entity
(Name
(Parent
(Parent
(Subp
))));
16306 Set_Entity
(Def
, Actual
);
16307 Set_Etype
(Def
, Etype
(Actual
));
16309 if Is_Global
(Actual
) then
16311 Make_Generic_Association
(Loc
,
16313 New_Occurrence_Of
(Subp
, Loc
),
16314 Explicit_Generic_Actual_Parameter
=>
16315 New_Occurrence_Of
(Actual
, Loc
));
16317 Set_Associated_Node
16318 (Explicit_Generic_Actual_Parameter
(Ndec
), Def
);
16320 Append
(Ndec
, Assoc1
);
16322 -- If there are other defaults, add a dummy association in case
16323 -- there are other defaulted formals with the same name.
16325 elsif Present
(Next
(Act2
)) then
16327 Make_Generic_Association
(Loc
,
16329 New_Occurrence_Of
(Subp
, Loc
),
16330 Explicit_Generic_Actual_Parameter
=> Empty
);
16332 Append
(Ndec
, Assoc1
);
16339 if Nkind
(Name
(N1
)) = N_Identifier
16340 and then Is_Child_Unit
(Gen_Id
)
16341 and then Is_Global
(Gen_Id
)
16342 and then Is_Generic_Unit
(Scope
(Gen_Id
))
16343 and then In_Open_Scopes
(Scope
(Gen_Id
))
16345 -- This is an instantiation of a child unit within a sibling, so
16346 -- that the generic parent is in scope. An eventual instance must
16347 -- occur within the scope of an instance of the parent. Make name
16348 -- in instance into an expanded name, to preserve the identifier
16349 -- of the parent, so it can be resolved subsequently.
16351 Rewrite
(Name
(N2
),
16352 Make_Expanded_Name
(Loc
,
16353 Chars
=> Chars
(Gen_Id
),
16354 Prefix
=> New_Occurrence_Of
(Scope
(Gen_Id
), Loc
),
16355 Selector_Name
=> New_Occurrence_Of
(Gen_Id
, Loc
)));
16356 Set_Entity
(Name
(N2
), Gen_Id
);
16358 Rewrite
(Name
(N1
),
16359 Make_Expanded_Name
(Loc
,
16360 Chars
=> Chars
(Gen_Id
),
16361 Prefix
=> New_Occurrence_Of
(Scope
(Gen_Id
), Loc
),
16362 Selector_Name
=> New_Occurrence_Of
(Gen_Id
, Loc
)));
16364 Set_Associated_Node
(Name
(N1
), Name
(N2
));
16365 Set_Associated_Node
(Prefix
(Name
(N1
)), Empty
);
16366 Set_Associated_Node
16367 (Selector_Name
(Name
(N1
)), Selector_Name
(Name
(N2
)));
16368 Set_Etype
(Name
(N1
), Etype
(Gen_Id
));
16370 end Save_Global_Defaults
;
16372 ----------------------------
16373 -- Save_Global_Descendant --
16374 ----------------------------
16376 procedure Save_Global_Descendant
(D
: Union_Id
) is
16380 if D
in Node_Range
then
16381 if D
= Union_Id
(Empty
) then
16384 elsif Nkind
(Node_Id
(D
)) /= N_Compilation_Unit
then
16385 Save_References
(Node_Id
(D
));
16388 elsif D
in List_Range
then
16389 pragma Assert
(D
/= Union_Id
(No_List
));
16390 -- Because No_List = Empty, which is in Node_Range above
16392 N1
:= First
(List_Id
(D
));
16393 while Present
(N1
) loop
16394 Save_References
(N1
);
16398 -- Element list or other non-node field, nothing to do
16403 end Save_Global_Descendant
;
16405 ---------------------
16406 -- Save_References --
16407 ---------------------
16409 -- This is the recursive procedure that does the work once the enclosing
16410 -- generic scope has been established. We have to treat specially a
16411 -- number of node rewritings that are required by semantic processing
16412 -- and which change the kind of nodes in the generic copy: typically
16413 -- constant-folding, replacing an operator node by a string literal, or
16414 -- a selected component by an expanded name. In each of those cases, the
16415 -- transformation is propagated to the generic unit.
16417 procedure Save_References
(N
: Node_Id
) is
16418 Loc
: constant Source_Ptr
:= Sloc
(N
);
16420 function Requires_Delayed_Save
(Nod
: Node_Id
) return Boolean;
16421 -- Determine whether arbitrary node Nod requires delayed capture of
16422 -- global references within its aspect specifications.
16424 procedure Save_References_In_Aggregate
(N
: Node_Id
);
16425 -- Save all global references in [extension] aggregate node N
16427 procedure Save_References_In_Char_Lit_Or_Op_Symbol
(N
: Node_Id
);
16428 -- Save all global references in a character literal or operator
16429 -- symbol denoted by N.
16431 procedure Save_References_In_Descendants
(N
: Node_Id
);
16432 -- Save all global references in all descendants of node N
16434 procedure Save_References_In_Identifier
(N
: Node_Id
);
16435 -- Save all global references in identifier node N
16437 procedure Save_References_In_Operator
(N
: Node_Id
);
16438 -- Save all global references in operator node N
16440 procedure Save_References_In_Pragma
(Prag
: Node_Id
);
16441 -- Save all global references found within the expression of pragma
16444 ---------------------------
16445 -- Requires_Delayed_Save --
16446 ---------------------------
16448 function Requires_Delayed_Save
(Nod
: Node_Id
) return Boolean is
16450 -- Generic packages and subprograms require delayed capture of
16451 -- global references within their aspects due to the timing of
16452 -- annotation analysis.
16454 if Nkind
(Nod
) in N_Generic_Package_Declaration
16455 | N_Generic_Subprogram_Declaration
16457 | N_Package_Body_Stub
16458 | N_Subprogram_Body
16459 | N_Subprogram_Body_Stub
16461 -- Since the capture of global references is done on the
16462 -- unanalyzed generic template, there is no information around
16463 -- to infer the context. Use the Associated_Entity linkages to
16464 -- peek into the analyzed generic copy and determine what the
16465 -- template corresponds to.
16467 if Nod
= Templ
then
16469 Is_Generic_Declaration_Or_Body
16470 (Unit_Declaration_Node
16471 (Get_Associated_Entity
(Defining_Entity
(Nod
))));
16473 -- Otherwise the generic unit being processed is not the top
16474 -- level template. It is safe to capture of global references
16475 -- within the generic unit because at this point the top level
16476 -- copy is fully analyzed.
16482 -- Otherwise capture the global references without interference
16487 end Requires_Delayed_Save
;
16489 ----------------------------------
16490 -- Save_References_In_Aggregate --
16491 ----------------------------------
16493 procedure Save_References_In_Aggregate
(N
: Node_Id
) is
16495 Qual
: Node_Id
:= Empty
;
16496 Typ
: Entity_Id
:= Empty
;
16499 N2
:= Get_Associated_Node
(N
);
16501 if Present
(N2
) then
16504 -- In an instance within a generic, use the name of the actual
16505 -- and not the original generic parameter. If the actual is
16506 -- global in the current generic it must be preserved for its
16509 if Parent_Kind
(Typ
) = N_Subtype_Declaration
16510 and then Present
(Generic_Parent_Type
(Parent
(Typ
)))
16512 Typ
:= Base_Type
(Typ
);
16513 Set_Etype
(N2
, Typ
);
16517 if No
(N2
) or else No
(Typ
) or else not Is_Global
(Typ
) then
16518 Set_Associated_Node
(N
, Empty
);
16520 -- If the aggregate is an actual in a call, it has been
16521 -- resolved in the current context, to some local type. The
16522 -- enclosing call may have been disambiguated by the aggregate,
16523 -- and this disambiguation might fail at instantiation time
16524 -- because the type to which the aggregate did resolve is not
16525 -- preserved. In order to preserve some of this information,
16526 -- wrap the aggregate in a qualified expression, using the id
16527 -- of its type. For further disambiguation we qualify the type
16528 -- name with its scope (if visible and not hidden by a local
16529 -- homograph) because both id's will have corresponding
16530 -- entities in an instance. This resolves most of the problems
16531 -- with missing type information on aggregates in instances.
16534 and then Nkind
(N2
) = Nkind
(N
)
16535 and then Nkind
(Parent
(N2
)) in N_Subprogram_Call
16536 and then Present
(Typ
)
16537 and then Comes_From_Source
(Typ
)
16539 Nam
:= Make_Identifier
(Loc
, Chars
(Typ
));
16541 if Is_Immediately_Visible
(Scope
(Typ
))
16543 (not In_Open_Scopes
(Scope
(Typ
))
16544 or else Current_Entity
(Scope
(Typ
)) = Scope
(Typ
))
16547 Make_Selected_Component
(Loc
,
16549 Make_Identifier
(Loc
, Chars
(Scope
(Typ
))),
16550 Selector_Name
=> Nam
);
16554 Make_Qualified_Expression
(Loc
,
16555 Subtype_Mark
=> Nam
,
16556 Expression
=> Relocate_Node
(N
));
16560 if Nkind
(N
) = N_Aggregate
then
16561 Save_Global_Descendant
(Union_Id
(Aggregate_Bounds
(N
)));
16563 elsif Nkind
(N
) = N_Extension_Aggregate
then
16564 Save_Global_Descendant
(Union_Id
(Ancestor_Part
(N
)));
16567 pragma Assert
(False);
16570 Save_Global_Descendant
(Union_Id
(Expressions
(N
)));
16571 Save_Global_Descendant
(Union_Id
(Component_Associations
(N
)));
16572 Save_Global_Descendant
(Union_Id
(Etype
(N
)));
16574 if Present
(Qual
) then
16577 end Save_References_In_Aggregate
;
16579 ----------------------------------------------
16580 -- Save_References_In_Char_Lit_Or_Op_Symbol --
16581 ----------------------------------------------
16583 procedure Save_References_In_Char_Lit_Or_Op_Symbol
(N
: Node_Id
) is
16585 if Nkind
(N
) = Nkind
(Get_Associated_Node
(N
)) then
16588 elsif Nkind
(N
) = N_Operator_Symbol
16589 and then Nkind
(Get_Associated_Node
(N
)) = N_String_Literal
16591 Change_Operator_Symbol_To_String_Literal
(N
);
16593 end Save_References_In_Char_Lit_Or_Op_Symbol
;
16595 ------------------------------------
16596 -- Save_References_In_Descendants --
16597 ------------------------------------
16599 procedure Save_References_In_Descendants
(N
: Node_Id
) is
16600 procedure Walk
is new Walk_Sinfo_Fields
(Save_Global_Descendant
);
16603 end Save_References_In_Descendants
;
16605 -----------------------------------
16606 -- Save_References_In_Identifier --
16607 -----------------------------------
16609 procedure Save_References_In_Identifier
(N
: Node_Id
) is
16611 -- The node did not undergo a transformation
16613 if Nkind
(N
) = Nkind
(Get_Associated_Node
(N
)) then
16614 -- If this is a discriminant reference, always save it.
16615 -- It is used in the instance to find the corresponding
16616 -- discriminant positionally rather than by name.
16618 Set_Original_Discriminant
16619 (N
, Original_Discriminant
(Get_Associated_Node
(N
)));
16623 -- The analysis of the generic copy transformed the identifier
16624 -- into another construct. Propagate the changes to the template.
16627 N2
:= Get_Associated_Node
(N
);
16629 -- The identifier denotes a call to a parameterless function.
16630 -- Mark the node as resolved when the function is external.
16632 if Nkind
(N2
) = N_Function_Call
then
16633 E
:= Entity
(Name
(N2
));
16635 if Present
(E
) and then Is_Global
(E
) then
16636 Set_Global_Type
(N
, N2
);
16638 Set_Associated_Node
(N
, Empty
);
16639 Set_Etype
(N
, Empty
);
16642 -- The identifier denotes a named number that was constant
16643 -- folded. Preserve the original name for ASIS and undo the
16644 -- constant folding which will be repeated in the instance.
16645 -- Is this still needed???
16647 elsif Nkind
(N2
) in N_Integer_Literal | N_Real_Literal
16648 and then Is_Entity_Name
(Original_Node
(N2
))
16650 Set_Associated_Node
(N
, Original_Node
(N2
));
16653 -- The identifier resolved to a string literal. Propagate this
16654 -- information to the generic template.
16656 elsif Nkind
(N2
) = N_String_Literal
then
16657 Rewrite
(N
, New_Copy
(N2
));
16659 -- The identifier is rewritten as a dereference if it is the
16660 -- prefix of an implicit dereference. Preserve the original
16661 -- tree as the analysis of the instance will expand the node
16662 -- again, but preserve the resolved entity if it is global.
16664 elsif Nkind
(N2
) = N_Explicit_Dereference
then
16665 if Is_Entity_Name
(Prefix
(N2
))
16666 and then Present
(Entity
(Prefix
(N2
)))
16667 and then Is_Global
(Entity
(Prefix
(N2
)))
16669 Set_Associated_Node
(N
, Prefix
(N2
));
16670 Set_Global_Type
(N
, Prefix
(N2
));
16672 elsif Nkind
(Prefix
(N2
)) = N_Function_Call
16673 and then Is_Entity_Name
(Name
(Prefix
(N2
)))
16674 and then Present
(Entity
(Name
(Prefix
(N2
))))
16675 and then Is_Global
(Entity
(Name
(Prefix
(N2
))))
16678 Make_Explicit_Dereference
(Loc
,
16680 Make_Function_Call
(Loc
,
16683 (Entity
(Name
(Prefix
(N2
))), Loc
))));
16684 Set_Associated_Node
16685 (Name
(Prefix
(N
)), Name
(Prefix
(N2
)));
16686 Set_Global_Type
(Name
(Prefix
(N
)), Name
(Prefix
(N2
)));
16689 Set_Associated_Node
(N
, Empty
);
16690 Set_Etype
(N
, Empty
);
16693 -- The subtype mark of a nominally unconstrained object is
16694 -- rewritten as a subtype indication using the bounds of the
16695 -- expression. Recover the original subtype mark.
16697 elsif Nkind
(N2
) = N_Subtype_Indication
16698 and then Is_Entity_Name
(Original_Node
(N2
))
16700 Set_Associated_Node
(N
, Original_Node
(N2
));
16704 end Save_References_In_Identifier
;
16706 ---------------------------------
16707 -- Save_References_In_Operator --
16708 ---------------------------------
16710 procedure Save_References_In_Operator
(N
: Node_Id
) is
16712 N2
:= Get_Associated_Node
(N
);
16714 -- The node did not undergo a transformation
16716 if Nkind
(N
) = Nkind
(N2
) then
16717 if Nkind
(N
) = N_Op_Concat
then
16718 Set_Is_Component_Left_Opnd
16719 (N
, Is_Component_Left_Opnd
(N2
));
16720 Set_Is_Component_Right_Opnd
16721 (N
, Is_Component_Right_Opnd
(N2
));
16726 -- The analysis of the generic copy transformed the operator into
16727 -- some other construct. Propagate the changes to the template if
16731 -- The operator resoved to a function call
16733 if Nkind
(N2
) = N_Function_Call
then
16735 -- Add explicit qualifications in the generic template for
16736 -- all operands of universal type. This aids resolution by
16737 -- preserving the actual type of a literal or an attribute
16738 -- that yields a universal result.
16740 Qualify_Universal_Operands
(N
, N2
);
16742 E
:= Entity
(Name
(N2
));
16744 if Present
(E
) and then Is_Global
(E
) then
16745 Set_Global_Type
(N
, N2
);
16747 Set_Associated_Node
(N
, Empty
);
16748 Set_Etype
(N
, Empty
);
16751 -- The operator was folded into a literal
16753 elsif Nkind
(N2
) in N_Integer_Literal
16757 if Present
(Original_Node
(N2
))
16758 and then Nkind
(Original_Node
(N2
)) = Nkind
(N
)
16760 -- Operation was constant-folded. Whenever possible,
16761 -- recover semantic information from unfolded node.
16762 -- This was initially done for ASIS but is apparently
16763 -- needed also for e.g. compiling a-nbnbin.adb.
16765 Set_Associated_Node
(N
, Original_Node
(N2
));
16767 if Nkind
(N
) = N_Op_Concat
then
16768 Set_Is_Component_Left_Opnd
(N
,
16769 Is_Component_Left_Opnd
(Get_Associated_Node
(N
)));
16770 Set_Is_Component_Right_Opnd
(N
,
16771 Is_Component_Right_Opnd
(Get_Associated_Node
(N
)));
16776 -- Propagate the constant folding back to the template
16779 Rewrite
(N
, New_Copy
(N2
));
16780 Set_Analyzed
(N
, False);
16783 -- The operator was folded into an enumeration literal. Retain
16784 -- the entity to avoid spurious ambiguities if it is overloaded
16785 -- at the point of instantiation or inlining.
16787 elsif Nkind
(N2
) = N_Identifier
16788 and then Ekind
(Entity
(N2
)) = E_Enumeration_Literal
16790 Rewrite
(N
, New_Copy
(N2
));
16791 Set_Analyzed
(N
, False);
16795 -- Complete the operands check if node has not been constant
16798 if Nkind
(N
) in N_Op
then
16799 Save_Entity_Descendants
(N
);
16801 end Save_References_In_Operator
;
16803 -------------------------------
16804 -- Save_References_In_Pragma --
16805 -------------------------------
16807 procedure Save_References_In_Pragma
(Prag
: Node_Id
) is
16809 Do_Save
: Boolean := True;
16812 -- Do not save global references in pragmas generated from aspects
16813 -- because the pragmas will be regenerated at instantiation time.
16815 if From_Aspect_Specification
(Prag
) then
16818 -- The capture of global references within contract-related source
16819 -- pragmas associated with generic packages, subprograms or their
16820 -- respective bodies must be delayed due to timing of annotation
16821 -- analysis. Global references are still captured in routine
16822 -- Save_Global_References_In_Contract.
16824 elsif Is_Generic_Contract_Pragma
(Prag
) and then Prag
/= Templ
then
16825 if Is_Package_Contract_Annotation
(Prag
) then
16826 Context
:= Find_Related_Package_Or_Body
(Prag
);
16828 pragma Assert
(Is_Subprogram_Contract_Annotation
(Prag
));
16829 Context
:= Find_Related_Declaration_Or_Body
(Prag
);
16832 -- The use of Original_Node accounts for the case when the
16833 -- related context is generic template.
16835 if Requires_Delayed_Save
(Original_Node
(Context
)) then
16840 -- For all other cases, save all global references within the
16841 -- descendants, but skip the following semantic fields:
16842 -- Next_Pragma, Corresponding_Aspect, Next_Rep_Item.
16845 Save_Global_Descendant
16846 (Union_Id
(Pragma_Argument_Associations
(N
)));
16847 Save_Global_Descendant
(Union_Id
(Pragma_Identifier
(N
)));
16849 end Save_References_In_Pragma
;
16851 -- Start of processing for Save_References
16859 elsif Nkind
(N
) in N_Aggregate | N_Extension_Aggregate
then
16860 Save_References_In_Aggregate
(N
);
16862 -- Character literals, operator symbols
16864 elsif Nkind
(N
) in N_Character_Literal | N_Operator_Symbol
then
16865 Save_References_In_Char_Lit_Or_Op_Symbol
(N
);
16867 -- Defining identifiers
16869 elsif Nkind
(N
) in N_Entity
then
16874 elsif Nkind
(N
) = N_Identifier
then
16875 Save_References_In_Identifier
(N
);
16879 elsif Nkind
(N
) in N_Op
then
16880 Save_References_In_Operator
(N
);
16884 elsif Nkind
(N
) = N_Pragma
then
16885 Save_References_In_Pragma
(N
);
16888 Save_References_In_Descendants
(N
);
16891 -- Save all global references found within the aspect specifications
16892 -- of the related node.
16894 if Permits_Aspect_Specifications
(N
) and then Has_Aspects
(N
) then
16896 -- The capture of global references within aspects associated with
16897 -- generic packages, subprograms or their bodies must be delayed
16898 -- due to timing of annotation analysis. Global references are
16899 -- still captured in routine Save_Global_References_In_Contract.
16901 if Requires_Delayed_Save
(N
) then
16904 -- Otherwise save all global references within the aspects
16907 Save_Global_References_In_Aspects
(N
);
16910 end Save_References
;
16912 ---------------------
16913 -- Set_Global_Type --
16914 ---------------------
16916 procedure Set_Global_Type
(N
: Node_Id
; N2
: Node_Id
) is
16917 Typ
: constant Entity_Id
:= Etype
(N2
);
16920 Set_Etype
(N
, Typ
);
16922 -- If the entity of N is not the associated node, this is a
16923 -- nested generic and it has an associated node as well, whose
16924 -- type is already the full view (see below). Indicate that the
16925 -- original node has a private view.
16927 if Entity
(N
) /= N2
then
16928 if Has_Private_View
(Entity
(N
)) then
16929 Set_Has_Private_View
(N
);
16932 if Has_Secondary_Private_View
(Entity
(N
)) then
16933 Set_Has_Secondary_Private_View
(N
);
16937 -- If not a private type, deal with a secondary private view
16939 if not Is_Private_Type
(Typ
) then
16940 if (Is_Access_Type
(Typ
)
16941 and then Is_Private_Type
(Designated_Type
(Typ
)))
16942 or else (Is_Array_Type
(Typ
)
16944 Is_Private_Type
(Component_Type_For_Private_View
(Typ
)))
16946 Set_Has_Secondary_Private_View
(N
);
16949 -- If it is a derivation of a private type in a context where no
16950 -- full view is needed, nothing to do either.
16952 elsif No
(Full_View
(Typ
)) and then Typ
/= Etype
(Typ
) then
16955 -- Otherwise mark the type for flipping and use the full view when
16959 Set_Has_Private_View
(N
);
16961 if Present
(Full_View
(Typ
)) then
16962 Set_Etype
(N2
, Full_View
(Typ
));
16966 if Is_Floating_Point_Type
(Typ
)
16967 and then Has_Dimension_System
(Typ
)
16969 Copy_Dimensions
(N2
, N
);
16971 end Set_Global_Type
;
16973 -- Start of processing for Save_Global_References
16976 Gen_Scope
:= Current_Scope
;
16978 -- If the generic unit is a child unit, references to entities in the
16979 -- parent are treated as local, because they will be resolved anew in
16980 -- the context of the instance of the parent.
16982 while Is_Child_Unit
(Gen_Scope
)
16983 and then Ekind
(Scope
(Gen_Scope
)) = E_Generic_Package
16985 Gen_Scope
:= Scope
(Gen_Scope
);
16988 Save_References
(Templ
);
16989 end Save_Global_References
;
16991 ---------------------------------------
16992 -- Save_Global_References_In_Aspects --
16993 ---------------------------------------
16995 procedure Save_Global_References_In_Aspects
(N
: Node_Id
) is
17000 Asp
:= First
(Aspect_Specifications
(N
));
17001 while Present
(Asp
) loop
17002 Expr
:= Expression
(Asp
);
17004 if Present
(Expr
) then
17005 Save_Global_References
(Expr
);
17010 end Save_Global_References_In_Aspects
;
17012 ------------------------------------------
17013 -- Set_Copied_Sloc_For_Inherited_Pragma --
17014 ------------------------------------------
17016 procedure Set_Copied_Sloc_For_Inherited_Pragma
17021 Create_Instantiation_Source
(N
, E
,
17022 Inlined_Body
=> False,
17023 Inherited_Pragma
=> True,
17024 Factor
=> S_Adjustment
);
17025 end Set_Copied_Sloc_For_Inherited_Pragma
;
17027 --------------------------------------
17028 -- Set_Copied_Sloc_For_Inlined_Body --
17029 --------------------------------------
17031 procedure Set_Copied_Sloc_For_Inlined_Body
(N
: Node_Id
; E
: Entity_Id
) is
17033 Create_Instantiation_Source
(N
, E
,
17034 Inlined_Body
=> True,
17035 Inherited_Pragma
=> False,
17036 Factor
=> S_Adjustment
);
17037 end Set_Copied_Sloc_For_Inlined_Body
;
17039 ---------------------
17040 -- Set_Instance_Of --
17041 ---------------------
17043 procedure Set_Instance_Of
(A
: Entity_Id
; B
: Entity_Id
) is
17045 Generic_Renamings
.Table
(Generic_Renamings
.Last
) := (A
, B
, Assoc_Null
);
17046 Generic_Renamings_HTable
.Set
(Generic_Renamings
.Last
);
17047 Generic_Renamings
.Increment_Last
;
17048 end Set_Instance_Of
;
17050 --------------------
17051 -- Set_Next_Assoc --
17052 --------------------
17054 procedure Set_Next_Assoc
(E
: Assoc_Ptr
; Next
: Assoc_Ptr
) is
17056 Generic_Renamings
.Table
(E
).Next_In_HTable
:= Next
;
17057 end Set_Next_Assoc
;
17059 -------------------
17060 -- Start_Generic --
17061 -------------------
17063 procedure Start_Generic
is
17065 -- ??? More things could be factored out in this routine.
17066 -- Should probably be done at a later stage.
17068 Generic_Flags
.Append
(Inside_A_Generic
);
17069 Inside_A_Generic
:= True;
17071 Expander_Mode_Save_And_Set
(False);
17074 ----------------------
17075 -- Set_Instance_Env --
17076 ----------------------
17078 -- WARNING: This routine manages SPARK regions
17080 procedure Set_Instance_Env
17081 (Gen_Unit
: Entity_Id
;
17082 Act_Unit
: Entity_Id
)
17084 Saved_AE
: constant Boolean := Assertions_Enabled
;
17085 Saved_CPL
: constant Node_Id
:= Check_Policy_List
;
17086 Saved_DEC
: constant Boolean := Dynamic_Elaboration_Checks
;
17087 Saved_SM
: constant SPARK_Mode_Type
:= SPARK_Mode
;
17088 Saved_SMP
: constant Node_Id
:= SPARK_Mode_Pragma
;
17091 -- Regardless of the current mode, predefined units are analyzed in the
17092 -- most current Ada mode, and earlier version Ada checks do not apply
17093 -- to predefined units. Nothing needs to be done for non-internal units.
17094 -- These are always analyzed in the current mode.
17096 if In_Internal_Unit
(Gen_Unit
) then
17098 -- The following call resets all configuration attributes to default
17099 -- or the xxx_Config versions of the attributes when the current sem
17100 -- unit is the main unit. At the same time, internal units must also
17101 -- inherit certain configuration attributes from their context. It
17102 -- is unclear what these two sets are.
17104 Set_Config_Switches
(True, Current_Sem_Unit
= Main_Unit
);
17106 -- Reinstall relevant configuration attributes of the context
17108 Assertions_Enabled
:= Saved_AE
;
17109 Check_Policy_List
:= Saved_CPL
;
17110 Dynamic_Elaboration_Checks
:= Saved_DEC
;
17112 Install_SPARK_Mode
(Saved_SM
, Saved_SMP
);
17115 Current_Instantiated_Parent
:=
17116 (Gen_Id
=> Gen_Unit
,
17117 Act_Id
=> Act_Unit
,
17118 Next_In_HTable
=> Assoc_Null
);
17119 end Set_Instance_Env
;
17125 procedure Switch_View
(T
: Entity_Id
) is
17126 BT
: constant Entity_Id
:= Base_Type
(T
);
17127 Priv_Elmt
: Elmt_Id
:= No_Elmt
;
17128 Priv_Sub
: Entity_Id
;
17131 -- T may be private but its base type may have been exchanged through
17132 -- some other occurrence, in which case there is nothing to switch
17133 -- besides T itself. Note that a private dependent subtype of a private
17134 -- type might not have been switched even if the base type has been,
17135 -- because of the last branch of Check_Private_View (see comment there).
17137 if not Is_Private_Type
(BT
) then
17138 Prepend_Elmt
(Full_View
(T
), Exchanged_Views
);
17139 Exchange_Declarations
(T
);
17143 Priv_Elmt
:= First_Elmt
(Private_Dependents
(BT
));
17145 if Present
(Full_View
(BT
)) then
17146 Prepend_Elmt
(Full_View
(BT
), Exchanged_Views
);
17147 Exchange_Declarations
(BT
);
17150 while Present
(Priv_Elmt
) loop
17151 Priv_Sub
:= Node
(Priv_Elmt
);
17153 if Present
(Full_View
(Priv_Sub
)) then
17154 Prepend_Elmt
(Full_View
(Priv_Sub
), Exchanged_Views
);
17155 Exchange_Declarations
(Priv_Sub
);
17158 Next_Elmt
(Priv_Elmt
);
17166 function True_Parent
(N
: Node_Id
) return Node_Id
is
17168 if Nkind
(Parent
(N
)) = N_Subunit
then
17169 return Parent
(Corresponding_Stub
(Parent
(N
)));
17175 -----------------------------
17176 -- Valid_Default_Attribute --
17177 -----------------------------
17179 procedure Valid_Default_Attribute
(Nam
: Entity_Id
; Def
: Node_Id
) is
17180 Attr_Id
: constant Attribute_Id
:=
17181 Get_Attribute_Id
(Attribute_Name
(Def
));
17182 T
: constant Entity_Id
:= Entity
(Prefix
(Def
));
17183 Is_Fun
: constant Boolean := (Ekind
(Nam
) = E_Function
);
17189 if No
(T
) or else T
= Any_Id
then
17194 F
:= First_Formal
(Nam
);
17195 while Present
(F
) loop
17196 Num_F
:= Num_F
+ 1;
17201 when Attribute_Adjacent
17202 | Attribute_Ceiling
17203 | Attribute_Copy_Sign
17205 | Attribute_Fraction
17206 | Attribute_Machine
17208 | Attribute_Remainder
17209 | Attribute_Rounding
17210 | Attribute_Unbiased_Rounding
17214 and then Is_Floating_Point_Type
(T
);
17216 when Attribute_Image
17220 | Attribute_Wide_Image
17221 | Attribute_Wide_Value
17223 OK
:= Is_Fun
and then Num_F
= 1 and then Is_Scalar_Type
(T
);
17228 OK
:= Is_Fun
and then Num_F
= 2 and then Is_Scalar_Type
(T
);
17230 when Attribute_Input
=>
17231 OK
:= (Is_Fun
and then Num_F
= 1);
17233 when Attribute_Output
17234 | Attribute_Put_Image
17238 OK
:= not Is_Fun
and then Num_F
= 2;
17246 ("attribute reference has wrong profile for subprogram", Def
);
17248 end Valid_Default_Attribute
;
17250 ----------------------------------
17251 -- Validate_Formal_Type_Default --
17252 ----------------------------------
17254 procedure Validate_Formal_Type_Default
(Decl
: Node_Id
) is
17255 Default
: constant Node_Id
:=
17256 Default_Subtype_Mark
(Original_Node
(Decl
));
17257 Formal
: constant Entity_Id
:= Defining_Identifier
(Decl
);
17259 Def_Sub
: Entity_Id
; -- Default subtype mark
17260 Type_Def
: Node_Id
;
17262 procedure Check_Discriminated_Formal
;
17263 -- Check that discriminants of default for private or incomplete
17264 -- type match those of formal type.
17266 function Reference_Formal
(N
: Node_Id
) return Traverse_Result
;
17267 -- Check whether formal type definition mentions a previous formal
17268 -- type of the same generic.
17270 ----------------------
17271 -- Reference_Formal --
17272 ----------------------
17274 function Reference_Formal
(N
: Node_Id
) return Traverse_Result
is
17276 if Is_Entity_Name
(N
)
17277 and then Scope
(Entity
(N
)) = Current_Scope
17283 end Reference_Formal
;
17285 function Depends_On_Other_Formals
is
17286 new Traverse_Func
(Reference_Formal
);
17288 function Default_Subtype_Matches
17289 (Gen_T
, Def_T
: Entity_Id
) return Boolean;
17291 procedure Validate_Array_Type_Default
;
17292 -- Verify that dimension, indices, and component types of default
17293 -- are compatible with formal array type definition.
17295 procedure Validate_Derived_Type_Default
;
17296 -- Verify that ancestor and progenitor types match.
17298 ---------------------------------
17299 -- Check_Discriminated_Formal --
17300 ---------------------------------
17302 procedure Check_Discriminated_Formal
is
17303 Formal_Discr
: Entity_Id
;
17304 Actual_Discr
: Entity_Id
;
17305 Formal_Subt
: Entity_Id
;
17308 if Has_Discriminants
(Formal
) then
17309 if not Has_Discriminants
(Def_Sub
) then
17311 ("default for & must have discriminants", Default
, Formal
);
17313 elsif Is_Constrained
(Def_Sub
) then
17315 ("default for & must be unconstrained", Default
, Formal
);
17318 Formal_Discr
:= First_Discriminant
(Formal
);
17319 Actual_Discr
:= First_Discriminant
(Def_Sub
);
17320 while Formal_Discr
/= Empty
loop
17321 if Actual_Discr
= Empty
then
17323 ("discriminants on Formal do not match formal",
17327 Formal_Subt
:= Etype
(Formal_Discr
);
17329 -- Access discriminants match if designated types do
17331 if Ekind
(Base_Type
(Formal_Subt
)) = E_Anonymous_Access_Type
17332 and then (Ekind
(Base_Type
(Etype
(Actual_Discr
)))) =
17333 E_Anonymous_Access_Type
17335 Designated_Type
(Base_Type
(Formal_Subt
)) =
17336 Designated_Type
(Base_Type
(Etype
(Actual_Discr
)))
17340 elsif Base_Type
(Formal_Subt
) /=
17341 Base_Type
(Etype
(Actual_Discr
))
17344 ("types of discriminants of default must match formal",
17347 elsif not Subtypes_Statically_Match
17348 (Formal_Subt
, Etype
(Actual_Discr
))
17349 and then Ada_Version
>= Ada_95
17352 ("subtypes of discriminants of default "
17353 & "must match formal",
17357 Next_Discriminant
(Formal_Discr
);
17358 Next_Discriminant
(Actual_Discr
);
17361 if Actual_Discr
/= Empty
then
17363 ("discriminants on default do not match formal",
17368 end Check_Discriminated_Formal
;
17370 ---------------------------
17371 -- Default_Subtype_Matches --
17372 ---------------------------
17374 function Default_Subtype_Matches
17375 (Gen_T
, Def_T
: Entity_Id
) return Boolean
17378 -- Check that the base types, root types (when dealing with class
17379 -- wide types), or designated types (when dealing with anonymous
17380 -- access types) of Gen_T and Def_T are statically matching subtypes.
17382 return (Base_Type
(Gen_T
) = Base_Type
(Def_T
)
17383 and then Subtypes_Statically_Match
(Gen_T
, Def_T
))
17385 or else (Is_Class_Wide_Type
(Gen_T
)
17386 and then Is_Class_Wide_Type
(Def_T
)
17387 and then Default_Subtype_Matches
17388 (Root_Type
(Gen_T
), Root_Type
(Def_T
)))
17390 or else (Is_Anonymous_Access_Type
(Gen_T
)
17391 and then Ekind
(Def_T
) = Ekind
(Gen_T
)
17392 and then Subtypes_Statically_Match
17393 (Designated_Type
(Gen_T
), Designated_Type
(Def_T
)));
17395 end Default_Subtype_Matches
;
17397 ----------------------------------
17398 -- Validate_Array_Type_Default --
17399 ----------------------------------
17401 procedure Validate_Array_Type_Default
is
17405 if not Is_Array_Type
(Def_Sub
) then
17406 Error_Msg_NE
("default for& must be an array type ",
17410 elsif Number_Dimensions
(Def_Sub
) /= Number_Dimensions
(Formal
)
17411 or else Is_Constrained
(Def_Sub
) /=
17412 Is_Constrained
(Formal
)
17414 Error_Msg_NE
("default array type does not match&",
17419 I1
:= First_Index
(Formal
);
17420 I2
:= First_Index
(Def_Sub
);
17421 for J
in 1 .. Number_Dimensions
(Formal
) loop
17423 -- If the indexes of the actual were given by a subtype_mark,
17424 -- the index was transformed into a range attribute. Retrieve
17425 -- the original type mark for checking.
17427 if Is_Entity_Name
(Original_Node
(I2
)) then
17428 T2
:= Entity
(Original_Node
(I2
));
17433 if not Subtypes_Statically_Match
(Etype
(I1
), T2
) then
17435 ("index types of default do not match those of formal &",
17443 if not Default_Subtype_Matches
17444 (Component_Type
(Formal
), Component_Type
(Def_Sub
))
17447 ("component subtype of default does not match that of formal &",
17451 if Has_Aliased_Components
(Formal
)
17452 and then not Has_Aliased_Components
(Default
)
17455 ("default must have aliased components to match formal type &",
17458 end Validate_Array_Type_Default
;
17460 -----------------------------------
17461 -- Validate_Derived_Type_Default --
17462 -----------------------------------
17464 procedure Validate_Derived_Type_Default
is
17466 if not Is_Ancestor
(Etype
(Formal
), Def_Sub
) then
17467 Error_Msg_NE
("default must be a descendent of&",
17468 Default
, Etype
(Formal
));
17471 if Has_Interfaces
(Formal
) then
17472 if not Has_Interfaces
(Def_Sub
) then
17474 ("default must implement all interfaces of formal&",
17480 Iface_Ent
: Entity_Id
;
17483 Iface
:= First
(Abstract_Interface_List
(Formal
));
17485 while Present
(Iface
) loop
17486 Iface_Ent
:= Entity
(Iface
);
17488 if Is_Ancestor
(Iface_Ent
, Def_Sub
)
17489 or else Is_Progenitor
(Iface_Ent
, Def_Sub
)
17495 ("Default must implement interface&",
17496 Default
, Etype
(Iface
));
17504 end Validate_Derived_Type_Default
;
17506 -- Start of processing for Validate_Formal_Type_Default
17510 if not Is_Entity_Name
(Default
)
17511 or else not Is_Type
(Entity
(Default
))
17514 ("Expect type name for default of formal type", Default
);
17517 Def_Sub
:= Entity
(Default
);
17520 -- Formal derived_type declarations are transformed into full
17521 -- type declarations or Private_Type_Extensions for ease of processing.
17523 if Nkind
(Decl
) = N_Full_Type_Declaration
then
17524 Type_Def
:= Type_Definition
(Decl
);
17526 elsif Nkind
(Decl
) = N_Private_Extension_Declaration
then
17527 Type_Def
:= Subtype_Indication
(Decl
);
17530 Type_Def
:= Formal_Type_Definition
(Decl
);
17533 if Depends_On_Other_Formals
(Type_Def
) = Abandon
17534 and then Scope
(Def_Sub
) /= Current_Scope
17536 Error_Msg_N
("default of formal type that depends on "
17537 & "other formals must be a previous formal type", Default
);
17540 elsif Def_Sub
= Formal
then
17542 ("default for formal type cannot be formal itsef", Default
);
17546 case Nkind
(Type_Def
) is
17548 when N_Formal_Private_Type_Definition
=>
17549 if (Is_Abstract_Type
(Formal
)
17550 and then not Is_Abstract_Type
(Def_Sub
))
17551 or else (Is_Limited_Type
(Formal
)
17552 and then not Is_Limited_Type
(Def_Sub
))
17555 ("default for private type$ does not match",
17559 Check_Discriminated_Formal
;
17561 when N_Formal_Derived_Type_Definition
=>
17562 Check_Discriminated_Formal
;
17563 Validate_Derived_Type_Default
;
17565 when N_Formal_Incomplete_Type_Definition
=>
17566 if Is_Tagged_Type
(Formal
)
17567 and then not Is_Tagged_Type
(Def_Sub
)
17570 ("default for & must be a tagged type", Default
, Formal
);
17573 Check_Discriminated_Formal
;
17575 when N_Formal_Discrete_Type_Definition
=>
17576 if not Is_Discrete_Type
(Def_Sub
) then
17577 Error_Msg_NE
("default for& must be a discrete type",
17581 when N_Formal_Signed_Integer_Type_Definition
=>
17582 if not Is_Integer_Type
(Def_Sub
) then
17583 Error_Msg_NE
("default for& must be a discrete type",
17587 when N_Formal_Modular_Type_Definition
=>
17588 if not Is_Modular_Integer_Type
(Def_Sub
) then
17589 Error_Msg_NE
("default for& must be a modular_integer Type",
17593 when N_Formal_Floating_Point_Definition
=>
17594 if not Is_Floating_Point_Type
(Def_Sub
) then
17595 Error_Msg_NE
("default for& must be a floating_point type",
17599 when N_Formal_Ordinary_Fixed_Point_Definition
=>
17600 if not Is_Ordinary_Fixed_Point_Type
(Def_Sub
) then
17601 Error_Msg_NE
("default for& must be "
17602 & "an ordinary_fixed_point type ",
17606 when N_Formal_Decimal_Fixed_Point_Definition
=>
17607 if not Is_Decimal_Fixed_Point_Type
(Def_Sub
) then
17608 Error_Msg_NE
("default for& must be "
17609 & "an Decimal_fixed_point type ",
17613 when N_Array_Type_Definition
=>
17614 Validate_Array_Type_Default
;
17616 when N_Access_Function_Definition |
17617 N_Access_Procedure_Definition
=>
17618 if Ekind
(Def_Sub
) /= E_Access_Subprogram_Type
then
17619 Error_Msg_NE
("default for& must be an Access_To_Subprogram",
17622 Check_Subtype_Conformant
17623 (Designated_Type
(Formal
), Designated_Type
(Def_Sub
));
17625 when N_Access_To_Object_Definition
=>
17626 if not Is_Access_Object_Type
(Def_Sub
) then
17627 Error_Msg_NE
("default for& must be an Access_To_Object",
17630 elsif not Default_Subtype_Matches
17631 (Designated_Type
(Formal
), Designated_Type
(Def_Sub
))
17633 Error_Msg_NE
("designated type of defaul does not match "
17634 & "designated type of formal type",
17638 when N_Record_Definition
=> -- Formal interface type
17639 if not Is_Interface
(Def_Sub
) then
17641 ("default for formal interface type must be an interface",
17644 elsif Is_Limited_Type
(Def_Sub
) /= Is_Limited_Type
(Formal
)
17645 or else Is_Task_Interface
(Formal
) /= Is_Task_Interface
(Def_Sub
)
17646 or else Is_Protected_Interface
(Formal
) /=
17647 Is_Protected_Interface
(Def_Sub
)
17648 or else Is_Synchronized_Interface
(Formal
) /=
17649 Is_Synchronized_Interface
(Def_Sub
)
17652 ("default for interface& does not match", Def_Sub
, Formal
);
17655 when N_Derived_Type_Definition
=>
17656 Validate_Derived_Type_Default
;
17658 when N_Identifier
=> -- case of a private extension
17659 Validate_Derived_Type_Default
;
17665 raise Program_Error
;
17667 end Validate_Formal_Type_Default
;