1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
5 -- E I N F O . U T I L S --
9 -- Copyright (C) 2020-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 Einfo
.Entities
; use Einfo
.Entities
;
27 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
29 package Einfo
.Utils
is
31 -------------------------------------------
32 -- Aliases/Renamings of Renamed_Or_Alias --
33 -------------------------------------------
35 -- See the comment in einfo.ads, "Renaming and Aliasing", which is somewhat
36 -- incorrect. Each of the following calls [Set_]Renamed_Or_Alias. Alias and
37 -- Renamed_Entity are fields of nonobject Entity_Ids, and the value of the
38 -- field is Entity_Id. Alias is only for callable entities and subprogram
39 -- types. We sometimes call Set_Renamed_Entity and then expect Alias to
40 -- return the value set. Renamed_Object is a field of Entity_Ids that are
41 -- objects, and it returns an expression, because you can rename things
42 -- like "X.all(J).Y". Renamings of entries and subprograms can also be
43 -- expressions, but those use different mechanisms; the fields here are not
46 function Alias
(N
: Entity_Id
) return Entity_Id
with Inline
;
47 procedure Set_Alias
(N
: Entity_Id
; Val
: Entity_Id
) with Inline
;
48 function Renamed_Entity
(N
: Entity_Id
) return Entity_Id
with Inline
;
49 procedure Set_Renamed_Entity
(N
: Entity_Id
; Val
: Entity_Id
) with Inline
;
50 function Renamed_Object
(N
: Entity_Id
) return Node_Id
with Inline
;
51 procedure Set_Renamed_Object
(N
: Entity_Id
; Val
: Node_Id
) with Inline
;
53 function Renamed_Entity_Or_Object
(N
: Entity_Id
) return Node_Id
55 -- This getter is used when we don't know statically whether we want to
56 -- call Renamed_Entity or Renamed_Object.
58 procedure Set_Renamed_Object_Of_Possibly_Void
59 (N
: Entity_Id
; Val
: Node_Id
) with Inline
;
60 -- Set_Renamed_Object doesn't allow Void; this is used in the rare cases
61 -- where we set the field of an entity that might be Void. It might be a
62 -- good idea to get rid of calls to this.
68 -- The following type synonyms are used to tidy up the function and
69 -- procedure declarations that follow. Note that E and N have predicates
70 -- ensuring the correct kind; we use Entity_Id or Node_Id when the
71 -- predicates can't be satisfied.
74 subtype C
is Component_Alignment_Kind
;
75 subtype E
is N_Entity_Id
;
76 subtype F
is Float_Rep_Kind
;
77 subtype M
is Mechanism_Type
;
78 subtype N
is Node_Id
with Predicate
=> N
/= Empty
and then N
not in E
;
81 subtype L
is Elist_Id
;
84 -------------------------------
85 -- Classification Attributes --
86 -------------------------------
88 -- These functions provide a convenient functional notation for testing
89 -- whether an Ekind value belongs to a specified kind, for example the
90 -- function Is_Elementary_Type tests if its argument is in Elementary_Kind.
91 -- In some cases, the test is of an entity attribute (e.g. in the case of
92 -- Is_Generic_Type where the Ekind does not provide the needed
95 function Is_Access_Object_Type
(Id
: E
) return B
with Inline
;
96 function Is_Access_Type
(Id
: E
) return B
with Inline
;
97 function Is_Access_Protected_Subprogram_Type
(Id
: E
) return B
with Inline
;
98 function Is_Access_Subprogram_Type
(Id
: E
) return B
with Inline
;
99 function Is_Address_Compatible_Type
(Id
: E
) return B
with Inline
;
100 -- Check whether the type represents an address
101 function Is_Aggregate_Type
(Id
: E
) return B
with Inline
;
102 function Is_Anonymous_Access_Type
(Id
: E
) return B
with Inline
;
103 function Is_Array_Type
(Id
: E
) return B
with Inline
;
104 function Is_Assignable
(Id
: E
) return B
with Inline
;
105 function Is_Class_Wide_Type
(Id
: E
) return B
with Inline
;
106 function Is_Composite_Type
(Id
: E
) return B
with Inline
;
107 function Is_Concurrent_Body
(Id
: E
) return B
with Inline
;
108 function Is_Concurrent_Type
(Id
: E
) return B
with Inline
;
109 function Is_Decimal_Fixed_Point_Type
(Id
: E
) return B
with Inline
;
110 function Is_Digits_Type
(Id
: E
) return B
with Inline
;
111 function Is_Discrete_Or_Fixed_Point_Type
(Id
: E
) return B
with Inline
;
112 function Is_Discrete_Type
(Id
: E
) return B
with Inline
;
113 function Is_Elementary_Type
(Id
: E
) return B
with Inline
;
114 function Is_Entry
(Id
: E
) return B
with Inline
;
115 function Is_Enumeration_Type
(Id
: E
) return B
with Inline
;
116 function Is_Fixed_Point_Type
(Id
: E
) return B
with Inline
;
117 function Is_Floating_Point_Type
(Id
: E
) return B
with Inline
;
118 function Is_Formal
(Id
: E
) return B
with Inline
;
119 function Is_Formal_Object
(Id
: E
) return B
with Inline
;
120 function Is_Generic_Subprogram
(Id
: E
) return B
with Inline
;
121 function Is_Generic_Unit
(Id
: E
) return B
with Inline
;
122 function Is_Ghost_Entity
(Id
: E
) return B
with Inline
;
123 function Is_Incomplete_Or_Private_Type
(Id
: E
) return B
with Inline
;
124 function Is_Incomplete_Type
(Id
: E
) return B
with Inline
;
125 function Is_Integer_Type
(Id
: E
) return B
with Inline
;
126 function Is_Modular_Integer_Type
(Id
: E
) return B
with Inline
;
127 function Is_Named_Access_Type
(Id
: E
) return B
with Inline
;
128 function Is_Named_Number
(Id
: E
) return B
with Inline
;
129 function Is_Numeric_Type
(Id
: E
) return B
with Inline
;
130 function Is_Object
(Id
: E
) return B
with Inline
;
131 function Is_Ordinary_Fixed_Point_Type
(Id
: E
) return B
with Inline
;
132 function Is_Overloadable
(Id
: E
) return B
with Inline
;
133 function Is_Private_Type
(Id
: E
) return B
with Inline
;
134 function Is_Protected_Type
(Id
: E
) return B
with Inline
;
135 function Is_Real_Type
(Id
: E
) return B
with Inline
;
136 function Is_Record_Type
(Id
: E
) return B
with Inline
;
137 function Is_Scalar_Type
(Id
: E
) return B
with Inline
;
138 function Is_Signed_Integer_Type
(Id
: E
) return B
with Inline
;
139 function Is_Subprogram
(Id
: E
) return B
with Inline
;
140 function Is_Subprogram_Or_Entry
(Id
: E
) return B
with Inline
;
141 function Is_Subprogram_Or_Generic_Subprogram
(Id
: E
) return B
with Inline
;
142 function Is_Task_Type
(Id
: E
) return B
with Inline
;
143 function Is_Type
(Id
: E
) return B
with Inline
;
145 -------------------------------------
146 -- Synthesized Attribute Functions --
147 -------------------------------------
149 -- The functions in this section synthesize attributes from the tree,
150 -- so they do not correspond to defined fields in the entity itself.
152 function Address_Clause
(Id
: E
) return Node_Id
with Inline
;
153 function Aft_Value
(Id
: E
) return U
;
154 function Alignment_Clause
(Id
: E
) return Node_Id
with Inline
;
155 function Base_Type
(Id
: E
) return E
with Inline
;
156 function Declaration_Node
(Id
: E
) return Node_Id
;
157 function Designated_Type
(Id
: E
) return E
;
158 function Entry_Index_Type
(Id
: E
) return E
;
159 function First_Component
(Id
: E
) return Entity_Id
;
160 function First_Component_Or_Discriminant
(Id
: E
) return Entity_Id
;
161 function First_Formal
(Id
: E
) return Entity_Id
;
162 function First_Formal_With_Extras
(Id
: E
) return Entity_Id
;
165 (N
: Entity_Id
) return F
with Inline
, Pre
=>
168 procedure Set_Float_Rep
169 (Ignore_N
: Entity_Id
; Ignore_Val
: F
) with Inline
, Pre
=>
170 Ignore_N
in E_Void_Id
173 function Has_Attach_Handler
(Id
: E
) return B
;
174 function Has_DIC
(Id
: E
) return B
;
175 function Has_Entries
(Id
: E
) return B
;
176 function Has_Foreign_Convention
(Id
: E
) return B
with Inline
;
177 function Has_Interrupt_Handler
(Id
: E
) return B
;
178 function Has_Invariants
(Id
: E
) return B
;
179 function Has_Limited_View
(Id
: E
) return B
;
180 function Has_Non_Limited_View
(Id
: E
) return B
with Inline
;
181 function Has_Non_Null_Abstract_State
(Id
: E
) return B
;
182 function Has_Non_Null_Visible_Refinement
(Id
: E
) return B
;
183 function Has_Null_Abstract_State
(Id
: E
) return B
;
184 function Has_Null_Visible_Refinement
(Id
: E
) return B
;
185 function Implementation_Base_Type
(Id
: E
) return E
;
186 function Is_Base_Type
(Id
: E
) return B
with Inline
;
187 -- Note that Is_Base_Type returns True for nontypes
188 function Is_Boolean_Type
(Id
: E
) return B
with Inline
;
189 function Is_Constant_Object
(Id
: E
) return B
with Inline
;
190 function Is_Controlled
(Id
: E
) return B
with Inline
;
191 function Is_Discriminal
(Id
: E
) return B
with Inline
;
192 function Is_Dynamic_Scope
(Id
: E
) return B
;
193 function Is_Elaboration_Target
(Id
: E
) return B
;
194 function Is_External_State
(Id
: E
) return B
;
195 function Is_Finalizer
(Id
: E
) return B
with Inline
;
196 function Is_Full_Access
(Id
: E
) return B
with Inline
;
197 function Is_Null_State
(Id
: E
) return B
;
198 function Is_Package_Or_Generic_Package
(Id
: E
) return B
with Inline
;
199 function Is_Packed_Array
(Id
: E
) return B
with Inline
;
200 function Is_Prival
(Id
: E
) return B
with Inline
;
201 function Is_Protected_Component
(Id
: E
) return B
with Inline
;
202 function Is_Protected_Interface
(Id
: E
) return B
;
203 function Is_Protected_Record_Type
(Id
: E
) return B
with Inline
;
204 function Is_Relaxed_Initialization_State
(Id
: E
) return B
;
205 function Is_Standard_Character_Type
(Id
: E
) return B
;
206 function Is_Standard_String_Type
(Id
: E
) return B
;
207 function Is_String_Type
(Id
: E
) return B
with Inline
;
208 function Is_Synchronized_Interface
(Id
: E
) return B
;
209 function Is_Synchronized_State
(Id
: E
) return B
;
210 function Is_Task_Interface
(Id
: E
) return B
;
211 function Is_Task_Record_Type
(Id
: E
) return B
with Inline
;
212 function Is_Wrapper_Package
(Id
: E
) return B
with Inline
;
213 function Last_Formal
(Id
: E
) return Entity_Id
;
214 function Machine_Emax_Value
(Id
: E
) return U
;
215 function Machine_Emin_Value
(Id
: E
) return U
;
216 function Machine_Mantissa_Value
(Id
: E
) return U
;
217 function Machine_Radix_Value
(Id
: E
) return U
;
218 function Model_Emin_Value
(Id
: E
) return U
;
219 function Model_Epsilon_Value
(Id
: E
) return R
;
220 function Model_Mantissa_Value
(Id
: E
) return U
;
221 function Model_Small_Value
(Id
: E
) return R
;
222 function Next_Component
(Id
: E
) return Entity_Id
;
223 function Next_Component_Or_Discriminant
(Id
: E
) return Entity_Id
;
224 function Next_Discriminant
(Id
: E
) return Entity_Id
;
225 function Next_Formal
(Id
: E
) return Entity_Id
;
226 function Next_Formal_With_Extras
(Id
: E
) return Entity_Id
;
227 function Next_Index
(Id
: N
) return Node_Id
;
228 function Next_Literal
(Id
: E
) return Entity_Id
;
229 function Next_Stored_Discriminant
(Id
: E
) return Entity_Id
;
230 function Number_Dimensions
(Id
: E
) return Pos
;
231 function Number_Entries
(Id
: E
) return Nat
;
232 function Number_Formals
(Id
: E
) return Nat
;
233 function Object_Size_Clause
(Id
: E
) return Node_Id
;
234 function Parameter_Mode
(Id
: E
) return Formal_Kind
;
235 function Partial_Refinement_Constituents
(Id
: E
) return L
;
236 function Primitive_Operations
(Id
: E
) return L
;
237 function Root_Type
(Id
: E
) return E
;
238 function Safe_Emax_Value
(Id
: E
) return U
;
239 function Safe_First_Value
(Id
: E
) return R
;
240 function Safe_Last_Value
(Id
: E
) return R
;
241 function Size_Clause
(Id
: E
) return Node_Id
with Inline
;
242 function Stream_Size_Clause
(Id
: E
) return N
with Inline
;
243 function Type_High_Bound
(Id
: E
) return N
with Inline
;
244 function Type_Low_Bound
(Id
: E
) return N
with Inline
;
245 function Underlying_Type
(Id
: E
) return Entity_Id
;
247 function Scope_Depth
(Id
: Scope_Kind_Id
) return U
with Inline
;
248 function Scope_Depth_Set
(Id
: Scope_Kind_Id
) return B
with Inline
;
250 function Scope_Depth_Default_0
(Id
: Scope_Kind_Id
) return U
;
251 -- In rare cases, the Scope_Depth_Value (queried by Scope_Depth) is
252 -- not correctly set before querying it; this may be used instead of
253 -- Scope_Depth in such cases. It returns Uint_0 if the Scope_Depth_Value
254 -- has not been set. See documentation in Einfo.
256 ------------------------------------------
257 -- Type Representation Attribute Fields --
258 ------------------------------------------
260 function Known_Alignment
(E
: Entity_Id
) return B
with Inline
;
261 procedure Reinit_Alignment
(Id
: E
) with Inline
;
262 procedure Copy_Alignment
(To
, From
: E
);
264 function Known_Component_Bit_Offset
(E
: Entity_Id
) return B
with Inline
;
265 function Known_Static_Component_Bit_Offset
(E
: Entity_Id
) return B
268 function Known_Component_Size
(E
: Entity_Id
) return B
with Inline
;
269 function Known_Static_Component_Size
(E
: Entity_Id
) return B
with Inline
;
271 function Known_Esize
(E
: Entity_Id
) return B
with Inline
;
272 function Known_Static_Esize
(E
: Entity_Id
) return B
with Inline
;
273 procedure Reinit_Esize
(Id
: E
) with Inline
;
274 procedure Copy_Esize
(To
, From
: E
);
276 function Known_Normalized_First_Bit
(E
: Entity_Id
) return B
with Inline
;
277 function Known_Static_Normalized_First_Bit
(E
: Entity_Id
) return B
280 function Known_Normalized_Position
(E
: Entity_Id
) return B
with Inline
;
281 function Known_Static_Normalized_Position
(E
: Entity_Id
) return B
284 function Known_RM_Size
(E
: Entity_Id
) return B
with Inline
;
285 function Known_Static_RM_Size
(E
: Entity_Id
) return B
with Inline
;
286 procedure Reinit_RM_Size
(Id
: E
) with Inline
;
287 procedure Copy_RM_Size
(To
, From
: E
);
289 -- NOTE: "known" here does not mean "known at compile time". It means that
290 -- the compiler has computed the value of the field (either by default, or
291 -- by noting some representation clauses), and the field has not been
294 -- We document the Esize functions here; the others above are analogous:
296 -- Known_Esize: True if Set_Esize has been called without a subsequent
299 -- Known_Static_Esize: True if Known_Esize and the Esize is known at
300 -- compile time. (We're not using "static" in the Ada RM sense here. We
301 -- are using it to mean "known at compile time".)
303 -- Reinit_Esize: Set the Esize field to its initial unknown state.
305 -- Copy_Esize: Copies the Esize from From to To; Known_Esize (From) may
306 -- be False, in which case Known_Esize (To) becomes False.
308 -- Esize: This is the normal automatically-generated getter for Esize,
309 -- declared elsewhere. Returns No_Uint if not Known_Esize.
311 -- Set_Esize: This is the normal automatically-generated setter for
312 -- Esize. After a call to this, Known_Esize is True. It is an error
313 -- to call this with a No_Uint value.
315 -- Normally, we call Set_Esize first, and then query Esize (and similarly
316 -- for other fields). However in some cases, we need to check Known_Esize
317 -- before calling Esize, because the code is written in such a way that we
318 -- don't know whether Set_Esize has already been called.
320 -- In two cases, Known_Static_Esize and Known_Static_RM_Size, there is one
321 -- more consideration, which is that we always return False for generic
322 -- types. Within a template, the size can look Known_Static, because of the
323 -- fake size values we put in template types, but they are not really
324 -- Known_Static and anyone testing if they are Known_Static within the
325 -- template should get False as a result to prevent incorrect assumptions.
327 ---------------------------------------------------------
328 -- Procedures for setting multiple of the above fields --
329 ---------------------------------------------------------
331 procedure Reinit_Component_Location
(Id
: E
);
332 -- Initializes all fields describing the location of a component
333 -- (Normalized_Position, Component_Bit_Offset, Normalized_First_Bit,
334 -- Esize) to all be Unknown.
336 procedure Init_Size
(Id
: E
; V
: Int
);
337 -- Initialize both the Esize and RM_Size fields of E to V
339 procedure Reinit_Size_Align
(Id
: E
);
340 -- This procedure initializes both size fields and the alignment
341 -- field to all be Unknown.
343 procedure Reinit_Object_Size_Align
(Id
: E
);
344 -- Same as Reinit_Size_Align except RM_Size field (which is only for types)
347 ---------------------------------------------------
348 -- Access to Subprograms in Subprograms_For_Type --
349 ---------------------------------------------------
351 -- Now that we have variable-sized nodes, it might be possible to replace
352 -- the following with regular fields, and get rid of the flags used to mark
353 -- these kinds of subprograms.
355 function Is_Partial_DIC_Procedure
(Id
: E
) return B
;
357 function DIC_Procedure
(Id
: E
) return Entity_Id
;
358 function Partial_DIC_Procedure
(Id
: E
) return Entity_Id
;
359 function Invariant_Procedure
(Id
: E
) return Entity_Id
;
360 function Partial_Invariant_Procedure
(Id
: E
) return Entity_Id
;
361 function Predicate_Function
(Id
: E
) return Entity_Id
;
363 procedure Set_DIC_Procedure
(Id
: E
; V
: E
);
364 procedure Set_Partial_DIC_Procedure
(Id
: E
; V
: E
);
365 procedure Set_Invariant_Procedure
(Id
: E
; V
: E
);
366 procedure Set_Partial_Invariant_Procedure
(Id
: E
; V
: E
);
367 procedure Set_Predicate_Function
(Id
: E
; V
: E
);
373 -- Next_xxx (obj) is equivalent to obj := Next_xxx (obj)
375 procedure Next_Component
(N
: in out Node_Id
) with Inline
;
376 procedure Next_Component_Or_Discriminant
(N
: in out Node_Id
) with Inline
;
377 procedure Next_Discriminant
(N
: in out Node_Id
) with Inline
;
378 procedure Next_Formal
(N
: in out Node_Id
) with Inline
;
379 procedure Next_Formal_With_Extras
(N
: in out Node_Id
) with Inline
;
380 procedure Next_Index
(N
: in out Node_Id
) with Inline
;
381 procedure Next_Inlined_Subprogram
(N
: in out Node_Id
) with Inline
;
382 procedure Next_Literal
(N
: in out Node_Id
) with Inline
;
383 procedure Next_Stored_Discriminant
(N
: in out Node_Id
) with Inline
;
385 ---------------------------
386 -- Testing Warning Flags --
387 ---------------------------
389 -- These routines are to be used rather than testing flags Warnings_Off,
390 -- Has_Pragma_Unmodified, Has_Pragma_Unreferenced. They deal with setting
391 -- the flags Warnings_Off_Used[_Unmodified|Unreferenced] for later access.
393 function Has_Warnings_Off
(E
: Entity_Id
) return Boolean;
394 -- If Warnings_Off is set on E, then returns True and also sets the flag
395 -- Warnings_Off_Used on E. If Warnings_Off is not set on E, returns False
396 -- and has no side effect.
398 function Has_Unmodified
(E
: Entity_Id
) return Boolean;
399 -- If flag Has_Pragma_Unmodified is set on E, returns True with no side
400 -- effects. Otherwise if Warnings_Off is set on E, returns True and also
401 -- sets the flag Warnings_Off_Used_Unmodified on E. If neither of the flags
402 -- Warnings_Off nor Has_Pragma_Unmodified is set, returns False with no
405 function Has_Unreferenced
(E
: Entity_Id
) return Boolean;
406 -- If flag Has_Pragma_Unreferenced is set on E, returns True with no side
407 -- effects. Otherwise if Warnings_Off is set on E, returns True and also
408 -- sets the flag Warnings_Off_Used_Unreferenced on E. If neither of the
409 -- flags Warnings_Off nor Has_Pragma_Unreferenced is set, returns False
410 -- with no side effects.
412 ----------------------------------------------
413 -- Subprograms for Accessing Rep Item Chain --
414 ----------------------------------------------
416 -- The First_Rep_Item field of every entity points to a linked list (linked
417 -- through Next_Rep_Item) of representation pragmas, attribute definition
418 -- clauses, representation clauses, and aspect specifications that apply to
419 -- the item. Note that in the case of types, it is assumed that any such
420 -- rep items for a base type also apply to all subtypes. This is achieved
421 -- by having the chain for subtypes link onto the chain for the base type,
422 -- so that new entries for the subtype are added at the start of the chain.
424 -- Note: aspect specification nodes are linked only when evaluation of the
425 -- expression is deferred to the freeze point. For further details see
426 -- Sem_Ch13.Analyze_Aspect_Specifications.
428 function Get_Attribute_Definition_Clause
430 Id
: Attribute_Id
) return Node_Id
;
431 -- Searches the Rep_Item chain for a given entity E, for an instance of an
432 -- attribute definition clause with the given attribute Id. If found, the
433 -- value returned is the N_Attribute_Definition_Clause node, otherwise
434 -- Empty is returned.
436 -- WARNING: There is a matching C declaration of this subprogram in fe.h
438 function Get_Pragma
(E
: Entity_Id
; Id
: Pragma_Id
) return Node_Id
;
439 -- Searches the Rep_Item chain of entity E, for an instance of a pragma
440 -- with the given pragma Id. If found, the value returned is the N_Pragma
441 -- node, otherwise Empty is returned. The following contract pragmas that
442 -- appear in N_Contract nodes are also handled by this routine:
448 -- Constant_After_Elaboration
467 -- Subprogram_Variant
471 function Get_Class_Wide_Pragma
473 Id
: Pragma_Id
) return Node_Id
;
474 -- Examine Rep_Item chain to locate a classwide pre- or postcondition of a
475 -- primitive operation. Returns Empty if not present.
477 function Get_Record_Representation_Clause
(E
: Entity_Id
) return Node_Id
;
478 -- Searches the Rep_Item chain for a given entity E, for a record
479 -- representation clause, and if found, returns it. Returns Empty
480 -- if no such clause is found.
482 function Present_In_Rep_Item
(E
: Entity_Id
; N
: Node_Id
) return Boolean;
483 -- Return True if N is present in the Rep_Item chain for a given entity E
485 procedure Record_Rep_Item
(E
: Entity_Id
; N
: Node_Id
);
486 -- N is the node for a representation pragma, representation clause, an
487 -- attribute definition clause, or an aspect specification that applies to
488 -- entity E. This procedure links the node N onto the Rep_Item chain for
489 -- entity E. Note that it is an error to call this procedure with E being
490 -- overloadable, and N being a pragma that applies to multiple overloadable
491 -- entities (Convention, Interface, Inline, Inline_Always, Import, Export,
492 -- External). This is not allowed even in the case where the entity is not
493 -- overloaded, since we can't rely on it being present in the overloaded
494 -- case, it is not useful to have it present in the non-overloaded case.
496 -------------------------------
497 -- Miscellaneous Subprograms --
498 -------------------------------
500 procedure Append_Entity
(Id
: Entity_Id
; Scop
: Entity_Id
);
501 -- Add an entity to the list of entities declared in the scope Scop
503 function Get_Full_View
(T
: Entity_Id
) return Entity_Id
;
504 -- If T is an incomplete type and the full declaration has been seen, or
505 -- is the name of a class_wide type whose root is incomplete, return the
506 -- corresponding full declaration, else return T itself.
508 function Is_Entity_Name
(N
: Node_Id
) return Boolean with Inline
;
509 -- Test if the node N is the name of an entity (i.e. is an identifier,
510 -- expanded name, or an attribute reference that returns an entity).
512 -- WARNING: There is a matching C declaration of this subprogram in fe.h
514 procedure Link_Entities
(First
, Second
: Entity_Id
);
515 -- Link entities First and Second in one entity chain.
517 -- NOTE: No updates are done to the First_Entity and Last_Entity fields
520 procedure Remove_Entity
(Id
: Entity_Id
);
521 -- Remove entity Id from the entity chain of its scope
523 function Subtype_Kind
(K
: Entity_Kind
) return Entity_Kind
;
524 -- Given an entity_kind K this function returns the entity_kind
525 -- corresponding to subtype kind of the type represented by K. For
526 -- example if K is E_Signed_Integer_Type then E_Signed_Integer_Subtype
527 -- is returned. If K is already a subtype kind it itself is returned. An
528 -- internal error is generated if no such correspondence exists for K.
530 procedure Unlink_Next_Entity
(Id
: Entity_Id
);
531 -- Unchain entity Id's forward link within the entity chain of its scope
533 function Is_Volatile
(Id
: E
) return B
;
534 procedure Set_Is_Volatile
(Id
: E
; V
: B
:= True);
535 -- Call [Set_]Is_Volatile_Type/Is_Volatile_Object as appropriate for the
539 (N
: Entity_Id
) return Convention_Id
renames Basic_Convention
;
540 procedure Set_Convention
(E
: Entity_Id
; Val
: Convention_Id
);
541 -- Same as Set_Basic_Convention, but with an extra check for access types.
542 -- In particular, if E is an access-to-subprogram type, and Val is a
543 -- foreign convention, then we set Can_Use_Internal_Rep to False on E.
544 -- Also, if the Etype of E is set and is an anonymous access type with
545 -- no convention set, this anonymous type inherits the convention of E.
547 ----------------------------------
548 -- Debugging Output Subprograms --
549 ----------------------------------
551 procedure Write_Entity_Info
(Id
: Entity_Id
; Prefix
: String);
552 -- A debugging procedure to write out information about an entity