1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                              S E M _ A U X                               --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2019, 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-- As a special exception,  if other files  instantiate  generics from this --
22-- unit, or you link  this unit with other files  to produce an executable, --
23-- this  unit  does not  by itself cause  the resulting  executable  to  be --
24-- covered  by the  GNU  General  Public  License.  This exception does not --
25-- however invalidate  any other reasons why  the executable file  might be --
26-- covered by the  GNU Public License.                                      --
27--                                                                          --
28-- GNAT was originally developed  by the GNAT team at  New York University. --
29-- Extensive contributions were provided by Ada Core Technologies Inc.      --
30--                                                                          --
31------------------------------------------------------------------------------
32
33--  Package containing utility procedures used throughout the compiler,
34--  and also by ASIS so dependencies are limited to ASIS included packages.
35
36--  Historical note. Many of the routines here were originally in Einfo, but
37--  Einfo is supposed to be a relatively low level package dealing with the
38--  content of entities in the tree, so this package is used for routines that
39--  require more than minimal semantic knowledge.
40
41with Alloc;
42with Namet; use Namet;
43with Table;
44with Types; use Types;
45with Sinfo; use Sinfo;
46
47package Sem_Aux is
48
49   --------------------------------
50   -- Obsolescent Warnings Table --
51   --------------------------------
52
53   --  This table records entities for which a pragma Obsolescent with a
54   --  message argument has been processed.
55
56   type OWT_Record is record
57      Ent : Entity_Id;
58      --  The entity to which the pragma applies
59
60      Msg : String_Id;
61      --  The string containing the message
62   end record;
63
64   package Obsolescent_Warnings is new Table.Table (
65     Table_Component_Type => OWT_Record,
66     Table_Index_Type     => Int,
67     Table_Low_Bound      => 0,
68     Table_Initial        => Alloc.Obsolescent_Warnings_Initial,
69     Table_Increment      => Alloc.Obsolescent_Warnings_Increment,
70     Table_Name           => "Obsolescent_Warnings");
71
72   procedure Initialize;
73   --  Called at the start of compilation of each new main source file to
74   --  initialize the allocation of the Obsolescent_Warnings table. Note that
75   --  Initialize must not be called if Tree_Read is used.
76
77   procedure Tree_Read;
78   --  Initializes Obsolescent_Warnings table from current tree file using the
79   --  relevant Table.Tree_Read routine.
80
81   procedure Tree_Write;
82   --  Writes out Obsolescent_Warnings table to current tree file using the
83   --  relevant Table.Tree_Write routine.
84
85   -----------------
86   -- Subprograms --
87   -----------------
88
89   function Ancestor_Subtype (Typ : Entity_Id) return Entity_Id;
90   --  The argument Id is a type or subtype entity. If the argument is a
91   --  subtype then it returns the subtype or type from which the subtype was
92   --  obtained, otherwise it returns Empty.
93
94   function Available_View (Ent : Entity_Id) return Entity_Id;
95   --  Ent denotes an abstract state or a type that may come from a limited
96   --  with clause. Return the non-limited view of Ent if there is one or Ent
97   --  if this is not the case.
98
99   function Constant_Value (Ent : Entity_Id) return Node_Id;
100   --  Ent is a variable, constant, named integer, or named real entity. This
101   --  call obtains the initialization expression for the entity. Will return
102   --  Empty for a deferred constant whose full view is not available or
103   --  in some other cases of internal entities, which cannot be treated as
104   --  constants from the point of view of constant folding. Empty is also
105   --  returned for variables with no initialization expression.
106
107   function Corresponding_Unsigned_Type (Typ : Entity_Id) return Entity_Id;
108   --  Typ is a signed integer subtype. This routine returns the standard
109   --  unsigned type with the same Esize as the implementation base type of
110   --  Typ, e.g. Long_Integer => Long_Unsigned.
111
112   function Enclosing_Dynamic_Scope (Ent : Entity_Id) return Entity_Id;
113   --  For any entity, Ent, returns the closest dynamic scope in which the
114   --  entity is declared or Standard_Standard for library-level entities.
115
116   function First_Discriminant (Typ : Entity_Id) return Entity_Id;
117   --  Typ is a type with discriminants. The discriminants are the first
118   --  entities declared in the type, so normally this is equivalent to
119   --  First_Entity. The exception arises for tagged types, where the tag
120   --  itself is prepended to the front of the entity chain, so the
121   --  First_Discriminant function steps past the tag if it is present.
122   --  The caller is responsible for checking that the type has discriminants.
123   --  When called on a private type with unknown discriminants, the function
124   --  always returns Empty.
125
126   function First_Stored_Discriminant (Typ : Entity_Id) return Entity_Id;
127   --  Typ is a type with discriminants. Gives the first discriminant stored
128   --  in an object of this type. In many cases, these are the same as the
129   --  normal visible discriminants for the type, but in the case of renamed
130   --  discriminants, this is not always the case.
131   --
132   --  For tagged types, and untagged types which are root types or derived
133   --  types but which do not rename discriminants in their root type, the
134   --  stored discriminants are the same as the actual discriminants of the
135   --  type, and hence this function is the same as First_Discriminant.
136   --
137   --  For derived untagged types that rename discriminants in the root type
138   --  this is the first of the discriminants that occur in the root type. To
139   --  be precise, in this case stored discriminants are entities attached to
140   --  the entity chain of the derived type which are a copy of the
141   --  discriminants of the root type. Furthermore their Is_Completely_Hidden
142   --  flag is set since although they are actually stored in the object, they
143   --  are not in the set of discriminants that is visible in the type.
144   --
145   --  For derived untagged types, the set of stored discriminants are the real
146   --  discriminants from Gigi's standpoint, i.e. those that will be stored in
147   --  actual objects of the type.
148
149   function First_Subtype (Typ : Entity_Id) return Entity_Id;
150   --  Applies to all types and subtypes. For types, yields the first subtype
151   --  of the type. For subtypes, yields the first subtype of the base type of
152   --  the subtype.
153
154   function First_Tag_Component (Typ : Entity_Id) return Entity_Id;
155   --  Typ must be a tagged record type. This function returns the Entity for
156   --  the first _Tag field in the record type.
157
158   function Get_Binary_Nkind (Op : Entity_Id) return Node_Kind;
159   --  Op must be an entity with an Ekind of E_Operator. This function returns
160   --  the Nkind value that would be used to construct a binary operator node
161   --  referencing this entity. It is an error to call this function if Ekind
162   --  (Op) /= E_Operator.
163
164   function Get_Called_Entity (Call : Node_Id) return Entity_Id;
165   --  Obtain the entity of the entry, operator, or subprogram being invoked
166   --  by call Call.
167
168   function Get_Low_Bound (E : Entity_Id) return Node_Id;
169   --  For an index subtype or string literal subtype, returns its low bound
170
171   function Get_Unary_Nkind (Op : Entity_Id) return Node_Kind;
172   --  Op must be an entity with an Ekind of E_Operator. This function returns
173   --  the Nkind value that would be used to construct a unary operator node
174   --  referencing this entity. It is an error to call this function if Ekind
175   --  (Op) /= E_Operator.
176
177   function Get_Rep_Item
178     (E             : Entity_Id;
179      Nam           : Name_Id;
180      Check_Parents : Boolean := True) return Node_Id;
181   --  Searches the Rep_Item chain for a given entity E, for an instance of a
182   --  rep item (pragma, attribute definition clause, or aspect specification)
183   --  whose name matches the given name Nam. If Check_Parents is False then it
184   --  only returns rep item that has been directly specified for E (and not
185   --  inherited from its parents, if any). If one is found, it is returned,
186   --  otherwise Empty is returned. A special case is that when Nam is
187   --  Name_Priority, the call will also find Interrupt_Priority.
188
189   function Get_Rep_Item
190     (E             : Entity_Id;
191      Nam1          : Name_Id;
192      Nam2          : Name_Id;
193      Check_Parents : Boolean := True) return Node_Id;
194   --  Searches the Rep_Item chain for a given entity E, for an instance of a
195   --  rep item (pragma, attribute definition clause, or aspect specification)
196   --  whose name matches one of the given names Nam1 or Nam2. If Check_Parents
197   --  is False then it only returns rep item that has been directly specified
198   --  for E (and not inherited from its parents, if any). If one is found, it
199   --  is returned, otherwise Empty is returned. A special case is that when
200   --  one of the given names is Name_Priority, the call will also find
201   --  Interrupt_Priority.
202
203   function Get_Rep_Pragma
204     (E             : Entity_Id;
205      Nam           : Name_Id;
206      Check_Parents : Boolean := True) return Node_Id;
207   --  Searches the Rep_Item chain for a given entity E, for an instance of a
208   --  representation pragma whose name matches the given name Nam. If
209   --  Check_Parents is False then it only returns representation pragma that
210   --  has been directly specified for E (and not inherited from its parents,
211   --  if any). If one is found and if it is the first rep item in the list
212   --  that matches Nam, it is returned, otherwise Empty is returned. A special
213   --  case is that when Nam is Name_Priority, the call will also find
214   --  Interrupt_Priority.
215
216   function Get_Rep_Pragma
217     (E             : Entity_Id;
218      Nam1          : Name_Id;
219      Nam2          : Name_Id;
220      Check_Parents : Boolean := True) return Node_Id;
221   --  Searches the Rep_Item chain for a given entity E, for an instance of a
222   --  representation pragma whose name matches one of the given names Nam1 or
223   --  Nam2. If Check_Parents is False then it only returns representation
224   --  pragma that has been directly specified for E (and not inherited from
225   --  its parents, if any). If one is found and if it is the first rep item in
226   --  the list that matches one of the given names, it is returned, otherwise
227   --  Empty is returned. A special case is that when one of the given names is
228   --  Name_Priority, the call will also find Interrupt_Priority.
229
230   function Has_Rep_Item
231     (E             : Entity_Id;
232      Nam           : Name_Id;
233      Check_Parents : Boolean := True) return Boolean;
234   --  Searches the Rep_Item chain for the given entity E, for an instance of a
235   --  rep item (pragma, attribute definition clause, or aspect specification)
236   --  with the given name Nam. If Check_Parents is False then it only checks
237   --  for a rep item that has been directly specified for E (and not inherited
238   --  from its parents, if any). If found then True is returned, otherwise
239   --  False indicates that no matching entry was found.
240
241   function Has_Rep_Item
242     (E             : Entity_Id;
243      Nam1          : Name_Id;
244      Nam2          : Name_Id;
245      Check_Parents : Boolean := True) return Boolean;
246   --  Searches the Rep_Item chain for the given entity E, for an instance of a
247   --  rep item (pragma, attribute definition clause, or aspect specification)
248   --  with the given names Nam1 or Nam2. If Check_Parents is False then it
249   --  only checks for a rep item that has been directly specified for E (and
250   --  not inherited from its parents, if any). If found then True is returned,
251   --  otherwise False indicates that no matching entry was found.
252
253   function Has_Rep_Item (E : Entity_Id; N : Node_Id) return Boolean;
254   --  Determine whether the Rep_Item chain of arbitrary entity E contains item
255   --  N. N must denote a valid rep item.
256
257   function Has_Rep_Pragma
258     (E             : Entity_Id;
259      Nam           : Name_Id;
260      Check_Parents : Boolean := True) return Boolean;
261   --  Searches the Rep_Item chain for the given entity E, for an instance of a
262   --  representation pragma with the given name Nam. If Check_Parents is False
263   --  then it only checks for a representation pragma that has been directly
264   --  specified for E (and not inherited from its parents, if any). If found
265   --  and if it is the first rep item in the list that matches Nam then True
266   --  is returned, otherwise False indicates that no matching entry was found.
267
268   function Has_Rep_Pragma
269     (E             : Entity_Id;
270      Nam1          : Name_Id;
271      Nam2          : Name_Id;
272      Check_Parents : Boolean := True) return Boolean;
273   --  Searches the Rep_Item chain for the given entity E, for an instance of a
274   --  representation pragma with the given names Nam1 or Nam2. If
275   --  Check_Parents is False then it only checks for a rep item that has been
276   --  directly specified for E (and not inherited from its parents, if any).
277   --  If found and if it is the first rep item in the list that matches one of
278   --  the given names then True is returned, otherwise False indicates that no
279   --  matching entry was found.
280
281   function Has_External_Tag_Rep_Clause (T : Entity_Id) return Boolean;
282   --  Defined in tagged types. Set if an External_Tag rep. clause has been
283   --  given for this type. Use to avoid the generation of the default
284   --  External_Tag.
285   --
286   --  Note: we used to use an entity flag for this purpose, but that was wrong
287   --  because it was not propagated from the private view to the full view. We
288   --  could have added that propagation, but it would have been an annoying
289   --  irregularity compared to other representation aspects, and the cost of
290   --  looking up the aspect when needed is small.
291
292   function Has_Unconstrained_Elements (T : Entity_Id) return Boolean;
293   --  True if T has discriminants and is unconstrained, or is an array type
294   --  whose element type Has_Unconstrained_Elements.
295
296   function Has_Variant_Part (Typ : Entity_Id) return Boolean;
297   --  Return True if the first subtype of Typ is a discriminated record type
298   --  which has a variant part. False otherwise.
299
300   function In_Generic_Body (Id : Entity_Id) return Boolean;
301   --  Determine whether entity Id appears inside a generic body
302
303   function Initialization_Suppressed (Typ : Entity_Id) return Boolean;
304   pragma Inline (Initialization_Suppressed);
305   --  Returns True if initialization should be suppressed for the given type
306   --  or subtype. This is true if Suppress_Initialization is set either for
307   --  the subtype itself, or for the corresponding base type.
308
309   function Is_Body (N : Node_Id) return Boolean;
310   --  Determine whether an arbitrary node denotes a body
311
312   function Is_By_Copy_Type (Ent : Entity_Id) return Boolean;
313   --  Ent is any entity. Returns True if Ent is a type entity where the type
314   --  is required to be passed by copy, as defined in (RM 6.2(3)).
315
316   function Is_By_Reference_Type (Ent : Entity_Id) return Boolean;
317   --  Ent is any entity. Returns True if Ent is a type entity where the type
318   --  is required to be passed by reference, as defined in (RM 6.2(4-9)).
319
320   function Is_Definite_Subtype (T : Entity_Id) return Boolean;
321   --  T is a type entity. Returns True if T is a definite subtype.
322   --  Indefinite subtypes are unconstrained arrays, unconstrained
323   --  discriminated types without defaulted discriminants, class-wide types,
324   --  and types with unknown discriminants. Definite subtypes are all others
325   --  (elementary, constrained composites (including the case of records
326   --  without discriminants), and types with defaulted discriminants).
327
328   function Is_Derived_Type (Ent : Entity_Id) return Boolean;
329   --  Determines if the given entity Ent is a derived type. Result is always
330   --  false if argument is not a type.
331
332   function Is_Generic_Formal (E : Entity_Id) return Boolean;
333   --  Determine whether E is a generic formal parameter. In particular this is
334   --  used to set the visibility of generic formals of a generic package
335   --  declared with a box or with partial parameterization.
336
337   function Is_Immutably_Limited_Type (Ent : Entity_Id) return Boolean;
338   --  Implements definition in Ada 2012 RM-7.5 (8.1/3). This differs from the
339   --  following predicate in that an untagged record with immutably limited
340   --  components is NOT by itself immutably limited. This matters, e.g. when
341   --  checking the legality of an access to the current instance.
342
343   function Is_Limited_View (Ent : Entity_Id) return Boolean;
344   --  Ent is any entity. True for a type that is "inherently" limited (i.e.
345   --  cannot become nonlimited). From the Ada 2005 RM-7.5(8.1/2), "a type with
346   --  a part that is of a task, protected, or explicitly limited record type".
347   --  These are the types that are defined as return-by-reference types in Ada
348   --  95 (see RM95-6.5(11-16)). In Ada 2005, these are the types that require
349   --  build-in-place for function calls. Note that build-in-place is allowed
350   --  for other types, too. This is also used for identifying pure procedures
351   --  whose calls should not be eliminated (RM 10.2.1(18/2)).
352
353   function Is_Limited_Type (Ent : Entity_Id) return Boolean;
354   --  Ent is any entity. Returns true if Ent is a limited type (limited
355   --  private type, limited interface type, task type, protected type,
356   --  composite containing a limited component, or a subtype of any of
357   --  these types). This older routine overlaps with the previous one, this
358   --  should be cleaned up???
359
360   function Nearest_Ancestor (Typ : Entity_Id) return Entity_Id;
361   --  Given a subtype Typ, this function finds out the nearest ancestor from
362   --  which constraints and predicates are inherited. There is no simple link
363   --  for doing this, consider:
364   --
365   --     subtype R is Integer range 1 .. 10;
366   --     type T is new R;
367   --
368   --  In this case the nearest ancestor is R, but the Etype of T'Base will
369   --  point to R'Base, so we have to go rummaging in the declarations to get
370   --  this information. It is used for making sure we freeze this before we
371   --  freeze Typ, and also for retrieving inherited predicate information.
372   --  For the case of base types or first subtypes, there is no useful entity
373   --  to return, so Empty is returned.
374   --
375   --  Note: this is similar to Ancestor_Subtype except that it also deals
376   --  with the case of derived types.
377
378   function Nearest_Dynamic_Scope (Ent : Entity_Id) return Entity_Id;
379   --  This is similar to Enclosing_Dynamic_Scope except that if Ent is itself
380   --  a dynamic scope, then it is returned. Otherwise the result is the same
381   --  as that returned by Enclosing_Dynamic_Scope.
382
383   function Next_Tag_Component (Tag : Entity_Id) return Entity_Id;
384   --  Tag must be an entity representing a _Tag field of a tagged record.
385   --  The result returned is the next _Tag field in this record, or Empty
386   --  if this is the last such field.
387
388   function Number_Components (Typ : Entity_Id) return Nat;
389   --  Typ is a record type, yields number of components (including
390   --  discriminants) in type.
391
392   function Number_Discriminants (Typ : Entity_Id) return Pos;
393   --  Typ is a type with discriminants, yields number of discriminants in type
394
395   function Object_Type_Has_Constrained_Partial_View
396     (Typ  : Entity_Id;
397      Scop : Entity_Id) return Boolean;
398   --  Return True if type of object has attribute Has_Constrained_Partial_View
399   --  set to True; in addition, within a generic body, return True if subtype
400   --  of the object is a descendant of an untagged generic formal private or
401   --  derived type, and the subtype is not an unconstrained array subtype
402   --  (RM 3.3(23.10/3)).
403
404   function Package_Body (E : Entity_Id) return Node_Id;
405   --  Given an entity for a package (spec or body), return the corresponding
406   --  package body if any, or else Empty.
407
408   function Package_Spec (E : Entity_Id) return Node_Id;
409   --  Given an entity for a package spec, return the corresponding package
410   --  spec if any, or else Empty.
411
412   function Package_Specification (E : Entity_Id) return Node_Id;
413   --  Given an entity for a package, return the corresponding package
414   --  specification.
415
416   function Subprogram_Body (E : Entity_Id) return Node_Id;
417   --  Given an entity for a subprogram (spec or body), return the
418   --  corresponding subprogram body if any, or else Empty.
419
420   function Subprogram_Body_Entity (E : Entity_Id) return Entity_Id;
421   --  Given an entity for a subprogram (spec or body), return the entity
422   --  corresponding to the subprogram body, which may be the same as E or
423   --  Empty if no body is available.
424
425   function Subprogram_Spec (E : Entity_Id) return Node_Id;
426   --  Given an entity for a subprogram spec, return the corresponding
427   --  subprogram spec if any, or else Empty.
428
429   function Subprogram_Specification (E : Entity_Id) return Node_Id;
430   --  Given an entity for a subprogram, return the corresponding subprogram
431   --  specification. If the entity is an inherited subprogram without
432   --  specification itself, return the specification of the inherited
433   --  subprogram.
434
435   function Ultimate_Alias (Prim : Entity_Id) return Entity_Id;
436   pragma Inline (Ultimate_Alias);
437   --  Return the last entity in the chain of aliased entities of Prim. If Prim
438   --  has no alias return Prim.
439
440   function Unit_Declaration_Node (Unit_Id : Entity_Id) return Node_Id;
441   --  Unit_Id is the simple name of a program unit, this function returns the
442   --  corresponding xxx_Declaration node for the entity. Also applies to the
443   --  body entities for subprograms, tasks and protected units, in which case
444   --  it returns the subprogram, task or protected body node for it. The unit
445   --  may be a child unit with any number of ancestors.
446
447end Sem_Aux;
448