1----------------------------------------------------------------------
2--  Thick_Queries - Package specification                           --
3--  Copyright (C) 2002-2009 Adalog                                  --
4--  Author: J-P. Rosen                                              --
5--                                                                  --
6--  ADALOG   is   providing   training,   consultancy,   expertise, --
7--  assistance and custom developments  in Ada and related software --
8--  engineering techniques.  For more info about our services:      --
9--  ADALOG                          Tel: +33 1 45 29 21 52          --
10--  2 rue du Docteur Lombard        Fax: +33 1 45 29 25 00          --
11--  92441 ISSY LES MOULINEAUX CEDEX E-m: info@adalog.fr             --
12--  FRANCE                          URL: http://www.adalog.fr       --
13--                                                                  --
14--  This  unit is  free software;  you can  redistribute  it and/or --
15--  modify  it under  terms of  the GNU  General Public  License as --
16--  published by the Free Software Foundation; either version 2, or --
17--  (at your  option) any later version.  This  unit is distributed --
18--  in the hope  that it will be useful,  but WITHOUT ANY WARRANTY; --
19--  without even the implied warranty of MERCHANTABILITY or FITNESS --
20--  FOR A  PARTICULAR PURPOSE.  See the GNU  General Public License --
21--  for more details.   You should have received a  copy of the GNU --
22--  General Public License distributed  with this program; see file --
23--  COPYING.   If not, write  to the  Free Software  Foundation, 59 --
24--  Temple Place - Suite 330, Boston, MA 02111-1307, USA.           --
25--                                                                  --
26--  As  a special  exception, if  other files  instantiate generics --
27--  from  this unit,  or you  link this  unit with  other  files to --
28--  produce an executable,  this unit does not by  itself cause the --
29--  resulting executable  to be covered  by the GNU  General Public --
30--  License.  This exception does  not however invalidate any other --
31--  reasons why  the executable  file might be  covered by  the GNU --
32--  Public License.                                                 --
33----------------------------------------------------------------------
34
35with Asis;
36with System;
37package Thick_Queries is
38
39   -------------------------------------------------------------------------------------------------
40   --                                                                                             --
41   -- Error report                                                                                --
42   --                                                                                             --
43   -------------------------------------------------------------------------------------------------
44
45   type Error_Procedure is access procedure (Message : Wide_String; Elem : Asis.Element);
46   procedure Set_Error_Procedure (To : Error_Procedure);
47   -- Defines a user defined procedure called in case of an internal error
48   -- ("impossible" cases, or calls with inappropriate elements)
49   -- The user procedure may raise an exception. If it doesn't (or no user procedure is defined),
50   -- Program_Error will be raised.
51
52   -------------------------------------------------------------------------------------------------
53   --                                                                                             --
54   -- Convenience subtypes (for binary operators only)                                            --
55   --                                                                                             --
56   -------------------------------------------------------------------------------------------------
57   subtype Logical_Operators     is Asis.Operator_Kinds range Asis.An_And_Operator     .. Asis.An_Xor_Operator;
58   subtype Equality_Operators    is Asis.Operator_Kinds range Asis.An_Equal_Operator   .. Asis.A_Not_Equal_Operator;
59   subtype Relational_Operators  is Asis.Operator_Kinds range Asis.An_Equal_Operator   ..
60                                                                              Asis.A_Greater_Than_Or_Equal_Operator;
61   subtype Adding_Operators      is Asis.Operator_Kinds range Asis.A_Plus_Operator     .. Asis.A_Minus_Operator;
62   subtype Multiplying_Operators is Asis.Operator_Kinds range Asis.A_Multiply_Operator .. Asis.A_Rem_Operator;
63
64   subtype Discrete_Type_Kinds is Asis.Type_Kinds
65   range Asis.An_Enumeration_Type_Definition .. Asis.A_Modular_Type_Definition;
66   subtype Fixed_Type_Kinds    is Asis.Type_Kinds
67   range Asis.An_Ordinary_Fixed_Point_Definition .. Asis.A_Decimal_Fixed_Point_Definition;
68
69   -------------------------------------------------------------------------------------------------
70   --                                                                                             --
71   --  General types                                                                              --
72   --                                                                                             --
73   -------------------------------------------------------------------------------------------------
74
75   type Privacy_Policy is (Follow_Private, Follow_User_Private, Stop_At_Private);
76   -- Used to define the behaviour of some queries when they encounter a private type
77   -- - Follow_Private: Don't stop at private type, use the properties of the full type (privacy breaking)
78   -- - Stop_At_Private: Stop at private types, don't consider full types (non privacy breaking)
79   -- - Follow_User_Private: Like Follow_Private for user-defined private types, and like
80   --                        Stop_At_Private for language defined and implementation defined private types
81
82   -------------------------------------------------------------------------------------------------
83   --                                                                                             --
84   -- Queries about program structure                                                             --
85   --                                                                                             --
86   -------------------------------------------------------------------------------------------------
87
88   function Enclosing_Program_Unit (Element          : Asis.Element;
89                                    Including_Accept : Boolean      := False)
90                                   return Asis.Defining_Name;
91   --  Return the Defining_Name of the innermost enclosing program unit of any Element
92   --  If Including_Accept is true and the element is within an accept statement, return
93   --  the corresponding entry name from the entry declaration (not really a program unit,
94   --  but useful f.e. if the Element is a Return_Statement, and you want to know what you
95   --  are returning from).
96   --
97   --  Appropriate Element_Kinds:
98   --     Any element
99   --
100   --  Returns
101   --     A_Defining_Name
102   --     Nil_Element if Element is Nil, or is a Compilation_Unit
103   --
104
105   function Is_Compilation_Unit (Element : Asis.Element) return Boolean;
106   --  Return True if Element is the declaration of its enclosing compilation unit
107   --
108   --  Appropriate Element_Kinds:
109   --     Any element
110
111   function Is_Ancestor (Outer : Asis.Compilation_Unit; Inner : Asis.Compilation_Unit) return Boolean;
112   -- Returns True if Inner Is_Equal to Outer or one of its (direct or indirect) children
113
114   Global_Level : constant Asis.ASIS_Natural := 0;
115   function Static_Level (Element : Asis.Element) return Asis.ASIS_Natural;
116   -- Returns the static scope nesting level of Element
117   -- Library units and entities declared in library packages have level 0 (global)
118   -- Subprograms and tasks add 1 to the level (not packages)
119   --  Appropriate Element_Kinds:
120   --    A_Declaration
121   --    A_Defining_Name
122   --    An_Expression
123   -- Appropriate Expression_Kinds:
124   --    An_Identifier
125   --    A_Selected_Component (checks the selector)
126
127   function First_Enclosing_Instantiation (The_Element : Asis.Element) return Asis.Declaration;
128   -- For an entity which Is_Part_Of_Instance:
129   -- Return the first enclosing instantiation, which can itself be Is_Part_Of_Instance
130
131   function Ultimate_Enclosing_Instantiation (The_Element : Asis.Element) return Asis.Declaration;
132   -- For an entity which Is_Part_Of_Instance:
133   -- Return the "true" instantiation, i.e. the one written by the user, going up instantiations
134   -- that appear in generics.
135
136   function Is_Generic_Unit (Element : in Asis.Element) return Boolean;
137   -- Returns True if Element is the declaration or the body of a generic unit
138   -- Returns False in all other cases
139   --
140   --  Appropriate Element_Kinds:
141   --     Any element
142
143
144   function Is_Part_Of_Generic (Element : in Asis.Element) return Boolean;
145   -- Checks whether the Element is included (directly or indirectly) in a generic
146   --
147   --  Appropriate Element_Kinds:
148   --     Any element
149
150   function Ultimate_Origin (Element : in Asis.Element) return Asis.Unit_Origins;
151   -- Returns the Unit_Origin of the Unit where Element is declared.
152   -- If Element is an instance or Is_Part_Of_Instance, returns the Unit_Origin of the
153   -- corresponding generic or generic element.
154   -- Follows renamings to avoid being fooled by (user) renaming of Standard units.
155   --
156   -- Appropriate Element_Kinds:
157   --    A_Declaration
158   --    A_Defining_Name
159   --    An_Expression
160   -- Appropriate Expression_Kinds:
161   --    An_Identifier
162   --    A_Selected_Component (checks the selector)
163
164   function Definition_Compilation_Unit (Element : in Asis.Element) return Asis.Compilation_Unit;
165   -- Returns the compilation unit in which Element is declared
166   --
167   -- Appropriate Element_Kinds:
168   --    A_Defining_Name
169   --    An_Expression
170   -- Appropriate Expression_Kinds:
171   --    An_Identifier
172   --    A_Selected_Component (checks the selector)
173
174   function Corresponding_Static_Exception_Handler (Exc            : Asis.Element;
175                                                    Where          : Asis.Element;
176                                                    Include_Others : Boolean)
177                                                    return Asis.Exception_Handler;
178   -- Returns the innermost exception handler that handles the given exception, and whose corresponding
179   -- sequence of statements statically encloses Where.
180   -- Returns a Nil_Element if no such handler is found
181   --
182   -- If the handler is a "when others" one, return it if Include_Others is true,
183   -- return Nil_Element otherwise.
184   --
185   -- Look up stops as soon as a callable entity (or task body) is encountered (since from that point on,
186   -- exception propagation is no more statically determinable).
187   --
188   -- Appropriate Element_Kinds:
189   --    A_Defining_Name
190   --    An_Expression
191   -- Appropriate Expression_Kinds:
192   --    An_Identifier
193   --    A_Selected_Component (checks the selector)
194
195
196   function Is_Handled_Sequence_Container (Element : in Asis.Element) return Boolean;
197   -- Returns True if Element is one of the elements that can contain a handled sequence of statements
198   -- Returns false otherwise
199
200   function Declarative_Items (Element : in Asis.Element; Include_Pragmas : in Boolean := False)
201                              return Asis.Declaration_List;
202   -- Returns the declarative items of any construct with declarative items.
203   -- Appropriate Element_Kinds:
204   --    A_Declaration
205   --    A_Statement
206   --
207   -- Appropriate Declaration_Kinds:
208   --    A_Package_Declaration
209   --    A_Generic_Package_Declaration
210   --    A_Function_Body_Declaration
211   --    A_Procedure_Body_Declaration
212   --    A_Package_Body_Declaration
213   --    A_Task_Body_Declaration
214   --    An_Entry_Body_Declaration
215   --    A_Protected_Body_Declaration
216   --
217   -- Appropriate Statement_Kinds:
218   --    A_Block_Statement
219
220
221   function Statements (Element         : in Asis.Element;
222                        Include_Pragmas : in Boolean := False) return Asis.Statement_List;
223   -- Returns the statements of any construct with statements.
224   -- Appropriate Element_Kinds:
225   --    A_Declaration
226   --    A_Statement
227   --    A_Path
228   --    An_Exception_Handler
229   --
230   -- Appropriate Declaration_Kinds:
231   --    A_Function_Body_Declaration
232   --    A_Procedure_Body_Declaration
233   --    A_Package_Body_Declaration
234   --    A_Task_Body_Declaration
235   --    An_Entry_Body_Declaration
236   --
237   -- Appropriate Statement_Kinds:
238   --    An_Accept_Statement
239   --    A_Block_Statement
240   --    A_Loop_Statement
241   --    A_While_Loop_Statement
242   --    A_For_Loop_Statement
243   --    An_Extended_Return_Statement
244
245   function Exception_Handlers (Element : Asis.Element) return Asis.Exception_Handler_List;
246   -- Returns the exception handlers of any construct with exception hanlders.
247   -- Appropriate Element_Kinds:
248   --    A_Declaration
249   --    A_Statement
250   --
251   -- Appropriate Declaration_Kinds:
252   --    A_Function_Body_Declaration
253   --    A_Procedure_Body_Declaration
254   --    A_Package_Body_Declaration
255   --    A_Task_Body_Declaration
256   --    An_Entry_Body_Declaration
257   --
258   -- Appropriate Statement_Kinds:
259   --    An_Accept_Statement
260   --    A_Block_Statement
261   --    An_Extended_Return_Statement
262
263
264   -------------------------------------------------------------------------------------------------
265   --                                                                                             --
266   -- Queries about statements                                                                    --
267   --                                                                                             --
268   -------------------------------------------------------------------------------------------------
269
270   function Last_Effective_Statement (Stats : Asis.Statement_List) return Asis.Statement;
271   -- Returns the last statement from Stats, unless it is a block statement without exception handlers,
272   -- in which case the last statement of the block is returned (recursively, of course).
273
274   function Are_Null_Statements (Stats : Asis.Statement_List; Except_Labelled : Boolean := False) return Boolean;
275   -- Checks whether Stats contain only null statement(s)
276   -- If Except_Labelled is True, returns False also if there is a labelled statement
277
278   function First_Exiting_Statement (Stats : Asis.Statement_List; Include_Returns : Boolean := True)
279                                     return Asis.Statement;
280   -- Returns the (textually) first exit or goto statement that transfer control outside of Stats.
281   -- If Include_Returns is True, also possibly returns a return statement, an extended return statement,
282   -- or a requeue statement.
283
284   function Is_Part_Of (Elem : Asis.Element; Inside : Asis.Element_List) return Boolean;
285   -- returns true if Elem is textually within Inside
286   -- Note: will return False for any element that Is_Part_Of_Instance, since these have no
287   --       *textual* representation. The caller should take care of calling Corresponding_Generic_Element
288   --       as needed to recognize elements that are Is_Part_Of_Instance
289
290   -------------------------------------------------------------------------------------------------
291   --                                                                                             --
292   -- Images                                                                                      --
293   --                                                                                             --
294   -------------------------------------------------------------------------------------------------
295
296   function Attribute_Name_Image (Attribute : Asis.Expression) return Wide_String;
297   --  Like Pragma_Name_Image, but for an Attribute_Reference
298   --
299   --  Appropriate Element_Kinds:
300   --    An_Expression
301   --  Appropriate Expression_Kinds:
302   --    An_Attribute_Reference
303
304
305   function Extended_Name_Image (Name_Elem               : Asis.Element;
306                                 Silent_If_Inappropriate : Boolean := False) return Wide_String;
307   -- Image of a Name, Defining_Name, or pragma given either as a simple name or as a Selected_Name
308   -- If Silent_If_Inappropriate is True, returns "" for inappropriate elements instead of raising an exception
309   --
310   --  Appropriate Element_Kinds:
311   --    An_Expression
312   --    A_Defining_Name
313   --    A_Pragma
314   --  Appropriate Expression_Kinds:
315   --    An_Identifier
316   --    A_Selected_Component
317   --    An_Attribute_Reference
318   --    An_Explicit_Dereference
319
320
321   function Full_Name_Image (The_Name     : in Asis.Element;
322                             With_Profile : in Boolean := False) return Wide_String;
323   -- Full name of a name
324   -- Works like Asis.Declarations.Defining_Name_Image (or Name_Image),
325   -- but returns the full (unique) name of The_Name, starting from the
326   -- enclosing compilation unit (Standard for predefined elements).
327   -- If With_Profile is true, "mangles" the name with a profile to provide a name
328   -- that is unique even if overloaded.
329   --
330   -- Returns "" if the Full_Name_Image cannot be computed. This happens:
331   --   - if The_Name is a predefined operator and With_Profile is True.
332   --   - if The_Name is a subprogram name or formal parameter from a dispatching call
333   --
334   -- Appropriate Element_Kinds:
335   --    A_Defining_Name
336   --    An_Expression
337   -- Appropriate Expression_Kinds:
338   --    An_Identifier
339   --    A_Selected_Component (returns the image of the selector)
340   --    An_Attribute_Reference
341
342
343   function Profile_Image (The_Name     : Asis.Element;
344                           With_Profile : Boolean := True) return Wide_String;
345   -- Image of the profile of a callable construct
346   -- If name is not a callable construct, returns ""
347   -- Otherwise:
348   --    for a procedure, entry...:
349   --       returns '{' {<Full_Name_Image (types of parameter) '}'}
350   --    for a function:
351   --       returns '{' {<Full_Name_Image (types of parameter) } ':' Full_Name_Image (result type) '}'
352   -- With_Profile determines if the Full_Name_Image generated for parameters and result includes
353   -- itself a profile.
354   --
355   -- Appropriate Element_Kinds:
356   --    A_Defining_Name
357   --    An_Expression
358   -- Appropriate Expression_Kinds:
359   --    An_Identifier
360   --    A_Selected_Component (returns the image of the selector)
361
362
363   -------------------------------------------------------------------------------------------------
364   --                                                                                             --
365   -- Queries about types                                                                         --
366   --                                                                                             --
367   -------------------------------------------------------------------------------------------------
368
369   function Subtype_Simple_Name (Definition : Asis.Definition) return Asis.Expression;
370   -- Like Subtype_Mark, but returns the selector if the subtype mark is a selected component
371   -- Moreover, it avoids the ambiguity between Asis.Subtype_Mark and Asis.Definitions.Subtype_Mark
372
373   function First_Subtype_Name (The_Subtype : Asis.Element) return Asis.Expression;
374   -- Unwinds subtype declarations and returns the *name* of the first subtype denoted by The_Subtype,
375   -- picked up from the last subtype declaration.
376   -- Returns its argument if The_Subtype already denotes a first subtype.
377   -- Unlike Corresponding_First_Subtype, this works in case of subtyping of a class wide type
378   -- (returns the XXX'class)
379   --
380   -- Appropriate Element_Kinds
381   --   A_Defining_Name
382   --   An_Expression
383   -- Appropriate Expression_Kinds:
384   --   An_Identifier
385   --   A_Selected_Component (works on selector)
386   --   An_Attribute_Reference (T'Base only)
387   --
388   -- Returns Expression_Kinds:
389   --   An_Identifier
390   --   An_Attribute_Reference
391
392   function Access_Target_Type (The_Subtype : Asis.Element) return Asis.Declaration;
393   -- Returns the declaration of the first subtype of the target of the access type if The_Subtype
394   -- is a declaration of an access to object type (including anonymous ones) or of a formal access
395   -- to object type.
396   -- It's the really first subtype ;-), ignoring 'Base and 'Class attributes that can be in the way.
397   -- Returns Nil_Element in all other cases
398   --
399   -- Appropriate Element_Kinds:
400   --    A_Declaration
401   --    A_Definition
402   --    A_Defining_Name
403
404   function Is_Access_Subtype (The_Subtype : Asis.Element) return Boolean;
405   -- Returns True if The_Subtype is a declaration of an access type or of a formal access type
406   -- Returns False in all other cases
407   --
408   -- Appropriate Element_Kinds:
409   --    A_Declaration
410   --    A_Definition
411   --    A_Defining_Name
412
413   function Is_Array_Subtype (The_Subtype : Asis.Element) return Boolean;
414   -- Returns True if The_Subtype is a declaration (or a definition) of an array type, or a name of an array type
415   -- Returns False in all other cases
416   --
417   -- Appropriate Element_Kinds:
418   --    A_Declaration
419   --    A_Definition
420   --    A_Defining_Name
421   --    An_Expression
422   --
423   -- Appropriate Declaration_Kinds:
424   --    An_Ordinary_Type_Declaration
425   --    A_Task_Type_Declaration
426   --    A_Protected_Type_Declaration
427   --    A_Private_Type_Declaration
428   --    A_Private_Extension_Declaration
429   --    A_Subtype_Declaration
430   --    A_Formal_Type_Declaration
431   --
432   -- Appropriate Expression_Kinds:
433   --    An_Identifier
434   --    A_Selected_Component (applies on selector)
435   --    An_Attribute_Reference
436
437
438   function Is_Character_Subtype (The_Subtype : Asis.Element) return Boolean;
439   -- Returns True if The_Subtype is a declaration of a character type, or a name of a character type
440   -- Returns False in all other cases
441   --
442   -- Appropriate Element_Kinds:
443   --    A_Declaration
444   --    A_Definition
445   --    A_Defining_Name
446   --    An_Expression
447
448   function Is_Class_Wide_Subtype (The_Subtype : Asis.Element) return Boolean;
449   -- Unwinds subtype declarations and returns true if the given subtype declaration,
450   -- or the type designated by the provided name, ultimately designates a class-wide type.
451   --
452   -- Appropriate Element_Kinds:
453   --    A_Declaration
454   --    A_Definition
455   --    A_Defining_Name
456   --    An_Expression
457   --
458   -- Appropriate Declaration_Kinds:
459   --    A_Subtype_Declaration
460   --
461   -- Appropriate Definition_Kinds:
462   --    A_Type_Definition (always returns false)
463   --    A_Subtype_Indication
464   --
465   -- Appropriate Expression_Kinds:
466   --    An_Identifier
467   --    A_Selected_Component (applies on selector)
468   --    An_Attribute_Reference
469
470   function Is_Limited (The_Element : Asis.Element) return Boolean;
471   -- Returns True if The_Element is a defining_name, declaration or definition of an (explicit or implicit)
472   -- limited type, of an object of a limited type, or an expression whose type is limited.
473   -- Returns False in all other cases
474   --
475   -- Appropriate Element_Kinds
476   --   A_Declaration
477   --   A_Definition
478   --   A_Defining_Name
479   --   An_Expression
480   --
481   --  Appropriate Expression_Kinds:
482   --       An_Identifier
483   --       An_Operator_Symbol
484   --       A_Character_Literal
485   --       An_Enumeration_Literal
486   --       A_Selected_Component (applies to selector)
487
488
489   function Corresponding_Full_Type_Declaration (Decl : Asis.Declaration) return Asis.Declaration;
490   -- Returns the full type of Decl if Decl is an incomplete or private (tagged) type declaration
491   -- Returns Decl otherwise
492   --
493   -- Appropriate Declaration_Kinds:
494   --       A_Type_Declaration
495
496
497   type Derivation_Descriptor is
498      record
499         Ultimate_Type    : Asis.Declaration;  -- The ancestor which is not a derived types
500         Derivation_Depth : Asis.ASIS_Natural; -- How many derivations
501         First_Constraint : Asis.Constraint;   -- The first constraint encountered when going up derivations
502      end record;
503
504   function Corresponding_Derivation_Description (The_Subtype : Asis.Declaration;
505                                                  Privacy     : Privacy_Policy := Follow_User_Private)
506                                                  return Derivation_Descriptor;
507   -- Unwinds subtype declarations, derivations, private types and returns the real declaration
508   -- that tells what the type really is, and how many declarations are encountered in the way
509   -- (0 means that The_Subtype is not a derived type).
510   --
511   -- Note that for tagged types, derivations are also unwound up to the declaration that
512   -- includes the word "tagged".
513   -- Privacy defines behaviour when a private type is encountered during unwinding.
514   -- Unwinding stops at formal types, even if they are derived formal types.
515   --
516   -- Appropriate Declaration_Kinds:
517   --       An_Ordinary_Type_Declaration
518   --       A_Task_Type_Declaration
519   --       A_Protected_Type_Declaration
520   --       A_Private_Type_Declaration
521   --       A_Private_Extension_Declaration
522   --       A_Subtype_Declaration
523   --       A_Formal_Type_Declaration
524   --
525   --  Returns Declaration_Kinds:
526   --       An_Ordinary_Type_Declaration
527   --       A_Task_Type_Declaration
528   --       A_Protected_Type_Declaration
529   --       A_Formal_Type_Declaration
530   --  Returns Type_Kinds:
531   --       An_Enumeration_Type_Definition
532   --       A_Signed_Integer_Type_Definition
533   --       A_Modular_Type_Definition
534   --       A_Floating_Point_Definition
535   --       An_Ordinary_Fixed_Point_Definition
536   --       A_Decimal_Fixed_Point_Definition
537   --       An_Unconstrained_Array_Definition
538   --       A_Constrained_Array_Definition
539   --       A_Record_Type_Definition
540   --       A_Tagged_Record_Type_Definition
541   --       An_Access_Type_Definition
542
543
544   function Ultimate_Type_Declaration (The_Subtype : Asis.Declaration;
545                                       Privacy     : Privacy_Policy := Follow_User_Private)
546                                       return Asis.Declaration;
547   -- Returns the Ultimate_Type component of Corresponding_Derivation_Description
548
549   function Derivation_Depth (The_Subtype : Asis.Declaration;
550                              Privacy     : Privacy_Policy := Follow_User_Private)
551                                       return Asis.ASIS_Natural;
552   -- Returns the Derivation_Depth component of Corresponding_Derivation_Description
553
554   function Is_Type_Declaration_Kind (The_Subtype : Asis.Declaration; The_Kind : Asis.Declaration_Kinds) return Boolean;
555   -- Unwinds subtype declarations and derivations and returns true if the given subtype
556   -- declaration ultimately designates a type of the given kind.
557   --
558   -- Appropriate Declaration_Kinds:
559   --       An_Ordinary_Type_Declaration
560   --       A_Task_Type_Declaration
561   --       A_Protected_Type_Declaration
562   --       A_Private_Type_Declaration
563   --       A_Private_Extension_Declaration
564   --       A_Subtype_Declaration
565   --       A_Formal_Type_Declaration
566
567
568   function Contains_Type_Declaration_Kind (The_Subtype : Asis.Declaration;
569                                            The_Kind    : Asis.Declaration_Kinds) return Boolean;
570   -- Like Is_Type_Declaration_Kind, but for composite types, returns True if any subcomponent is
571   -- of the given kind.
572   --
573   -- Appropriate Declaration_Kinds:
574   --       An_Ordinary_Type_Declaration
575   --       A_Task_Type_Declaration
576   --       A_Protected_Type_Declaration
577   --       A_Private_Type_Declaration
578   --       A_Private_Extension_Declaration
579   --       A_Subtype_Declaration
580   --       A_Formal_Type_Declaration
581
582   type Discriminant_Part_Kinds is (No_Discriminant_Part,          A_Nondefaulted_Discriminant_Part,
583                                    A_Defaulted_Discriminant_Part, An_Unknown_Discriminant_Part);
584   function Discriminant_Part_Kind (Elem : Asis.Element) return Discriminant_Part_Kinds;
585   -- Appropriate Element_Kinds:
586   --     A_Declaration
587   --     A_Definition
588   --  Appropriate Declaration_Kinds:
589   --     An_Ordinary_Type_Declaration
590   --     A_Task_Type_Declaration
591   --     A_Protected_Type_Declaration
592   --     An_Incomplete_Type_Declaration
593   --     A_Tagged_Incomplete_Type_Declaration
594   --     A_Private_Type_Declaration
595   --     A_Private_Extension_Declaration
596   --     A_Formal_Type_Declaration
597   --  Appropriate Definition_Kinds:
598   --     An_Unknown_Discriminant_Part
599   --     A_Known_Discriminant_Part
600   --  Nil_Element is allowed and returns No_Discriminant_Part
601
602
603   function Attribute_Clause_Expression (Attribute : in Asis.Attribute_Kinds;
604                                         Elem      : in Asis.Element)
605                                         return Asis.Expression;
606   -- Returns the Expression of the attribute specification clause that applies
607   -- to the indicated type or object (or declaration thereof)
608   -- Returns Nil_Element if there is no applicable clause.
609   -- If Attribute is 'Address or 'Alignment, Ada83 equivalent forms are considered
610   --
611   -- Warning: implementation relies on Corresponding_Representation_Clauses, and therefore
612   --          cannot be trusted for objects.
613   --
614   -- Appropriate Element_Kinds:
615   --     A_Declaration
616   --     A_Defining_Name
617   --     An_Expression
618   --
619   --  Appropriate Expression_Kinds:
620   --       An_Identifier
621   --       A_Selected_Component (applies to selector)
622   --       An_Attribute_Reference (T'Base or T'Class)
623
624   function Corresponding_Component_Clause (Component : in Asis.Defining_Name) return Asis.Component_Clause;
625   -- Returns the component clause that applies to the indicated component.
626   -- Returns Nil_Element if there is no applicable component clause.
627   --
628   -- We use the defining_name rather than the component declaration here to avoid problems in
629   -- case of declarations with several defining names.
630
631   function Corresponding_Enumeration_Clause (Enumeration_Value : in Asis.Defining_Name) return Asis.Association;
632   -- Returns the association Enumeration_Value => Representation for the given Enumeration_Value
633   -- Returns Nil_Element if there is no applicable enumeration representation clause
634
635
636   type Type_Categories is (Not_A_Type,
637                            An_Enumeration_Type,
638                            A_Signed_Integer_Type,
639                            A_Modular_Type,
640                            A_Fixed_Point_Type,
641                            A_Floating_Point_Type,
642                            An_Array_Type,
643                            A_Record_Type,               -- untagged
644                            A_Tagged_Type,               -- including record extensions if Separate_Extension is false
645                            An_Extended_Tagged_Type,
646                            An_Access_Type,
647                            A_Derived_Type,
648                            A_Private_Type,
649                            A_Task_Type,
650                            A_Protected_Type);
651   subtype Discrete_Types     is Type_Categories range An_Enumeration_Type   .. A_Modular_Type;
652   subtype Numeric_Types      is Type_Categories range A_Signed_Integer_Type .. A_Modular_Type;
653   subtype Scalar_Types       is Type_Categories range An_Enumeration_Type   .. A_Floating_Point_Type;
654   subtype Integer_Types      is Type_Categories range A_Signed_Integer_Type .. A_Modular_Type;
655   subtype Real_Types         is Type_Categories range A_Fixed_Point_Type    .. A_Floating_Point_Type;
656   subtype Composite_Types    is Type_Categories range An_Array_Type         .. A_Tagged_Type;
657   subtype Synchronized_Types is Type_Categories range A_Task_Type           .. A_Protected_Type;
658
659   function Type_Category (Elem               : in Asis.Element;
660                           Follow_Derived     : in Boolean := False;
661                           Privacy            : in Privacy_Policy := Stop_At_Private;
662                           Separate_Extension : in Boolean := False) return Type_Categories;
663   -- For private and derived types:
664   --    If Follow_Derived (resp. Follow_Private) is True, returns the category of the
665   --    parent (full) type instead of A_Derived_Type (A_Private_Type).
666   --    Formal private types return A_Private_Type even if Follow_Private is True (no corresponding full declaration)
667   --
668   -- For (private) type extensions:
669   --   if Separate_Extension is True, returns An_Extended_Tagged_Type, otherwise returns A_Tagged_Type.
670   --
671   -- Incomplete types are always followed.
672   --
673   -- Expressions can be either type names or true (typed) expressions
674   --
675   -- Appropriate Element_Kinds:
676   --       A_Declaration
677   --       A_Definition
678   --       A_Defining_Name
679   --       An_Expression
680   -- Appropriate Declaration_Kinds:
681   --       An_Ordinary_Type_Declaration
682   --       A_Task_Type_Declaration
683   --       A_Protected_Type_Declaration
684   --       A_Private_Type_Declaration
685   --       A_Private_Extension_Declaration
686   --       A_Subtype_Declaration
687   --       A_Formal_Type_Declaration
688   --       A_Variable_Declaration
689   --       A_Constant_Declaration
690   --       A_Deferred_Constant_Declaration
691   --       A_Component_Declaration
692   --       A_Discriminant_Specification
693   -- Appropriate Definition_Types:
694   --       A_Type_Definition
695   --       A_Task_Definition
696   --       A_Protected_Definition
697   --
698   -- Notes:
699   -- 1- We do not distinguish between ordinary and decimal fixed point types, because we
700   --    would be unable to know what to return for expressions that are universal_fixed
701   -- 2- Handling of expressions of a root or universal type:
702   --    Root_Integer and Universal_Integer returns A_Signed_Integer_Type
703   --    Root_Real and Universal_Real returns A_Floating_Point_Type (which is the best we can do)
704   --    Universal_Fixed returns A_Fixed_Point type, of course
705
706   function Range_Ultimate_Name (Range_Def : Asis.Definition) return Asis.Defining_Name;
707   -- Return the name of the type of the given range.
708   -- Returns Nil_Element if the range is given by two integer literals (implicit Integer)
709   --
710   --  Expected Definition_Kinds:
711   --       A_Discrete_Subtype_Definition
712   --       A_Discrete_Range
713
714   function Dimensionality (Type_Def : Asis.Type_Definition) return Asis.ASIS_Natural;
715   -- Return the number of dimensions of a (constrained or unconstrained) array type.
716   -- Returns 0 if the definition is not of an array type.
717   --
718   -- Appropriate type kinds:
719   --       An_Unconstrained_Array_Definition
720   --       A_Constrained_Array_Definition
721   -- Appropriate formal type kinds:
722   --       A_Formal_Unconstrained_Array_Definition
723   --       A_Formal_Constrained_Array_Definition
724
725   function Index_Subtypes_Names (Type_Def : Asis.Type_Definition) return Asis.Element_List;
726   -- Return the list of defining names for the subtypes of an (constrained or unconstrained) array
727   -- definition.
728   -- Returns a nil element instead of a defining name in the case of e.g. array(1..10)
729   --
730   -- Appropriate type kinds:
731   --       An_Unconstrained_Array_Definition
732   --       A_Constrained_Array_Definition
733   -- Appropriate formal type kinds:
734   --       A_Formal_Unconstrained_Array_Definition
735   --       A_Formal_Constrained_Array_Definition
736
737   function Corresponding_Static_Predicates (Elem : in Asis.Element) return Asis.Element_List;
738   -- Return the list of expressions of all applicable static predicates (directly given or inherited)
739   -- Returns a Nil_Element_List if there are no applicable static predicate
740   -- In case of an expression, returns applicable static predicates for its subtype.
741   -- Returns Nil_Element_List for any inappropriate element
742   --
743   -- Appropriate element kinds:
744   --      An_Expression
745   --      A_Declaration
746
747   function Corresponding_Static_Predicates (List : in Asis.Element_List) return Asis.Element_List;
748   -- Return the catenation of Corresponding_Static_Predicates for all elements in List
749
750   -------------------------------------------------------------------------------------------------
751   --                                                                                             --
752   -- Queries about names and expressions                                                         --
753   --                                                                                             --
754   -------------------------------------------------------------------------------------------------
755
756   function Simple_Name (The_Name : Asis.Expression) return Asis.Expression;
757   -- Gets rid of selection, i.e. returns the selector of its argument if A_Selected_Component,
758   -- its argument otherwise.
759
760   function Unindexed_Name (The_Name : Asis.Expression) return Asis.Expression;
761   -- Gets rid of indexing, i.e. returns the selector of its argument if An_Indexed_Component,
762   -- its argument otherwise.
763
764   function Strip_Attributes (Name : Asis.Expression) return Asis.Expression;
765   -- If Name is an Attribute_Reference, returns the first prefix which is not itself an Attribute_Reference.
766   -- Returns Name otherwise
767
768   function Strip_Parentheses (Expr : Asis.Expression) return Asis.Expression;
769   -- If Expr is a parenthesized expression, removes all levels of parentheses,
770   -- otherwise returns Expr
771
772   function Ultimate_Name (The_Name : Asis.Element; No_Component : Boolean := False) return Asis.Element;
773   -- For a name defined by a renaming declaration: returns the name of the entity, which is not
774   --   itself defined by a renaming.
775   --   - In the case of a renaming whose target is part of a record (or protected) type:
776   --        if No_Component is False, returns the name of the component
777   --        if No_Component is True, returns the name of the object the field belongs to
778   --   - In the case of a renaming whose target is part of an array, returns the name of
779   --     array object
780   --        (i.e. X : T renames V.Field (2) => Field if No_Component is false,
781     --                                      => V if No_Component is True).
782   --   - In the case of a renaming whose target is An_Explicit_Dereference, returns Nil_Element
783   --     (the target is statically unknown)
784   --   - In the case of a renaming whose target is A_Function_Call, returns Nil_Element
785   --     (the target is statically unknown, it designates the result of the function call)
786   --   - In the case of the renaming of an attribute, returns the attribute
787   -- Otherwise: returns its argument (including A_Nil_Element)
788   --
789   -- In any case, if The_Name is A_Defining_Name, then A_Defining_Name is returned
790   -- if The_Name is An_Identifier, then An_Identifier (or An_Attribute_Reference) is returned,
791   --   and always as a simple name.
792   --
793   -- Appropriate Element_Kinds:
794   --    A_Defining_Name
795   --    An_Expression
796   -- Appropriate Expression_Kinds:
797   --    An_Identifier
798   --    A_Selected_Component (operates on selector)
799   --    An_Attribute_Reference
800
801   function First_Defining_Name (Name : Asis.Element) return Asis.Defining_Name;
802   -- Returns the first textually encountered defining name of Name (assuming normal
803   -- processing order), i.e.:
804   -- For a program unit with a spec: the defining name from the spec, given the name
805   --     of a spec, the name of a body, the name of a stub, or the name of a proper body
806   -- For a subprogram without a spec: the defining name from the body (given same input)
807   -- For a private or incomplete or deferred declaration, or the full declaration of one
808   --     of these: the defining name of the private or incomplete or deferred declaration.
809   -- For a formal parameter of a body: the corresponding formal parameter of the spec if
810   --     there is one, the one from the body otherwise.
811   -- For a formal parameter of a proper body: the corresponding formal parameter of the spec if
812   --     there is one, the one from the stub otherwise.
813   --
814   -- Appropriate Element_Kinds:
815   --    A_Defining_Name
816   --    An_Expression
817   -- Appropriate Expression_Kinds:
818   --    An_Identifier
819   --    A_Selected_Component (operates on selector)
820
821   function Matching_Name (Name : Asis.Defining_Name; Decl : Asis.Declaration) return Asis.Defining_Name;
822   -- Return the Defining_Name from Decl which is identical to Name
823   -- return Nil_Element if not found
824
825   function Ultimate_Expression (Expr : Asis.Expression) return Asis.Expression;
826   -- Returns Simple_name (Expr), unless Expr is the name of constant, in which case it returns
827   -- the Ultimate_Expression of the initialization expression of the constant.
828
829   function Association_Choices (Assoc : Asis.Association) return Asis.Expression_List;
830   -- Returns the list of choices (LHS) of the association, independently of the association kind.
831   -- Returns Nil_Element_List for a positional association.
832
833   function Association_Value (Assoc : Asis.Association) return Asis.Expression;
834   -- Returns the value (RHS) of the association, independently of the association kind.
835
836   function Is_Static_Object (Obj : Asis.Expression) return Boolean;
837   -- Return True if Obj is a name that designates a statically determinable object
838   -- (including, f.e., statically indexed array components).
839   -- Return False in all other cases, including when Obj does not designate an Object
840
841
842   function Used_Identifiers (Name : Asis.Expression) return Asis.Expression_List;
843   -- Return all identifiers corresponding to entities accessed by the use of the name.
844   -- For identifiers that are not renamings, returns Name in a list of length 1
845   -- For identifiers declared by renaming, returns Name plus every record field and object name which
846   -- is part of the renamed expression, but not parts that are evaluated by the
847   -- elaboration of the renaming declaration itself. In short, if we see a name "Ren" declared by:
848   --    Ren : Integer renames Integer'(Pack.Tab(I).F);
849   -- we must consider that when Ren is used, Tab (a variable) is used, and F (a record field)
850   -- is used, but not Pack (a package) nor I (evaluated by the elaboration of the renaming),
851   -- nor Integer (evaluated by the elaboration of the renaming).
852   -- Of course, this is recursive. Given:
853   --    Ren : Integer renames A.I;
854   --    A   : Rec renames B;
855   --    B   : Rec;
856   -- The returned list is (Ren, A, B, I)
857   -- Lower bound of result is always 1, and the first element of the list Is_Identical to Name
858   --
859   -- Appropriate Expression_Kinds:
860   --    An_Identifier
861   --    An_Operator_Symbol
862   --    An_Enumeration_Literal
863
864
865   function Corresponding_Expression_Type_Definition (The_Element : Asis.Expression) return Asis.Definition;
866   -- return the (full) type definition of the type of The_Element
867   -- Unlike Corresponding_Expression_Type, works if the the type of The_Element is
868   -- an anonymous type and unwinds subtypes (but not derived types)
869   -- This query is a candidate for ASIS05, and already provided by ASIS-for-GNAT,
870   -- but we don't use it as long as it is not standard
871   --
872   -- WARNING 1: When passed a slice, returns the definition of the sliced object, bounds
873   --            will be those of the sliced object, not the slice itself. But what else
874   --            can we do?
875   -- WARNING 2: This function works when passed a type name (not really an expression),
876   --            not sure if it will work with the ASIS05 query
877
878   function Corresponding_Components (The_Element : Asis.Element) return Asis.Record_Component_List;
879   -- If the element is (a defining name of) a variable or a component of a record type, returns the
880   -- corresponding components
881   -- Return Nil_Element_List otherwise
882
883   function Ultimate_Expression_Type (The_Element : Asis.Expression) return Asis.Definition;
884   -- return the type definition of the ultimate ancestor type of The_Element
885   -- (going up all subtype and derived type declaration, and through private and incomplete declarations).
886
887
888   function Expression_Type_Kind (The_Element : Asis.Expression) return Asis.Type_Kinds;
889   -- Real kind of an expression
890   -- return the Type_Kind of the ultimate ancestor of The_Element
891   -- (going up all subtype and derived type declaration).
892
893   function Is_Access_Expression (The_Element : Asis.Expression) return Boolean;
894   -- Return True if The_Element is of an access type or of a formal access type.
895   -- Return False in all other cases
896
897   type Expression_Usage_Kinds is (Untouched, Read, Write, Read_Write, Unknown);
898   function Expression_Usage_Kind (Expr : Asis.Expression) return Expression_Usage_Kinds;
899   -- Returns Untouched if Expr is part of a renaming declaration or the prefix of an attribute
900   -- Returns Write if Expr designates a variable which is the
901   --  target of an assignment statement, or an actual corresponding
902   --  to an out parameter in a procedure or entry call.
903   -- Returns Read_Write if Expr designates a variable which is
904   --  an actual corresponding to an in out parameter in a procedure
905   --  or entry call.
906   -- Returns Unknown when usage cannot be determined (parameter of a dispatching call)
907   -- Returns Read in all other cases (including when Expr is not a variable)
908   --
909   -- Note that this function handles access types properly, i.e. in:
910   --    Integer_Pointer.all := 1;
911   -- if passed Integer_Pointer.all, it will return Write;
912   -- if passed Integer_Pointer, it will return Read.
913
914   function Includes_Renaming (Path : Asis.Expression) return Boolean;
915   -- Checks whether any element in the Path is a renaming
916   --
917   -- Appropriate expression kinds:
918   --   An_Identifier
919   --   A_Selected_Component
920   --   A_Function_Call
921   --   An_Indexed_Component
922   --   A_Slice
923
924
925   -------------------------------------------------------------------------------------------------
926   --                                                                                             --
927   -- Queries about pragmas                                                                       --
928   --                                                                                             --
929   -------------------------------------------------------------------------------------------------
930
931   type Pragma_Set is array (Asis.Pragma_Kinds) of Boolean;
932   function Corresponding_Pragma_Set (Element : in Asis.Element) return Pragma_Set;
933   -- Returns the set of pragmas that apply to the corresponding name or defining name
934   -- (including, for an object, those inherited from its type).
935   -- Pragmas that apply to T'Class are not included to the set for T (due to ASIS weakness)
936   -- Note that unlike Corresponding_Pragmas, this query makes sure that the pragma applies
937   -- really to the given element in the case of a multiple declaration.
938   --
939   -- Appropriate element kinds:
940   --   An_Expression
941   --   A_Defining_Name
942   -- Appropriate expression kinds
943   --   An_Identifier
944   --   A_Selected_Component (function applied to the selector)
945
946
947   function Is_Profile_Applied (Element : in Asis.Element; Profile : Wide_String) return Boolean;
948   -- Returns True if Profile applies to Element.
949   -- Profile must be given in upper case.
950   --
951   -- Appropriate element kinds:
952   --   Any element
953
954
955   -------------------------------------------------------------------------------------------------
956   --                                                                                             --
957   -- Queries about callable constructs                                                           --
958   --                                                                                             --
959   -------------------------------------------------------------------------------------------------
960
961   type Callable_Kinds is (Not_A_Callable,          A_Procedure_Callable,  A_Function_Callable,
962                           An_Enumeration_Callable, A_Task_Entry_Callable, A_Protected_Entry_Callable);
963   subtype A_Subprogram_Callable is Callable_Kinds range A_Procedure_Callable  .. A_Function_Callable;
964   subtype An_Entry_Callable     is Callable_Kinds range A_Task_Entry_Callable .. A_Protected_Entry_Callable;
965
966   function Callable_Kind (Element : Asis.Element) return Callable_Kinds;
967   -- Checks whether the Element is a callable construct, and which one
968   -- Expected elements:
969   --    A_Declaration
970   --    A_Definition
971   --    A_Defining_Name
972   --    An_Expression
973   -- Appropriate Expression_Kinds:
974   --    An_Identifier
975   --    An_Attribute_Reference
976   --    A_Selected_Component (applies to the selector)
977
978   function Is_Callable_Construct (Element : Asis.Element) return Boolean;
979   -- Checks whether the Element is a callable construct
980   -- Expected elements like Callable_Kind
981
982   function Is_Task_Entry (Declaration : Asis.Declaration) return Boolean;
983   -- Returns True if the Declaration is An_Entry_Declaration of a task.
984   -- Returns False if it is An_Entry_Declaration of a protected type
985   -- Expected elements:
986   --    A_Declaration
987   -- Appropriate Declaration_Kinds:
988   --    An_Entry_Declaration
989
990   function Is_Predefined_Operator (Decl : Asis.Declaration) return Boolean;
991   -- Expected declaration kind:
992   --    A_Function_Declaration
993   --    A_Function_Body_Declaration
994   -- (of operator)
995   -- Returns True if the operator is identical to a predefined one.
996
997   function Called_Simple_Name (Call : Asis.Element) return Asis.Expression;
998   -- Given a procedure, entry or function call, returns the simple name of the called
999   -- entity (from the call).
1000   -- It handles all cases in the same function (i.e. whether it is a procedure or a function,
1001   -- whether the call is from an access to subprogram, etc.)
1002   -- Returns the simple name of the called entity (i.e. not a Selected_Name).
1003   -- For calls to an entry family, returns the name of the family
1004   -- Returns a Nil_Element if the call is through an access to subprogram
1005   -- Works with dispatching calls!
1006   --
1007   -- Appropriate Element_Kinds:
1008   --    A_Statement
1009   --    An_Expression
1010   -- Appropriate Statement_Kinds:
1011   --    A_Procedure_Call_Statement
1012   --    An_Entry_Call_Statement
1013   -- Appropriate Expression_Kinds:
1014   --    A_Function_Call
1015
1016
1017   type Call_Kind is (A_Regular_Call,     A_Predefined_Entity_Call, An_Attribute_Call,
1018                      A_Dereference_Call, A_Dispatching_Call,       An_Enumeration_Literal);
1019   type Call_Descriptor (Kind : Call_Kind := A_Regular_Call) is
1020      record
1021         case Kind is
1022            when A_Regular_Call =>
1023               Declaration : Asis.Declaration;
1024            when others =>
1025               null;
1026         end case;
1027      end record;
1028   function Corresponding_Call_Description (Call : Asis.Element) return Call_Descriptor;
1029   -- Given a procedure, entry or function call, returns the descriptor of the called
1030   -- entity.
1031   -- If the call is to a good ol' statically determinable callable entity, the descriptor
1032   -- is A_Regular_Call, and the Declaration field contains the real declaration, after unwinding
1033   -- all possible renamings.
1034   -- Otherwise, the Kind discriminant tells why the declaration is not available.
1035   --
1036   -- Appropriate Element_Kinds:
1037   --    A_Statement
1038   --    An_Expression
1039   -- Appropriate Statement_Kinds:
1040   --    A_Procedure_Call_Statement
1041   --    An_Entry_Call_Statement
1042   -- Appropriate Expression_Kinds:
1043   --    A_Function_Call
1044
1045   function Called_Profile (Call : Asis.Element) return Asis.Parameter_Specification_List;
1046   -- Given a procedure, entry or function call, returns the parameter profile of the called
1047   -- entity.
1048   -- For simple cases, it is like Parameter_Profile (Corresponding_Called_Entity (Call)),
1049   -- but it handles all cases in the same function (i.e. whether it is a procedure or a function,
1050   -- whether the call is from an access to subprogram, etc.)
1051   --
1052   -- Appropriate Element_Kinds:
1053   --    A_Statement
1054   --    An_Expression
1055   -- Appropriate Statement_Kinds:
1056   --    A_Procedure_Call_Statement
1057   --    An_Entry_Call_Statement
1058   -- Appropriate Expression_Kinds:
1059   --    A_Function_Call
1060
1061
1062   type Type_Attribute is (None, Base, Class);
1063   type Profile_Descriptor (Formals_Length : Asis.ASIS_Natural);
1064   type Profile_Access is access Profile_Descriptor;
1065   type Profile_Entry is
1066      record
1067         Access_Form  : Asis.Access_Definition_Kinds;
1068         Attribute    : Type_Attribute;
1069         Name         : Asis.Defining_Name;
1070         Anon_Profile : Profile_Access;
1071      end record;
1072   type Profile_Table is array (Asis.List_Index range <>) of Profile_Entry;
1073   type Profile_Descriptor (Formals_Length : Asis.ASIS_Natural) is
1074      record
1075         Result_Type : Profile_Entry;
1076         Formals     : Profile_Table (1 .. Formals_Length);
1077      end record;
1078
1079   function Types_Profile (Declaration : in Asis.Element)  return Profile_Descriptor;
1080   -- Given a callable entity declaration, returns a description of the profile
1081   -- type Profile_Descriptor:
1082   --    Result_Type describes the result *type* for a function, Nil_Element for other callable entities
1083   --    Formals are (in order of declaration) the *types* of the parameters.
1084   --       Multiple declarations are separated, i.e. "A,B : Integer" yields two entries in the table.
1085   -- type Profile_Entry:
1086   --    Access_Form : for anonymous access parameters: the kind of anonymous access (or Not_An_Access_Definition)
1087   --    Attribute   : The kind of attribute used with the type name, if any
1088   --    Name        : the type name, stripped off of any decoration (access, 'Base, 'Class)
1089   --                  only for non-anonymous access types and anonymous access to object types (otherwise nil_element)
1090   --    Anon_Profile: only for anonymour access to subprograms, the profile pointed to. Since these are supposed to be
1091   --                  pretty (!) rare, we don't care about deallocating the corresponding structure
1092   --                  (yes, it is a deliberate memory leak).
1093   --
1094   -- Note that Non-nil Name and Non-nil Anon_Profile are exclusive, but we didn't put them as variants,
1095   -- because this would have required a discriminant (sometimes evaluated dynamically, preventing aggregates) and
1096   -- would complicate making arrays of Profile_Entry... Too much burden to save a single word.
1097   --
1098   -- Appropriate Element_Kinds:
1099   --   A_Declaration
1100   --
1101   -- Appropriate Declaration_Kinds:
1102   --   Any (generic) callable entity declaration or body, or an anonymous access to subprogram definition
1103
1104
1105   function All_Formals (Profile : Asis.Parameter_Specification_List) return Asis.Defining_Name_List;
1106   -- Builds a list of all Defining_Name in the profile, "flattening" multiple declarations
1107
1108
1109   function Formal_Name (Call : Asis.Element; Actual : Asis.List_Index) return Asis.Defining_Name;
1110   -- Given a procedure, entry or function call, or a generic instantiation, returns the defining name
1111   -- of the formal corresponding to the actual at the given position in the call.
1112   -- Not to be called on an actual which is An_Others_Choice_Specification, since it may correspond to
1113   -- several formals.
1114   -- Note: if the full Parameter_Specification is desired, it is the Enclosing_Element of the Formal_Name
1115   --
1116   -- Returns a nil element if:
1117   --   Actual is greater than the number of actuals in the call
1118   --   The call is to a dispatching operation
1119
1120
1121   function Formal_Name (Assoc : Asis.Association) return Asis.Defining_Name;
1122   -- Same as above, but retrieves the call (or instantiation) and the position given an association
1123   -- Does not work if Assoc has been obtained from a normalized association!
1124
1125
1126   function Matching_Formal_Name (Name : Asis.Defining_Name; Into : Asis.Declaration) return Asis.Defining_Name;
1127   -- Given the defining name of a formal parameter of a callable entity, returns the defining name
1128   -- of the same parameter from the provided other part of the callable entity (spec, body, stub)
1129
1130
1131   function Actual_Expression (Call           : Asis.Element;
1132                               Formal         : Asis.Defining_Name;
1133                               Return_Default : Boolean := True) return Asis.Expression;
1134   -- Given a procedure, entry or function call, or a generic instantiation, returns the value
1135   -- of the actual corresponding to the formal whose defining_identifier is passed.
1136   -- If there is no such actual (the call used the default value) and Return_Default is True,
1137   -- the default expression is returned.
1138   --
1139   -- Returns a nil element if:
1140   --   The call is to a dispatching operation
1141   --   The formal is not from the called entity
1142   --   The call used the default value and Return_Default is False
1143
1144
1145   function Actual_Parameters (Element : Asis.Element; Normalized : Boolean := False) return Asis.Association_List;
1146   -- Returns the actual parameters of a procedure, entry, or function call, or of
1147   -- a generic instantiation
1148
1149
1150   function External_Call_Target (Call : Asis.Element) return Asis.Expression;
1151   -- Returns the prefix of the call that designates the target object
1152   -- of an external call (LRM 9.5 (2..7)).
1153   -- Returns Nil_Element if Element does not designate an external call.
1154   --
1155   -- Appropriate Element_Kinds:
1156   --   An_Expression
1157   --   A_Statement
1158   --
1159   -- Appropriate Expression_Kinds:
1160   --   A_Function_Call
1161   --
1162   -- Appropriate Statement_Kinds:
1163   --   A_Procedure_Call_Statement
1164   --   An_Entry_Call_Statement
1165   --   A_Requeue_Statement
1166   --   A_Requeue_Statement_With_Abort
1167
1168
1169   -------------------------------------------------------------------------------------------------
1170   --                                                                                             --
1171   -- Static evaluator and static properties of ranges and constraints                            --
1172   --                                                                                             --
1173   -------------------------------------------------------------------------------------------------
1174
1175   type Extended_Biggest_Int is range System.Min_Int .. System.Max_Int; -- The best we can do
1176   Not_Static : constant Extended_Biggest_Int := Extended_Biggest_Int'Last;
1177
1178   subtype Biggest_Int              is Extended_Biggest_Int range Extended_Biggest_Int'First .. Not_Static - 1;
1179   subtype Biggest_Natural          is Biggest_Int          range 0 .. Biggest_Int'Last;
1180   subtype Biggest_Positive         is Biggest_Int          range 1 .. Biggest_Int'Last;
1181   subtype Extended_Biggest_Natural is Extended_Biggest_Int range 0 .. Not_Static;
1182
1183   function Biggest_Int_Img (Item : Biggest_Int) return Wide_String;
1184   -- Like Biggest_Int'Wide_Image, without the !*#!! initial space.
1185   -- (avoids depending on the Gnat specific attribute 'Img)
1186
1187   type Extended_Biggest_Int_List is array (Asis.List_Index range <>) of Extended_Biggest_Int;
1188   Nil_Extended_Biggest_Int_List : constant Extended_Biggest_Int_List (1 .. 0) := (others => 0);
1189   function "=" (Left, Right : Extended_Biggest_Int_List) return Boolean;
1190   -- Like the regular "=", except that it returns false if there is a Not_Static in either parameter
1191
1192   type Extended_Biggest_Natural_List is array (Asis.List_Index range <>) of Extended_Biggest_Natural;
1193   Nil_Extended_Biggest_Natural_List : constant Extended_Biggest_Natural_List (1 .. 0) := (others => 0);
1194
1195   type Biggest_Float is digits System.Max_Digits; -- The same for floatting point numbers
1196
1197   function Static_Expression_Value_Image (Expression : Asis.Expression) return Wide_String;
1198   --  Computes the value of Expression if it is a static expression
1199   --  and represents it as a (wide) string. For enumeration expressions, the
1200   --  image of the Pos value of the defining enumeration or character literal
1201   --  corresponding to the  value of the expression is returned.
1202   --  There is NO leading space for positive values!
1203   --
1204   --  For non-static expressions, or expressions that we cannot (yet) evaluate,
1205   --  an empty string is returned.
1206   --
1207   --  Currently implemented:
1208   --  All types:
1209   --     Constant
1210   --     Parenthesized expression
1211   --     'Pred, 'Succ, 'Pos, 'Val, 'First, 'Last
1212   --     'Size if specified by a size clause, or a standard type, or a type derived type from one of these
1213   --     Conversions and qualified expressions
1214   --     Comparison operators
1215   --  Integer: (provided values are within System.Min_Int .. System.Max_Int)
1216   --     Literal
1217   --     Named number
1218   --     + - * / **
1219   --  Real:
1220   --     Literal
1221   --     Named number
1222   --     + - * / **
1223   --  Enumerated:
1224   --     Literal
1225   --  String: (no way to distinguish true "" from non-static expression)
1226   --     Literal
1227   --     &
1228   --
1229   --  Appropriate Element_Kinds:
1230   --     An_Expression
1231   --
1232   --  The specification of this function is derived (and compatible with) the one
1233   --  declared in the GNAT extension ASIS.Extensions
1234   --  (except that we do not have the same set of implemented/non-implemented features)
1235
1236
1237   function Discrete_Static_Expression_Value (Expression : Asis.Expression) return Extended_Biggest_Int;
1238   -- Like Static_Expression_Value_Image, but returns the actual value for static discrete expressions.
1239   -- Returns Not_Static for other cases
1240
1241   function Is_Static_Expression (Expr : Asis.Expression) return Boolean;
1242   -- Returns True if Expr is a static expression
1243   -- TBH: if it is a static expression that Static_Expression_Value_Image is able to evaluate
1244
1245   function Size_Value_Image (Name : Asis.Element) return Wide_String;
1246   -- Name must be the name of a type or object
1247   --
1248   -- For a type:
1249   --   - If a Size clause applies to the type, returns the value from the clause (including
1250   --     when the clause is inherited from some ancestor)
1251   --   - returns the host value for usual predefined types (Boolean, [Wide_[Wide_]Character,
1252   --     [Long_]Integer, [Long_]Float). For a cross-compiler, this may differ from the target!
1253   -- For a stand-alone object:
1254   --   - If a Size clause applies to the object, returns the value from the clause
1255   -- For a record component
1256   --   - if the component has a component clause from a record representation clause, returns
1257   --     the size computed from the component clause
1258   -- For an array component
1259   --   - If there is a Component_Size clause for the type of the array, returns the value from
1260   --     the clause
1261   -- In all other cases:
1262   --   - returns ""
1263   --
1264   -- Appropriate Element_Kinds:
1265   --   A_Defining_Name
1266   --   An_Expression
1267   --
1268   -- Appropriate Expression_Kinds:
1269   --   An_Identifier
1270   --   A_Selected_Component (applies to selector)
1271   --   An_Indexed_Component
1272
1273
1274   function Size_Value (Name : Asis.Expression) return Extended_Biggest_Int;
1275   -- Name must be the name of a type or object
1276   -- Like Size_Value_Image, but returns the actual value.
1277   -- Returns Not_Static if Size_Value_Image is ""
1278
1279
1280   function Constraining_Definition (E : Asis.Element) return Asis.Definition;
1281   -- Like Corresponding_Last_Constraint, except that it does not unwind subtypes at least once,
1282   -- accepts pretty much anything on input, and returns the first definition that imposes a constraint.
1283   --
1284   -- Appropriate Element_Kinds:
1285   --   An_Expression
1286   --   A_Declaration
1287   --   A_Definition
1288   --   A_Defining_Name
1289
1290
1291   function Discrete_Constraining_Bounds (Elem          : Asis.Element;
1292                                          Follow_Access : Boolean := False)
1293                                          return Asis.Element_List;
1294   -- Elem must designate a type or subtype, a variable, a constant, a formal parameter,
1295   -- a range, or a generic formal object.
1296   --
1297   -- Discrete or real type:
1298   -- Returns the expressions that constrain the values of a discrete or real type.
1299   -- Returned list has two elements
1300   -- Enumerated type     : returns (First_Defining_Name, Last_Defining_Name)
1301   -- Signed integer type : returns (First_Expression, Last_Expression)
1302   -- Subtype of modular  : returns (First_Expression, Last_Expression)
1303   -- Modular type        : returns (Nil_Element, Mod_Expression)
1304   -- Real type           : returns (First_Expression, Last_Expression) if range explicitely specified
1305   --                               (Nil_Element, Nil_Element) otherwise
1306   -- The expressions are replaced by Nil_Element if they cannot be determined (formal type, root type)
1307   --
1308   -- Arrays:
1309   -- Returns the expressions that constrain the indexes of an array object or type.
1310   -- Returned list has an even number of elements (First(1), Last (1), First (2), Last (2), ...)
1311   -- Each pair of elements is the same as above
1312   --
1313   -- Access types:
1314   -- Returns the Discrete_Constraining_Bounds of the accessed type if Follow_Access is True,
1315   -- Nil_Element_List otherwise
1316   --
1317   -- Others:
1318   -- Returns Nil_Element_List if the type that applies to Elem is not discrete or array
1319   --
1320   -- Appropriate Element_Kinds:
1321   --   An_Expression
1322   --   A_Declaration
1323   --   A_Definition
1324   --   A_Defining_Name
1325   --
1326   -- Appropriate Expression_Kind:
1327   --   An_Identifier
1328   --   A_Selected_Component (operates on the selector)
1329   --   A_Function_Call (operates on the returned object)
1330   --
1331   -- Appropriate Declaration_Kinds
1332   --   An_Ordinary_Type_Declaration
1333   --   A_Subtype_Declaration
1334   --   A_Task_Type_Declaration
1335   --   A_Protected_Type_Declaration
1336   --   A_Private_Extension_Declaration
1337   --   An_Incomplete_Type_Declaration
1338   --   A_Private_Type_Declaration
1339   --   A_Variable_Declaration
1340   --   A_Constant_Declaration
1341   --   A_Component_Declaration
1342   --   A_Parameter_Specification
1343   --   A_Formal_Object_Declaration
1344   --
1345   -- Appropriate Definition_Kinds
1346   --   A_Discrete_Range
1347   --   A_Constraint
1348   --   A_Type_Definition, appropriate Type_Kinds:
1349   --      An_Unconstrained_Array_Definition
1350   --      A_Constrained_Array_Definition
1351   --   A_Formal_Type_Definition, appropriate Formal_Type_Kinds:
1352   --      A_Formal_Unconstrained_Array_Definition
1353   --      A_Formal_Constrained_Array_Definition   --
1354   -- Returns Element_Kind:
1355   --   Not_An_Element
1356   --   An_Expression
1357   --   A_Defining_Name
1358
1359
1360   function Discrete_Constraining_Values (Elem          : Asis.Element;
1361                                          Follow_Access : Boolean := False)
1362                                          return Extended_Biggest_Int_List;
1363   -- Like Discrete_Constraining_Bounds, but returns the actual values of the bounds
1364   -- if statically determinable.
1365   -- Returns Not_Static if not statically determinable
1366
1367
1368   function Discrete_Constraining_Lengths (Elem          : Asis.Element;
1369                                           Follow_Access : Boolean := False)
1370                                           return Extended_Biggest_Natural_List;
1371   -- Like Discrete_Constraining_Bounds, but returns the number of values in the range instead of
1372   -- the bounds if statically determinable
1373   -- Returns Not_Static (-1) if not statically determinable
1374
1375   function Are_Matching_Subtypes (Left, Right : Asis.Element) return Boolean;
1376   -- Determines if Left and Right are statically matching subtypes, as defined in 4.9.1
1377   -- Implemented for the moment: only the case of two subtypes comming from the same elaboration
1378   --
1379   -- If Left or Right is the name of an object, operates on its Corresponding_Expression_Type.
1380   -- Otherwise, Left and Right are expected to be (sub)type names.
1381   --
1382   -- Appropriate Element_Kinds:
1383   --   An_Expression
1384   --   A_Defining_Name
1385   --   A_Declaration
1386   --   A_Definition
1387   -- Appropriate Expression_Kind:
1388   --   An_Identifier
1389   --   A_Selected_Component (operates on the selector)
1390   --
1391   -- Returns False for any unexpected (or yet unimplemented) element
1392
1393
1394   type Result_Confidence is (Unlikely, Possible, Certain);
1395   type Variable_Overlap  is (Complete, Partial, None);
1396   type Proximity is
1397      record
1398         Confidence : Result_Confidence;
1399         Overlap    : Variable_Overlap;
1400      end record;
1401   Same_Variable       : constant Proximity := (Certain, Complete);
1402   Different_Variables : constant Proximity := (Certain, None);
1403
1404   function Variables_Proximity (Left, Right : Asis.Element) return Proximity;
1405   -- Determines if Left and Right can possibly refer to (part of) the same variables.
1406   -- If Left or Right is not a variable, always returns (Certain, None)
1407   -- Overlap => None is only returned with Confidence => Certain
1408   --
1409   -- Some especially useful results:
1410   -- (Certain, Complete): Statically known to be the same variable
1411   -- (Certain, None)    : Statically known to be different variables
1412   --
1413   -- Appropriate Element_Kinds:
1414   --   An_Expression
1415   --   A_Defining_Name
1416
1417   function Same_Value (Left, Right : Asis.Expression) return Boolean;
1418   -- Determines if Left and Right statically have the same value.
1419   -- Returns True if:
1420   --   Left and Right statically denote the same constant or in parameter
1421   --   or Left and Right are discrete and evaluate statically to the same value.
1422
1423end Thick_Queries;
1424