Add assember CFI directives to millicode division and remainder routines.
[official-gcc.git] / gcc / ada / einfo-utils.ads
blob896d8f0de199f379b10779773642d12869dd4b96
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E I N F O . U T I L S --
6 -- --
7 -- S p e c --
8 -- --
9 -- Copyright (C) 2020-2023, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with 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
44 -- used.
46 function Alias (N : Entity_Id) return Entity_Id;
47 procedure Set_Alias (N : Entity_Id; Val : Entity_Id);
48 function Renamed_Entity (N : Entity_Id) return Entity_Id;
49 procedure Set_Renamed_Entity (N : Entity_Id; Val : Entity_Id);
50 function Renamed_Object (N : Entity_Id) return Node_Id;
51 procedure Set_Renamed_Object (N : Entity_Id; Val : Node_Id);
53 function Renamed_Entity_Or_Object (N : Entity_Id) return Node_Id;
54 -- This getter is used when we don't know statically whether we want to
55 -- call Renamed_Entity or Renamed_Object.
57 procedure Set_Renamed_Object_Of_Possibly_Void
58 (N : Entity_Id; Val : Node_Id);
59 -- Set_Renamed_Object doesn't allow Void; this is used in the rare cases
60 -- where we set the field of an entity that might be Void. It might be a
61 -- good idea to get rid of calls to this.
63 pragma Inline (Alias);
64 pragma Inline (Set_Alias);
65 pragma Inline (Renamed_Entity);
66 pragma Inline (Set_Renamed_Entity);
67 pragma Inline (Renamed_Object);
68 pragma Inline (Set_Renamed_Object);
69 pragma Inline (Renamed_Entity_Or_Object);
70 pragma Inline (Set_Renamed_Object_Of_Possibly_Void);
72 -------------------
73 -- Type Synonyms --
74 -------------------
76 -- The following type synonyms are used to tidy up the function and
77 -- procedure declarations that follow. Note that E and N have predicates
78 -- ensuring the correct kind; we use Entity_Id or Node_Id when the
79 -- predicates can't be satisfied.
81 subtype B is Boolean;
82 subtype C is Component_Alignment_Kind;
83 subtype E is N_Entity_Id;
84 subtype F is Float_Rep_Kind;
85 subtype M is Mechanism_Type;
86 subtype N is Node_Id with Predicate => N /= Empty and then N not in E;
87 subtype U is Uint;
88 subtype R is Ureal;
89 subtype L is Elist_Id;
90 subtype S is List_Id;
92 -------------------------------
93 -- Classification Attributes --
94 -------------------------------
96 -- These functions provide a convenient functional notation for testing
97 -- whether an Ekind value belongs to a specified kind, for example the
98 -- function Is_Elementary_Type tests if its argument is in Elementary_Kind.
99 -- In some cases, the test is of an entity attribute (e.g. in the case of
100 -- Is_Generic_Type where the Ekind does not provide the needed
101 -- information).
103 function Is_Access_Object_Type (Id : E) return B;
104 function Is_Access_Type (Id : E) return B;
105 function Is_Access_Protected_Subprogram_Type (Id : E) return B;
106 function Is_Access_Subprogram_Type (Id : E) return B;
107 function Is_Aggregate_Type (Id : E) return B;
108 function Is_Anonymous_Access_Type (Id : E) return B;
109 function Is_Array_Type (Id : E) return B;
110 function Is_Assignable (Id : E) return B;
111 function Is_Class_Wide_Type (Id : E) return B;
112 function Is_Composite_Type (Id : E) return B;
113 function Is_Concurrent_Body (Id : E) return B;
114 function Is_Concurrent_Type (Id : E) return B;
115 function Is_Decimal_Fixed_Point_Type (Id : E) return B;
116 function Is_Digits_Type (Id : E) return B;
117 function Is_Discrete_Or_Fixed_Point_Type (Id : E) return B;
118 function Is_Discrete_Type (Id : E) return B;
119 function Is_Elementary_Type (Id : E) return B;
120 function Is_Entry (Id : E) return B;
121 function Is_Enumeration_Type (Id : E) return B;
122 function Is_Fixed_Point_Type (Id : E) return B;
123 function Is_Floating_Point_Type (Id : E) return B;
124 function Is_Formal (Id : E) return B;
125 function Is_Formal_Object (Id : E) return B;
126 function Is_Generic_Subprogram (Id : E) return B;
127 function Is_Generic_Unit (Id : E) return B;
128 function Is_Ghost_Entity (Id : E) return B;
129 function Is_Incomplete_Or_Private_Type (Id : E) return B;
130 function Is_Incomplete_Type (Id : E) return B;
131 function Is_Integer_Type (Id : E) return B;
132 function Is_Modular_Integer_Type (Id : E) return B;
133 function Is_Named_Access_Type (Id : E) return B;
134 function Is_Named_Number (Id : E) return B;
135 function Is_Numeric_Type (Id : E) return B;
136 function Is_Object (Id : E) return B;
137 function Is_Ordinary_Fixed_Point_Type (Id : E) return B;
138 function Is_Overloadable (Id : E) return B;
139 function Is_Private_Type (Id : E) return B;
140 function Is_Protected_Type (Id : E) return B;
141 function Is_Real_Type (Id : E) return B;
142 function Is_Record_Type (Id : E) return B;
143 function Is_Scalar_Type (Id : E) return B;
144 function Is_Signed_Integer_Type (Id : E) return B;
145 function Is_Subprogram (Id : E) return B;
146 function Is_Subprogram_Or_Entry (Id : E) return B;
147 function Is_Subprogram_Or_Generic_Subprogram (Id : E) return B;
148 function Is_Task_Type (Id : E) return B;
149 function Is_Type (Id : E) return B;
151 pragma Inline (Is_Access_Object_Type);
152 pragma Inline (Is_Access_Type);
153 pragma Inline (Is_Access_Protected_Subprogram_Type);
154 pragma Inline (Is_Access_Subprogram_Type);
155 pragma Inline (Is_Aggregate_Type);
156 pragma Inline (Is_Anonymous_Access_Type);
157 pragma Inline (Is_Array_Type);
158 pragma Inline (Is_Assignable);
159 pragma Inline (Is_Class_Wide_Type);
160 pragma Inline (Is_Composite_Type);
161 pragma Inline (Is_Concurrent_Body);
162 pragma Inline (Is_Concurrent_Type);
163 pragma Inline (Is_Decimal_Fixed_Point_Type);
164 pragma Inline (Is_Digits_Type);
165 pragma Inline (Is_Discrete_Type);
166 pragma Inline (Is_Elementary_Type);
167 pragma Inline (Is_Entry);
168 pragma Inline (Is_Enumeration_Type);
169 pragma Inline (Is_Fixed_Point_Type);
170 pragma Inline (Is_Floating_Point_Type);
171 pragma Inline (Is_Formal);
172 pragma Inline (Is_Formal_Object);
173 pragma Inline (Is_Generic_Subprogram);
174 pragma Inline (Is_Generic_Unit);
175 pragma Inline (Is_Ghost_Entity);
176 pragma Inline (Is_Incomplete_Or_Private_Type);
177 pragma Inline (Is_Incomplete_Type);
178 pragma Inline (Is_Integer_Type);
179 pragma Inline (Is_Modular_Integer_Type);
180 pragma Inline (Is_Named_Access_Type);
181 pragma Inline (Is_Named_Number);
182 pragma Inline (Is_Numeric_Type);
183 pragma Inline (Is_Object);
184 pragma Inline (Is_Ordinary_Fixed_Point_Type);
185 pragma Inline (Is_Overloadable);
186 pragma Inline (Is_Private_Type);
187 pragma Inline (Is_Protected_Type);
188 pragma Inline (Is_Real_Type);
189 pragma Inline (Is_Record_Type);
190 pragma Inline (Is_Scalar_Type);
191 pragma Inline (Is_Signed_Integer_Type);
192 pragma Inline (Is_Subprogram);
193 pragma Inline (Is_Subprogram_Or_Entry);
194 pragma Inline (Is_Subprogram_Or_Generic_Subprogram);
195 pragma Inline (Is_Task_Type);
196 pragma Inline (Is_Type);
198 -------------------------------------
199 -- Synthesized Attribute Functions --
200 -------------------------------------
202 -- The functions in this section synthesize attributes from the tree,
203 -- so they do not correspond to defined fields in the entity itself.
205 function Address_Clause (Id : E) return Node_Id;
206 function Aft_Value (Id : E) return U;
207 function Alignment_Clause (Id : E) return Node_Id;
208 function Base_Type (Id : E) return E;
209 function Declaration_Node (Id : E) return Node_Id;
210 function Designated_Type (Id : E) return E;
211 function Entry_Index_Type (Id : E) return E;
212 function First_Component (Id : E) return Entity_Id;
213 function First_Component_Or_Discriminant (Id : E) return Entity_Id;
214 function First_Formal (Id : E) return Entity_Id;
215 function First_Formal_With_Extras (Id : E) return Entity_Id;
217 function Float_Rep
218 (N : Entity_Id) return F with Inline, Pre =>
219 N in E_Void_Id
220 | Float_Kind_Id;
221 procedure Set_Float_Rep
222 (Ignore_N : Entity_Id; Ignore_Val : F) with Inline, Pre =>
223 Ignore_N in E_Void_Id
224 | Float_Kind_Id;
226 function Has_Attach_Handler (Id : E) return B;
227 function Has_DIC (Id : E) return B;
228 function Has_Entries (Id : E) return B;
229 function Has_Foreign_Convention (Id : E) return B;
230 function Has_Interrupt_Handler (Id : E) return B;
231 function Has_Invariants (Id : E) return B;
232 function Has_Limited_View (Id : E) return B;
233 function Has_Non_Limited_View (Id : E) return B;
234 function Has_Non_Null_Abstract_State (Id : E) return B;
235 function Has_Non_Null_Visible_Refinement (Id : E) return B;
236 function Has_Null_Abstract_State (Id : E) return B;
237 function Has_Null_Visible_Refinement (Id : E) return B;
238 function Implementation_Base_Type (Id : E) return E;
239 function Is_Base_Type (Id : E) return B;
240 -- Note that Is_Base_Type returns True for nontypes
241 function Is_Boolean_Type (Id : E) return B;
242 function Is_Constant_Object (Id : E) return B;
243 function Is_Controlled (Id : E) return B;
244 function Is_Discriminal (Id : E) return B;
245 function Is_Dynamic_Scope (Id : E) return B;
246 function Is_Elaboration_Target (Id : E) return B;
247 function Is_External_State (Id : E) return B;
248 function Is_Finalizer (Id : E) return B;
249 function Is_Full_Access (Id : E) return B;
250 function Is_Null_State (Id : E) return B;
251 function Is_Package_Or_Generic_Package (Id : E) return B;
252 function Is_Packed_Array (Id : E) return B;
253 function Is_Prival (Id : E) return B;
254 function Is_Protected_Component (Id : E) return B;
255 function Is_Protected_Interface (Id : E) return B;
256 function Is_Protected_Record_Type (Id : E) return B;
257 function Is_Relaxed_Initialization_State (Id : E) return B;
258 function Is_Standard_Character_Type (Id : E) return B;
259 function Is_Standard_String_Type (Id : E) return B;
260 function Is_String_Type (Id : E) return B;
261 function Is_Synchronized_Interface (Id : E) return B;
262 function Is_Synchronized_State (Id : E) return B;
263 function Is_Task_Interface (Id : E) return B;
264 function Is_Task_Record_Type (Id : E) return B;
265 function Is_Wrapper_Package (Id : E) return B;
266 function Last_Formal (Id : E) return Entity_Id;
267 function Machine_Emax_Value (Id : E) return U;
268 function Machine_Emin_Value (Id : E) return U;
269 function Machine_Mantissa_Value (Id : E) return U;
270 function Machine_Radix_Value (Id : E) return U;
271 function Model_Emin_Value (Id : E) return U;
272 function Model_Epsilon_Value (Id : E) return R;
273 function Model_Mantissa_Value (Id : E) return U;
274 function Model_Small_Value (Id : E) return R;
275 function Next_Component (Id : E) return Entity_Id;
276 function Next_Component_Or_Discriminant (Id : E) return Entity_Id;
277 function Next_Discriminant (Id : E) return Entity_Id;
278 function Next_Formal (Id : E) return Entity_Id;
279 function Next_Formal_With_Extras (Id : E) return Entity_Id;
280 function Next_Index (Id : N) return Node_Id;
281 function Next_Literal (Id : E) return Entity_Id;
282 function Next_Stored_Discriminant (Id : E) return Entity_Id;
283 function Number_Dimensions (Id : E) return Pos;
284 function Number_Entries (Id : E) return Nat;
285 function Number_Formals (Id : E) return Pos;
286 function Object_Size_Clause (Id : E) return Node_Id;
287 function Parameter_Mode (Id : E) return Formal_Kind;
288 function Partial_Refinement_Constituents (Id : E) return L;
289 function Primitive_Operations (Id : E) return L;
290 function Root_Type (Id : E) return E;
291 function Safe_Emax_Value (Id : E) return U;
292 function Safe_First_Value (Id : E) return R;
293 function Safe_Last_Value (Id : E) return R;
294 function Size_Clause (Id : E) return Node_Id;
295 function Stream_Size_Clause (Id : E) return N;
296 function Type_High_Bound (Id : E) return N;
297 function Type_Low_Bound (Id : E) return N;
298 function Underlying_Type (Id : E) return Entity_Id;
300 function Scope_Depth (Id : E) return U;
301 function Scope_Depth_Set (Id : E) return B;
303 function Scope_Depth_Default_0 (Id : E) return U;
304 -- In rare cases, the Scope_Depth_Value (queried by Scope_Depth) is
305 -- not correctly set before querying it; this may be used instead of
306 -- Scope_Depth in such cases. It returns Uint_0 if the Scope_Depth_Value
307 -- has not been set. See documentation in Einfo.
309 pragma Inline (Address_Clause);
310 pragma Inline (Alignment_Clause);
311 pragma Inline (Base_Type);
312 pragma Inline (Has_Foreign_Convention);
313 pragma Inline (Has_Non_Limited_View);
314 pragma Inline (Is_Base_Type);
315 pragma Inline (Is_Boolean_Type);
316 pragma Inline (Is_Constant_Object);
317 pragma Inline (Is_Controlled);
318 pragma Inline (Is_Discriminal);
319 pragma Inline (Is_Finalizer);
320 pragma Inline (Is_Full_Access);
321 pragma Inline (Is_Null_State);
322 pragma Inline (Is_Package_Or_Generic_Package);
323 pragma Inline (Is_Packed_Array);
324 pragma Inline (Is_Prival);
325 pragma Inline (Is_Protected_Component);
326 pragma Inline (Is_Protected_Record_Type);
327 pragma Inline (Is_String_Type);
328 pragma Inline (Is_Task_Record_Type);
329 pragma Inline (Is_Wrapper_Package);
330 pragma Inline (Scope_Depth);
331 pragma Inline (Scope_Depth_Set);
332 pragma Inline (Size_Clause);
333 pragma Inline (Stream_Size_Clause);
334 pragma Inline (Type_High_Bound);
335 pragma Inline (Type_Low_Bound);
337 ------------------------------------------
338 -- Type Representation Attribute Fields --
339 ------------------------------------------
341 function Known_Alignment (E : Entity_Id) return B with Inline;
342 procedure Reinit_Alignment (Id : E) with Inline;
343 procedure Copy_Alignment (To, From : E);
345 function Known_Component_Bit_Offset (E : Entity_Id) return B with Inline;
346 function Known_Static_Component_Bit_Offset (E : Entity_Id) return B
347 with Inline;
349 function Known_Component_Size (E : Entity_Id) return B with Inline;
350 function Known_Static_Component_Size (E : Entity_Id) return B with Inline;
352 function Known_Esize (E : Entity_Id) return B with Inline;
353 function Known_Static_Esize (E : Entity_Id) return B with Inline;
354 procedure Reinit_Esize (Id : E) with Inline;
355 procedure Copy_Esize (To, From : E);
357 function Known_Normalized_First_Bit (E : Entity_Id) return B with Inline;
358 function Known_Static_Normalized_First_Bit (E : Entity_Id) return B
359 with Inline;
361 function Known_Normalized_Position (E : Entity_Id) return B with Inline;
362 function Known_Static_Normalized_Position (E : Entity_Id) return B
363 with Inline;
365 function Known_RM_Size (E : Entity_Id) return B with Inline;
366 function Known_Static_RM_Size (E : Entity_Id) return B with Inline;
367 procedure Reinit_RM_Size (Id : E) with Inline;
368 procedure Copy_RM_Size (To, From : E);
370 -- NOTE: "known" here does not mean "known at compile time". It means that
371 -- the compiler has computed the value of the field (either by default, or
372 -- by noting some representation clauses), and the field has not been
373 -- reinitialized.
375 -- We document the Esize functions here; the others above are analogous:
377 -- Known_Esize: True if Set_Esize has been called without a subsequent
378 -- Reinit_Esize.
380 -- Known_Static_Esize: True if Known_Esize and the Esize is known at
381 -- compile time. (We're not using "static" in the Ada RM sense here. We
382 -- are using it to mean "known at compile time".)
384 -- Reinit_Esize: Set the Esize field to its initial unknown state.
386 -- Copy_Esize: Copies the Esize from From to To; Known_Esize (From) may
387 -- be False, in which case Known_Esize (To) becomes False.
389 -- Esize: This is the normal automatically-generated getter for Esize,
390 -- declared elsewhere. Returns No_Uint if not Known_Esize.
392 -- Set_Esize: This is the normal automatically-generated setter for
393 -- Esize. After a call to this, Known_Esize is True. It is an error
394 -- to call this with a No_Uint value.
396 -- Normally, we call Set_Esize first, and then query Esize (and similarly
397 -- for other fields). However in some cases, we need to check Known_Esize
398 -- before calling Esize, because the code is written in such a way that we
399 -- don't know whether Set_Esize has already been called.
401 -- In two cases, Known_Static_Esize and Known_Static_RM_Size, there is one
402 -- more consideration, which is that we always return False for generic
403 -- types. Within a template, the size can look Known_Static, because of the
404 -- fake size values we put in template types, but they are not really
405 -- Known_Static and anyone testing if they are Known_Static within the
406 -- template should get False as a result to prevent incorrect assumptions.
408 ---------------------------------------------------------
409 -- Procedures for setting multiple of the above fields --
410 ---------------------------------------------------------
412 procedure Reinit_Component_Location (Id : E);
413 -- Initializes all fields describing the location of a component
414 -- (Normalized_Position, Component_Bit_Offset, Normalized_First_Bit,
415 -- Esize) to all be Unknown.
417 procedure Init_Size (Id : E; V : Int);
418 -- Initialize both the Esize and RM_Size fields of E to V
420 procedure Reinit_Size_Align (Id : E);
421 -- This procedure initializes both size fields and the alignment
422 -- field to all be Unknown.
424 procedure Reinit_Object_Size_Align (Id : E);
425 -- Same as Reinit_Size_Align except RM_Size field (which is only for types)
426 -- is unaffected.
428 ---------------------------------------------------
429 -- Access to Subprograms in Subprograms_For_Type --
430 ---------------------------------------------------
432 -- Now that we have variable-sized nodes, it might be possible to replace
433 -- the following with regular fields, and get rid of the flags used to mark
434 -- these kinds of subprograms.
436 function Is_Partial_DIC_Procedure (Id : E) return B;
438 function DIC_Procedure (Id : E) return Entity_Id;
439 function Partial_DIC_Procedure (Id : E) return Entity_Id;
440 function Invariant_Procedure (Id : E) return Entity_Id;
441 function Partial_Invariant_Procedure (Id : E) return Entity_Id;
442 function Predicate_Function (Id : E) return Entity_Id;
444 procedure Set_DIC_Procedure (Id : E; V : E);
445 procedure Set_Partial_DIC_Procedure (Id : E; V : E);
446 procedure Set_Invariant_Procedure (Id : E; V : E);
447 procedure Set_Partial_Invariant_Procedure (Id : E; V : E);
448 procedure Set_Predicate_Function (Id : E; V : E);
450 ---------------
451 -- Iterators --
452 ---------------
454 -- The call to Next_xxx (obj) is equivalent to obj := Next_xxx (obj)
455 -- We define the set of Proc_Next_xxx routines simply for the purposes
456 -- of inlining them without necessarily inlining the function.
458 procedure Proc_Next_Component (N : in out Node_Id);
459 procedure Proc_Next_Component_Or_Discriminant (N : in out Node_Id);
460 procedure Proc_Next_Discriminant (N : in out Node_Id);
461 procedure Proc_Next_Formal (N : in out Node_Id);
462 procedure Proc_Next_Formal_With_Extras (N : in out Node_Id);
463 procedure Proc_Next_Index (N : in out Node_Id);
464 procedure Proc_Next_Inlined_Subprogram (N : in out Node_Id);
465 procedure Proc_Next_Literal (N : in out Node_Id);
466 procedure Proc_Next_Stored_Discriminant (N : in out Node_Id);
468 pragma Inline (Proc_Next_Component);
469 pragma Inline (Proc_Next_Component_Or_Discriminant);
470 pragma Inline (Proc_Next_Discriminant);
471 pragma Inline (Proc_Next_Formal);
472 pragma Inline (Proc_Next_Formal_With_Extras);
473 pragma Inline (Proc_Next_Index);
474 pragma Inline (Proc_Next_Inlined_Subprogram);
475 pragma Inline (Proc_Next_Literal);
476 pragma Inline (Proc_Next_Stored_Discriminant);
478 procedure Next_Component (N : in out Node_Id)
479 renames Proc_Next_Component;
481 procedure Next_Component_Or_Discriminant (N : in out Node_Id)
482 renames Proc_Next_Component_Or_Discriminant;
484 procedure Next_Discriminant (N : in out Node_Id)
485 renames Proc_Next_Discriminant;
487 procedure Next_Formal (N : in out Node_Id)
488 renames Proc_Next_Formal;
490 procedure Next_Formal_With_Extras (N : in out Node_Id)
491 renames Proc_Next_Formal_With_Extras;
493 procedure Next_Index (N : in out Node_Id)
494 renames Proc_Next_Index;
496 procedure Next_Inlined_Subprogram (N : in out Node_Id)
497 renames Proc_Next_Inlined_Subprogram;
499 procedure Next_Literal (N : in out Node_Id)
500 renames Proc_Next_Literal;
502 procedure Next_Stored_Discriminant (N : in out Node_Id)
503 renames Proc_Next_Stored_Discriminant;
505 ---------------------------
506 -- Testing Warning Flags --
507 ---------------------------
509 -- These routines are to be used rather than testing flags Warnings_Off,
510 -- Has_Pragma_Unmodified, Has_Pragma_Unreferenced. They deal with setting
511 -- the flags Warnings_Off_Used[_Unmodified|Unreferenced] for later access.
513 function Has_Warnings_Off (E : Entity_Id) return Boolean;
514 -- If Warnings_Off is set on E, then returns True and also sets the flag
515 -- Warnings_Off_Used on E. If Warnings_Off is not set on E, returns False
516 -- and has no side effect.
518 function Has_Unmodified (E : Entity_Id) return Boolean;
519 -- If flag Has_Pragma_Unmodified is set on E, returns True with no side
520 -- effects. Otherwise if Warnings_Off is set on E, returns True and also
521 -- sets the flag Warnings_Off_Used_Unmodified on E. If neither of the flags
522 -- Warnings_Off nor Has_Pragma_Unmodified is set, returns False with no
523 -- side effects.
525 function Has_Unreferenced (E : Entity_Id) return Boolean;
526 -- If flag Has_Pragma_Unreferenced is set on E, returns True with no side
527 -- effects. Otherwise if Warnings_Off is set on E, returns True and also
528 -- sets the flag Warnings_Off_Used_Unreferenced on E. If neither of the
529 -- flags Warnings_Off nor Has_Pragma_Unreferenced is set, returns False
530 -- with no side effects.
532 ----------------------------------------------
533 -- Subprograms for Accessing Rep Item Chain --
534 ----------------------------------------------
536 -- The First_Rep_Item field of every entity points to a linked list (linked
537 -- through Next_Rep_Item) of representation pragmas, attribute definition
538 -- clauses, representation clauses, and aspect specifications that apply to
539 -- the item. Note that in the case of types, it is assumed that any such
540 -- rep items for a base type also apply to all subtypes. This is achieved
541 -- by having the chain for subtypes link onto the chain for the base type,
542 -- so that new entries for the subtype are added at the start of the chain.
544 -- Note: aspect specification nodes are linked only when evaluation of the
545 -- expression is deferred to the freeze point. For further details see
546 -- Sem_Ch13.Analyze_Aspect_Specifications.
548 function Get_Attribute_Definition_Clause
549 (E : Entity_Id;
550 Id : Attribute_Id) return Node_Id;
551 -- Searches the Rep_Item chain for a given entity E, for an instance of an
552 -- attribute definition clause with the given attribute Id. If found, the
553 -- value returned is the N_Attribute_Definition_Clause node, otherwise
554 -- Empty is returned.
556 -- WARNING: There is a matching C declaration of this subprogram in fe.h
558 function Get_Pragma (E : Entity_Id; Id : Pragma_Id) return Node_Id;
559 -- Searches the Rep_Item chain of entity E, for an instance of a pragma
560 -- with the given pragma Id. If found, the value returned is the N_Pragma
561 -- node, otherwise Empty is returned. The following contract pragmas that
562 -- appear in N_Contract nodes are also handled by this routine:
563 -- Abstract_State
564 -- Async_Readers
565 -- Async_Writers
566 -- Attach_Handler
567 -- Constant_After_Elaboration
568 -- Contract_Cases
569 -- Depends
570 -- Effective_Reads
571 -- Effective_Writes
572 -- Global
573 -- Initial_Condition
574 -- Initializes
575 -- Interrupt_Handler
576 -- No_Caching
577 -- Part_Of
578 -- Precondition
579 -- Postcondition
580 -- Refined_Depends
581 -- Refined_Global
582 -- Refined_Post
583 -- Refined_State
584 -- Subprogram_Variant
585 -- Test_Case
586 -- Volatile_Function
588 function Get_Class_Wide_Pragma
589 (E : Entity_Id;
590 Id : Pragma_Id) return Node_Id;
591 -- Examine Rep_Item chain to locate a classwide pre- or postcondition of a
592 -- primitive operation. Returns Empty if not present.
594 function Get_Record_Representation_Clause (E : Entity_Id) return Node_Id;
595 -- Searches the Rep_Item chain for a given entity E, for a record
596 -- representation clause, and if found, returns it. Returns Empty
597 -- if no such clause is found.
599 function Present_In_Rep_Item (E : Entity_Id; N : Node_Id) return Boolean;
600 -- Return True if N is present in the Rep_Item chain for a given entity E
602 procedure Record_Rep_Item (E : Entity_Id; N : Node_Id);
603 -- N is the node for a representation pragma, representation clause, an
604 -- attribute definition clause, or an aspect specification that applies to
605 -- entity E. This procedure links the node N onto the Rep_Item chain for
606 -- entity E. Note that it is an error to call this procedure with E being
607 -- overloadable, and N being a pragma that applies to multiple overloadable
608 -- entities (Convention, Interface, Inline, Inline_Always, Import, Export,
609 -- External). This is not allowed even in the case where the entity is not
610 -- overloaded, since we can't rely on it being present in the overloaded
611 -- case, it is not useful to have it present in the non-overloaded case.
613 -------------------------------
614 -- Miscellaneous Subprograms --
615 -------------------------------
617 procedure Append_Entity (Id : Entity_Id; Scop : Entity_Id);
618 -- Add an entity to the list of entities declared in the scope Scop
620 function Get_Full_View (T : Entity_Id) return Entity_Id;
621 -- If T is an incomplete type and the full declaration has been seen, or
622 -- is the name of a class_wide type whose root is incomplete, return the
623 -- corresponding full declaration, else return T itself.
625 function Is_Entity_Name (N : Node_Id) return Boolean;
626 -- Test if the node N is the name of an entity (i.e. is an identifier,
627 -- expanded name, or an attribute reference that returns an entity).
629 -- WARNING: There is a matching C declaration of this subprogram in fe.h
631 procedure Link_Entities (First, Second : Entity_Id);
632 -- Link entities First and Second in one entity chain.
634 -- NOTE: No updates are done to the First_Entity and Last_Entity fields
635 -- of the scope.
637 procedure Remove_Entity (Id : Entity_Id);
638 -- Remove entity Id from the entity chain of its scope
640 function Subtype_Kind (K : Entity_Kind) return Entity_Kind;
641 -- Given an entity_kind K this function returns the entity_kind
642 -- corresponding to subtype kind of the type represented by K. For
643 -- example if K is E_Signed_Integer_Type then E_Signed_Integer_Subtype
644 -- is returned. If K is already a subtype kind it itself is returned. An
645 -- internal error is generated if no such correspondence exists for K.
647 procedure Unlink_Next_Entity (Id : Entity_Id);
648 -- Unchain entity Id's forward link within the entity chain of its scope
650 function Is_Volatile (Id : E) return B;
651 procedure Set_Is_Volatile (Id : E; V : B := True);
652 -- Call [Set_]Is_Volatile_Type/Is_Volatile_Object as appropriate for the
653 -- Ekind of Id.
655 function Convention
656 (N : Entity_Id) return Convention_Id renames Basic_Convention;
657 procedure Set_Convention (E : Entity_Id; Val : Convention_Id);
658 -- Same as Set_Basic_Convention, but with an extra check for access types.
659 -- In particular, if E is an access-to-subprogram type, and Val is a
660 -- foreign convention, then we set Can_Use_Internal_Rep to False on E.
661 -- Also, if the Etype of E is set and is an anonymous access type with
662 -- no convention set, this anonymous type inherits the convention of E.
664 pragma Inline (Is_Entity_Name);
666 ----------------------------------
667 -- Debugging Output Subprograms --
668 ----------------------------------
670 procedure Write_Entity_Info (Id : Entity_Id; Prefix : String);
671 -- A debugging procedure to write out information about an entity
673 end Einfo.Utils;