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