1------------------------------------------------------------------------------
2--                                                                          --
3--                            Matreshka Project                             --
4--                                                                          --
5--                               Web Framework                              --
6--                                                                          --
7--                              Tools Component                             --
8--                                                                          --
9------------------------------------------------------------------------------
10--                                                                          --
11-- Copyright © 2015, Vadim Godunko <vgodunko@gmail.com>                     --
12-- All rights reserved.                                                     --
13--                                                                          --
14-- Redistribution and use in source and binary forms, with or without       --
15-- modification, are permitted provided that the following conditions       --
16-- are met:                                                                 --
17--                                                                          --
18--  * Redistributions of source code must retain the above copyright        --
19--    notice, this list of conditions and the following disclaimer.         --
20--                                                                          --
21--  * Redistributions in binary form must reproduce the above copyright     --
22--    notice, this list of conditions and the following disclaimer in the   --
23--    documentation and/or other materials provided with the distribution.  --
24--                                                                          --
25--  * Neither the name of the Vadim Godunko, IE nor the names of its        --
26--    contributors may be used to endorse or promote products derived from  --
27--    this software without specific prior written permission.              --
28--                                                                          --
29-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS      --
30-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT        --
31-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR    --
32-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT     --
33-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,   --
34-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED --
35-- TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR   --
36-- PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF   --
37-- LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING     --
38-- NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS       --
39-- SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.             --
40--                                                                          --
41------------------------------------------------------------------------------
42--  $Revision: 5280 $ $Date: 2015-05-12 19:18:31 +0300 (Tue, 12 May 2015) $
43------------------------------------------------------------------------------
44with Asis.Extensions.Flat_Kinds;
45
46with League.Strings;
47
48with Properties.Declarations.Constant_Declarations;
49with Properties.Declarations.Defining_Expanded_Name;
50with Properties.Declarations.Defining_Names;
51with Properties.Declarations.Element_Iterator_Specification;
52with Properties.Declarations.Function_Declarations;
53with Properties.Declarations.Function_Renaming_Declaration;
54with Properties.Declarations.Loop_Parameter_Specification;
55with Properties.Declarations.Ordinary_Type;
56with Properties.Declarations.Package_Declaration;
57with Properties.Declarations.Package_Instantiation;
58with Properties.Declarations.Private_Type;
59with Properties.Declarations.Procedure_Body_Declarations;
60with Properties.Declarations.Procedure_Declaration;
61with Properties.Definitions.Access_To_Object;
62with Properties.Definitions.Component_Definition;
63with Properties.Definitions.Constrained_Array_Type;
64with Properties.Definitions.Derived_Type;
65with Properties.Definitions.Discriminant_Constraint;
66with Properties.Definitions.Enumeration_Type;
67with Properties.Definitions.Index_Constraint;
68with Properties.Definitions.Range_Attribute;
69with Properties.Definitions.Record_Type;
70with Properties.Definitions.Simple_Expression_Range;
71with Properties.Definitions.Subtype_Indication;
72with Properties.Definitions.Tagged_Record_Type;
73with Properties.Expressions.Allocation;
74with Properties.Expressions.Allocation_From_Subtype;
75with Properties.Expressions.Array_Component_Association;
76with Properties.Expressions.Attribute_Reference;
77with Properties.Expressions.Enumeration_Literal;
78with Properties.Expressions.Explicit_Dereference;
79with Properties.Expressions.Function_Calls;
80with Properties.Expressions.Identifiers;
81with Properties.Expressions.If_Expression;
82with Properties.Expressions.Indexed_Component;
83with Properties.Expressions.Integer_Literal;
84with Properties.Expressions.Named_Array_Aggregate;
85with Properties.Expressions.Null_Literal;
86with Properties.Expressions.Parameter_Association;
87with Properties.Expressions.Parenthesized;
88with Properties.Expressions.Record_Aggregate;
89with Properties.Expressions.Record_Component_Association;
90with Properties.Expressions.Selected_Components;
91with Properties.Expressions.String_Literal;
92with Properties.Expressions.Type_Conversion;
93with Properties.Statements.Assignment_Statement;
94with Properties.Statements.Case_Statement;
95with Properties.Statements.Exit_Statement;
96with Properties.Statements.For_Loop_Statement;
97with Properties.Statements.If_Statement;
98with Properties.Statements.Loop_Statement;
99with Properties.Statements.Null_Statement;
100with Properties.Statements.Procedure_Call_Statement;
101with Properties.Statements.Raise_Statement;
102with Properties.Statements.Return_Statement;
103with Properties.Statements.While_Loop_Statement;
104
105procedure Engines.Registry_All_Actions
106  (Self : in out Engines.Contexts.Context)
107is
108   type Text_Callback is access function
109     (Engine  : access Engines.Contexts.Context;
110      Element : Asis.Element;
111      Name    : Engines.Text_Property) return League.Strings.Universal_String;
112
113   type Action_Item is record
114      Name   : Engines.Text_Property;
115      Kind   : Asis.Extensions.Flat_Kinds.Flat_Element_Kinds;
116      Action : Text_Callback;
117   end record;
118
119   type Boolean_Callback is access function
120     (Engine  : access Engines.Contexts.Context;
121      Element : Asis.Element;
122      Name    : Engines.Boolean_Property) return Boolean;
123
124   type Boolean_Action_Item is record
125      Name   : Engines.Boolean_Property;
126      Kind   : Asis.Extensions.Flat_Kinds.Flat_Element_Kinds;
127      Action : Boolean_Callback;
128   end record;
129
130   type Action_Array is array (Positive range <>) of Action_Item;
131
132   type Action_Range is record
133      Name     : Engines.Text_Property;
134      From, To : Asis.Extensions.Flat_Kinds.Flat_Element_Kinds;
135      Action   : Text_Callback;
136   end record;
137
138   type Range_Array is array (Positive range <>) of Action_Range;
139
140   package F renames Asis.Extensions.Flat_Kinds;
141   package N renames Engines;
142   package P renames Properties;
143
144   Action_List : constant Action_Array :=
145     --  Code
146     ((Name   => N.Code,
147       Kind   => F.A_Use_Package_Clause,
148       Action => P.Statements.Null_Statement.Code'Access),
149      (Name   => N.Code,
150       Kind   => F.A_Constant_Declaration,
151       Action => P.Declarations.Constant_Declarations.Code'Access),
152      (Name   => N.Code,
153       Kind   => F.A_Deferred_Constant_Declaration,
154       Action => P.Statements.Null_Statement.Code'Access),
155      (Name   => N.Code,
156       Kind   => F.A_Function_Declaration,
157       Action => P.Declarations.Function_Declarations.Code'Access),
158      (Name   => N.Code,
159       Kind   => F.An_Ordinary_Type_Declaration,
160       Action => P.Declarations.Ordinary_Type.Code'Access),
161      (Name   => N.Code,
162       Kind   => F.A_Package_Declaration,
163       Action => P.Declarations.Package_Declaration.Code'Access),
164      (Name   => N.Code,
165       Kind   => F.A_Generic_Package_Declaration,
166       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
167      (Name   => N.Code,
168       Kind   => F.A_Package_Renaming_Declaration,  --  FIXME
169       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
170      (Name   => N.Code,
171       Kind   => F.A_Private_Extension_Declaration,
172       Action => P.Statements.Null_Statement.Code'Access),
173      (Name   => N.Code,
174       Kind   => F.A_Private_Type_Declaration,
175       Action => P.Statements.Null_Statement.Code'Access),
176      (Name   => N.Code,
177       Kind   => F.An_Incomplete_Type_Declaration,
178       Action => P.Statements.Null_Statement.Code'Access),
179      (Name   => N.Code,
180       Kind   => F.A_Procedure_Body_Declaration,
181       Action => P.Declarations.Procedure_Body_Declarations.Code'Access),
182      (Name   => N.Code,
183       Kind   => F.A_Function_Body_Declaration,
184       Action => P.Declarations.Procedure_Body_Declarations.Code'Access),
185      (Name   => N.Code,
186       Kind   => F.A_Procedure_Declaration,
187       Action => P.Declarations.Function_Declarations.Code'Access),
188      (Name   => N.Code,
189       Kind   => F.A_Loop_Parameter_Specification,
190       Action =>
191         P.Declarations.Loop_Parameter_Specification.Code'Access),
192      (Name   => N.Code,
193       Kind   => F.An_Element_Iterator_Specification,
194       Action =>
195         P.Declarations.Element_Iterator_Specification.Code'Access),
196      (Name   => N.Code,
197       Kind   => F.A_Subtype_Declaration,
198       Action => P.Statements.Null_Statement.Code'Access),
199      (Name   => N.Code,
200       Kind   => F.A_Variable_Declaration,
201       Action => P.Declarations.Constant_Declarations.Code'Access),
202      (Name   => N.Code,
203       Kind   => F.A_Function_Renaming_Declaration,
204       Action => P.Declarations.Function_Renaming_Declaration.Code'Access),
205      (Name   => N.Code,
206       Kind   => F.A_Defining_Identifier,
207       Action => P.Declarations.Defining_Names.Code'Access),
208      (Name   => N.Code,
209       Kind   => F.A_Defining_Enumeration_Literal,
210       Action => P.Declarations.Defining_Names.Code'Access),
211      (Name   => N.Code,
212       Kind   => F.A_Defining_Expanded_Name,
213       Action => P.Declarations.Defining_Expanded_Name.Code'Access),
214      (Name   => N.Code,
215       Kind   => F.A_Package_Instantiation,
216       Action => P.Declarations.Package_Instantiation.Code'Access),
217      (Name   => N.Code,
218       Kind   => F.An_Enumeration_Type_Definition,
219       Action => P.Definitions.Enumeration_Type.Code'Access),
220      (Name   => N.Code,
221       Kind   => F.A_Subtype_Indication,
222       Action => P.Definitions.Subtype_Indication.Code'Access),
223      (Name   => N.Code,
224       Kind   => F.A_Constrained_Array_Definition,
225       Action => P.Definitions.Constrained_Array_Type.Code'Access),
226      (Name   => N.Code,
227       Kind   => F.An_Unconstrained_Array_Definition,
228       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
229      (Name   => N.Code,
230       Kind   => F.A_Derived_Type_Definition,
231       Action => P.Definitions.Derived_Type.Code'Access),
232      (Name   => N.Code,
233       Kind   => F.A_Derived_Record_Extension_Definition,
234       Action => P.Definitions.Tagged_Record_Type.Code'Access),
235      (Name   => N.Code,
236       Kind   => F.A_Tagged_Record_Type_Definition,
237       Action => P.Definitions.Tagged_Record_Type.Code'Access),
238      (Name   => N.Code,
239       Kind   => F.A_Record_Type_Definition,
240       Action => P.Definitions.Record_Type.Code'Access),
241      (Name   => N.Code,
242       Kind   => F.A_Discriminant_Constraint,
243       Action => P.Definitions.Discriminant_Constraint.Code'Access),
244      (Name   => N.Code,
245       Kind   => F.An_Access_To_Variable,
246       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
247      (Name   => N.Code,
248       Kind   => F.A_Pool_Specific_Access_To_Variable,
249       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
250      (Name   => N.Code,
251       Kind   => F.An_Allocation_From_Qualified_Expression,
252       Action => P.Expressions.Allocation.Code'Access),
253      (Name   => N.Code,
254       Kind   => F.An_Allocation_From_Subtype,
255       Action => P.Expressions.Allocation_From_Subtype.Code'Access),
256      (Name   => N.Code,
257       Kind   => F.An_Enumeration_Literal,
258       Action => P.Expressions.Enumeration_Literal.Code'Access),
259      (Name   => N.Code,
260       Kind   => F.An_Explicit_Dereference,
261       Action => P.Expressions.Explicit_Dereference.Code'Access),
262      (Name   => N.Code,
263       Kind   => F.A_Function_Call,
264       Action => P.Expressions.Function_Calls.Code'Access),
265      (Name   => N.Code,
266       Kind   => F.An_Identifier,
267       Action => P.Expressions.Identifiers.Code'Access),
268      (Name   => N.Code,
269       Kind   => F.An_Indexed_Component,
270       Action => P.Expressions.Indexed_Component.Code'Access),
271      (Name   => N.Code,
272       Kind   => F.An_Integer_Literal,
273       Action => P.Expressions.Integer_Literal.Code'Access),
274      (Name   => N.Code,
275       Kind   => F.A_Real_Literal,
276       Action => P.Expressions.Integer_Literal.Code'Access),
277      (Name   => N.Code,
278       Kind   => F.A_Named_Array_Aggregate,
279       Action => P.Expressions.Named_Array_Aggregate.Code'Access),
280      (Name   => N.Code,
281       Kind   => F.A_Record_Aggregate,
282       Action => P.Expressions.Record_Aggregate.Code'Access),
283      (Name   => N.Code,
284       Kind   => F.An_Array_Component_Association,
285       Action => P.Expressions.Array_Component_Association.Code'Access),
286      (Name   => N.Code,
287       Kind   => F.A_Record_Component_Association,
288       Action => P.Expressions.Record_Component_Association.Code'Access),
289      (Name   => N.Code,
290       Kind   => F.A_Null_Literal,
291       Action => P.Expressions.Null_Literal.Code'Access),
292      (Name   => N.Code,
293       Kind   => F.A_Selected_Component,
294       Action => P.Expressions.Selected_Components.Code'Access),
295      (Name   => N.Code,
296       Kind   => F.A_String_Literal,
297       Action => P.Expressions.String_Literal.Code'Access),
298      (Name   => N.Code,
299       Kind   => F.A_Type_Conversion,
300       Action => P.Expressions.Type_Conversion.Code'Access),
301      (Name   => N.Code,
302       Kind   => F.A_Qualified_Expression,
303       Action => P.Expressions.Type_Conversion.Code'Access),
304      (Name   => N.Code,
305       Kind   => F.A_Parenthesized_Expression,
306       Action => P.Expressions.Parenthesized.Code'Access),
307      (Name   => N.Code,
308       Kind   => F.An_If_Expression,
309       Action => P.Expressions.If_Expression.Code'Access),
310      (Name   => N.Code,
311       Kind   => F.An_Assignment_Statement,
312       Action => P.Statements.Assignment_Statement.Code'Access),
313      (Name   => N.Code,
314       Kind   => F.A_Case_Statement,
315       Action => P.Statements.Case_Statement.Code'Access),
316      (Name   => N.Code,
317       Kind   => F.A_For_Loop_Statement,
318       Action => P.Statements.For_Loop_Statement.Code'Access),
319      (Name   => N.Code,
320       Kind   => F.A_Loop_Statement,
321       Action => P.Statements.Loop_Statement.Code'Access),
322      (Name   => N.Code,
323       Kind   => F.An_If_Statement,
324       Action => P.Statements.If_Statement.Code'Access),
325      (Name   => N.Code,
326       Kind   => F.A_Null_Statement,
327       Action => P.Statements.Null_Statement.Code'Access),
328      (Name   => N.Code,
329       Kind   => F.A_Use_Type_Clause,
330       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
331      (Name   => N.Code,
332       Kind   => F.A_Procedure_Call_Statement,
333       Action => P.Statements.Procedure_Call_Statement.Code'Access),
334      (Name   => N.Code,
335       Kind   => F.A_Return_Statement,
336       Action => P.Statements.Return_Statement.Code'Access),
337      (Name   => N.Code,
338       Kind   => F.An_Exit_Statement,
339       Action => P.Statements.Exit_Statement.Code'Access),
340      (Name   => N.Code,
341       Kind   => F.A_While_Loop_Statement,
342       Action => P.Statements.While_Loop_Statement.Code'Access),
343      (Name   => N.Code,
344       Kind   => F.A_Raise_Statement,
345       Action => P.Statements.Raise_Statement.Code'Access),
346      (Name   => N.Code,
347       Kind   => F.A_With_Clause,
348       Action => P.Statements.Null_Statement.Code'Access),
349
350      (Name   => N.Condition,
351       Kind   => F.An_Element_Iterator_Specification,
352       Action =>
353         P.Declarations.Element_Iterator_Specification.Condition'Access),
354      (Name   => N.Condition,
355       Kind   => F.A_Loop_Parameter_Specification,
356       Action =>
357         P.Declarations.Loop_Parameter_Specification.Condition'Access),
358
359      --  Bounds
360      (Name   => N.Bounds,
361       Kind   => F.A_Constant_Declaration,
362       Action => P.Declarations.Constant_Declarations.Bounds'Access),
363      (Name   => N.Bounds,
364       Kind   => F.A_Variable_Declaration,
365       Action => P.Declarations.Constant_Declarations.Bounds'Access),
366      (Name   => N.Bounds,
367       Kind   => F.A_Component_Declaration,
368       Action => P.Declarations.Constant_Declarations.Bounds'Access),
369      (Name   => N.Bounds,
370       Kind   => F.A_Component_Definition,
371       Action => P.Definitions.Component_Definition.Bounds'Access),
372      (Name   => N.Bounds,
373       Kind   => F.A_Subtype_Indication,
374       Action => P.Definitions.Subtype_Indication.Bounds'Access),
375      (Name   => N.Bounds,
376       Kind   => F.An_Index_Constraint,
377       Action => P.Definitions.Index_Constraint.Bounds'Access),
378      (Name   => N.Bounds,
379       Kind   => F.An_Identifier,
380       Action => P.Expressions.Identifiers.Bounds'Access),
381      (Name   => N.Bounds,
382       Kind   => F.A_Selected_Component,
383       Action => P.Expressions.Selected_Components.Bounds'Access),
384      (Name   => N.Bounds,
385       Kind   => F.An_Ordinary_Type_Declaration,
386       Action => P.Declarations.Ordinary_Type.Code'Access),
387      (Name   => N.Bounds,
388       Kind   => F.A_Constrained_Array_Definition,
389       Action => P.Definitions.Constrained_Array_Type.Bounds'Access),
390      (Name   => N.Bounds,
391       Kind   => F.A_Return_Statement,
392       Action => P.Statements.Return_Statement.Bounds'Access),
393      (Name   => N.Bounds,
394       Kind   => F.A_Derived_Type_Definition,
395       Action => P.Definitions.Derived_Type.Bounds'Access),
396      (Name   => N.Bounds,
397       Kind   => F.A_Parameter_Association,
398       Action => P.Expressions.Parameter_Association.Bounds'Access),
399
400      --  Initialize
401      (Name   => N.Initialize,
402       Kind   => F.A_Constant_Declaration,
403       Action => P.Declarations.Constant_Declarations.Initialize'Access),
404      (Name   => N.Initialize,
405       Kind   => F.A_Component_Declaration,
406       Action => P.Declarations.Constant_Declarations.Initialize'Access),
407      (Name   => N.Initialize,
408       Kind   => F.A_Variable_Declaration,
409       Action => P.Declarations.Constant_Declarations.Initialize'Access),
410      (Name   => N.Initialize,
411       Kind   => F.An_Ordinary_Type_Declaration,
412       Action => P.Declarations.Ordinary_Type.Code'Access),
413      (Name   => N.Initialize,
414       Kind   => F.A_Subtype_Declaration,
415       Action => P.Declarations.Ordinary_Type.Code'Access),
416      (Name   => N.Initialize,
417       Kind   => F.A_Private_Extension_Declaration,
418       Action => P.Declarations.Private_Type.Initialize'Access),
419      (Name   => N.Initialize,
420       Kind   => F.A_Private_Type_Declaration,
421       Action => P.Declarations.Private_Type.Initialize'Access),
422      (Name   => N.Initialize,
423       Kind   => F.A_Loop_Parameter_Specification,
424       Action =>
425         P.Declarations.Loop_Parameter_Specification.Initialize'Access),
426      (Name   => N.Initialize,
427       Kind   => F.An_Element_Iterator_Specification,
428       Action =>
429         P.Declarations.Element_Iterator_Specification.Initialize'Access),
430      (Name   => N.Initialize,
431       Kind   => F.A_Component_Definition,
432       Action => P.Definitions.Component_Definition.Initialize'Access),
433      (Name   => N.Initialize,
434       Kind   => F.A_Derived_Record_Extension_Definition,
435       Action => P.Statements.Null_Statement.Code'Access),  --  Ignore
436      (Name   => N.Initialize,
437       Kind   => F.An_Access_To_Variable,
438       Action => P.Definitions.Access_To_Object.Initialize'Access),
439      (Name   => N.Initialize,
440       Kind   => F.An_Anonymous_Access_To_Constant,
441       Action => P.Definitions.Access_To_Object.Initialize'Access),
442      (Name   => N.Initialize,
443       Kind   => F.A_Constrained_Array_Definition,
444       Action => P.Definitions.Constrained_Array_Type.Initialize'Access),
445      (Name   => N.Initialize,
446       Kind   => F.A_Subtype_Indication,
447       Action => P.Definitions.Subtype_Indication.Initialize'Access),
448      (Name   => N.Initialize,
449       Kind   => F.An_Identifier,
450       Action => P.Expressions.Identifiers.Initialize'Access),
451      (Name   => N.Initialize,
452       Kind   => F.A_Selected_Component,
453       Action => P.Expressions.Selected_Components.Initialize'Access),
454      (Name   => N.Initialize,
455       Kind   => F.A_Derived_Type_Definition,
456       Action => P.Definitions.Derived_Type.Initialize'Access),
457      (Name   => N.Initialize,
458       Kind   => F.A_Record_Type_Definition,
459       Action => P.Definitions.Record_Type.Initialize'Access),
460      (Name    => N.Initialize,
461       Kind    => F.An_Enumeration_Type_Definition,
462       Action  => P.Definitions.Enumeration_Type.Initialize'Access),
463      (Name    => N.Initialize,
464       Kind    => F.A_Signed_Integer_Type_Definition,
465       Action  => P.Definitions.Enumeration_Type.Initialize'Access),
466      (Name    => N.Initialize,
467       Kind    => F.A_Floating_Point_Definition,
468       Action  => P.Definitions.Enumeration_Type.Initialize'Access),
469
470      (Name   => N.Lower,
471       Kind   => F.A_Discrete_Simple_Expression_Range_As_Subtype_Definition,
472       Action => P.Definitions.Simple_Expression_Range.Lower'Access),
473      (Name   => N.Upper,
474       Kind   => F.A_Discrete_Simple_Expression_Range_As_Subtype_Definition,
475       Action => P.Definitions.Simple_Expression_Range.Upper'Access),
476      (Name   => N.Lower,
477       Kind   => F.A_Discrete_Simple_Expression_Range,
478       Action => P.Definitions.Simple_Expression_Range.Lower'Access),
479      (Name   => N.Upper,
480       Kind   => F.A_Discrete_Simple_Expression_Range,
481       Action => P.Definitions.Simple_Expression_Range.Upper'Access),
482      (Name   => N.Lower,
483       Kind   => F.A_Simple_Expression_Range,
484       Action => P.Definitions.Simple_Expression_Range.Lower'Access),
485      (Name   => N.Upper,
486       Kind   => F.A_Simple_Expression_Range,
487       Action => P.Definitions.Simple_Expression_Range.Upper'Access),
488      (Name   => N.Upper,
489       Kind   => F.A_Discrete_Subtype_Indication_As_Subtype_Definition,
490       Action => P.Definitions.Subtype_Indication.Bounds'Access),
491      (Name   => N.Lower,
492       Kind   => F.A_Discrete_Subtype_Indication_As_Subtype_Definition,
493       Action => P.Definitions.Subtype_Indication.Bounds'Access),
494      (Name   => N.Upper,
495       Kind   => F.A_Discrete_Range_Attribute_Reference_As_Subtype_Definition,
496       Action => P.Definitions.Range_Attribute.Upper'Access),
497      (Name   => N.Lower,
498       Kind   => F.A_Discrete_Range_Attribute_Reference_As_Subtype_Definition,
499       Action => P.Definitions.Range_Attribute.Lower'Access),
500      (Name   => N.Upper,
501       Kind   => F.An_Identifier,
502       Action => P.Expressions.Identifiers.Bounds'Access),
503      (Name   => N.Lower,
504       Kind   => F.An_Identifier,
505       Action => P.Expressions.Identifiers.Bounds'Access),
506      (Name   => N.Upper,
507       Kind   => F.An_Ordinary_Type_Declaration,
508       Action => P.Declarations.Ordinary_Type.Code'Access),
509      (Name   => N.Lower,
510       Kind   => F.An_Ordinary_Type_Declaration,
511       Action => P.Declarations.Ordinary_Type.Code'Access),
512      (Name   => N.Lower,
513       Kind   => F.An_Enumeration_Type_Definition,
514       Action => P.Definitions.Enumeration_Type.Lower'Access),
515      (Name   => N.Upper,
516       Kind   => F.An_Enumeration_Type_Definition,
517       Action => P.Definitions.Enumeration_Type.Upper'Access),
518
519      --  Intrinsic_Name
520      (Name   => N.Intrinsic_Name,
521       Kind   => F.A_Function_Declaration,
522       Action => P.Declarations.Function_Declarations.Intrinsic_Name'Access),
523      (Name   => N.Intrinsic_Name,
524       Kind   => F.A_Function_Renaming_Declaration,
525       Action => P.Declarations.Function_Renaming_Declaration
526                   .Intrinsic_Name'Access),
527      (Name   => N.Intrinsic_Name,
528       Kind   => F.A_Procedure_Declaration,
529       Action => P.Declarations.Procedure_Declaration.Intrinsic_Name'Access),
530      (Name   => N.Intrinsic_Name,
531       Kind   => F.An_Identifier,
532       Action => P.Expressions.Identifiers.Intrinsic_Name'Access),
533      (Name   => N.Intrinsic_Name,
534       Kind   => F.A_Selected_Component,
535       Action => P.Expressions.Selected_Components
536                   .Intrinsic_Name'Access)
537     );
538
539   Range_List : constant Range_Array :=
540     ((N.Code,
541       F.An_And_Operator, F.A_Not_Operator,
542       P.Expressions.Identifiers.Code'Access),
543      (N.Code,
544       F.A_Defining_And_Operator, F.A_Defining_Not_Operator,
545       Action => P.Declarations.Defining_Names.Code'Access),
546      (N.Code,
547       F.An_Access_Attribute, F.An_Implementation_Defined_Attribute,
548       P.Expressions.Attribute_Reference.Code'Access),
549      (N.Intrinsic_Name,
550       F.An_Access_Attribute, F.An_Unknown_Attribute,
551       P.Expressions.Attribute_Reference.Intrinsic_Name'Access),
552      (N.Intrinsic_Name,
553       F.An_And_Operator, F.A_Not_Operator,
554       P.Expressions.Identifiers.Intrinsic_Name'Access));
555
556   Boolean_Actions : constant array (Positive range <>) of Boolean_Action_Item
557     :=
558     ((Name   => N.Export,
559       Kind   => F.A_Function_Body_Declaration,
560       Action => P.Declarations.Procedure_Body_Declarations.Export'Access),
561      (Name   => N.Export,
562       Kind   => F.A_Function_Declaration,
563       Action => P.Declarations.Function_Declarations.Export'Access),
564      (Name   => N.Export,
565       Kind   => F.A_Procedure_Body_Declaration,
566       Action => P.Declarations.Procedure_Body_Declarations.Export'Access),
567      (Name   => N.Export,
568       Kind   => F.A_Procedure_Declaration,
569       Action => P.Declarations.Function_Declarations.Export'Access),
570      (Kind    => F.A_Function_Declaration,
571       Name    => N.Is_Dispatching,
572       Action  => P.Declarations.Function_Declarations.Is_Dispatching'Access),
573      (Kind    => F.A_Procedure_Declaration,
574       Name    => N.Is_Dispatching,
575       Action  => P.Declarations.Function_Declarations.Is_Dispatching'Access),
576      (Kind    => F.A_Function_Body_Declaration,
577       Name    => N.Is_Dispatching,
578       Action  =>
579         P.Declarations.Procedure_Body_Declarations.Is_Dispatching'Access),
580      (Kind    => F.A_Procedure_Body_Declaration,
581       Name    => N.Is_Dispatching,
582       Action  =>
583         P.Declarations.Procedure_Body_Declarations.Is_Dispatching'Access),
584      (Kind    => F.A_Selected_Component,
585       Name    => N.Is_Dispatching,
586       Action  => P.Expressions.Selected_Components.Is_Dispatching'Access),
587      (Kind    => F.An_Identifier,
588       Name    => N.Is_Dispatching,
589       Action  => P.Expressions.Identifiers.Is_Dispatching'Access),
590      (Kind   => F.A_Function_Renaming_Declaration,
591       Name   => N.Is_Dispatching,
592       Action => P.Declarations.Function_Renaming_Declaration
593       .Is_Dispatching'Access),
594      (Kind   => F.A_Constant_Declaration,
595       Name   => N.Is_Simple_Ref,
596       Action => P.Declarations.Constant_Declarations.Is_Simple_Ref'Access),
597      (Kind   => F.A_Component_Declaration,
598       Name   => N.Is_Simple_Ref,  --  The same as constant
599       Action => P.Declarations.Constant_Declarations.Is_Simple_Ref'Access),
600      (Kind   => F.A_Variable_Declaration,
601       Name   => N.Is_Simple_Ref,
602       Action => P.Declarations.Constant_Declarations.Is_Simple_Ref'Access),
603      (Kind   => F.A_Subtype_Indication,
604       Name   => N.Is_Simple_Type,
605       Action => P.Definitions.Subtype_Indication.Is_Simple_Type'Access),
606      (Kind    => F.A_Selected_Component,
607       Name    => N.Is_Simple_Type,
608       Action  => P.Expressions.Selected_Components.Is_Dispatching'Access),
609      (Kind    => F.An_Identifier,
610       Name    => N.Is_Simple_Type,
611       Action  => P.Expressions.Identifiers.Is_Dispatching'Access),
612      (Kind    => F.An_Ordinary_Type_Declaration,
613       Name    => N.Is_Simple_Type,
614       Action  => P.Declarations.Ordinary_Type.Is_Simple_Type'Access),
615      (Kind    => F.A_Subtype_Declaration,
616       Name    => N.Is_Simple_Type,
617       Action  => P.Declarations.Ordinary_Type.Is_Simple_Type'Access),
618      (Kind    => F.A_Private_Type_Declaration,
619       Name    => N.Is_Simple_Type,
620       Action  => P.Declarations.Private_Type.Is_Simple_Type'Access),
621      (Kind    => F.An_Enumeration_Type_Definition,
622       Name    => N.Is_Simple_Type,
623       Action  => P.Definitions.Enumeration_Type.Is_Simple_Type'Access),
624      (Kind    => F.A_Signed_Integer_Type_Definition,
625       Name    => N.Is_Simple_Type,
626       Action  => P.Definitions.Enumeration_Type.Is_Simple_Type'Access),
627      (Kind    => F.A_Floating_Point_Definition,
628       Name    => N.Is_Simple_Type,
629       Action  => P.Definitions.Enumeration_Type.Is_Simple_Type'Access),
630      (Kind    => F.An_Access_To_Variable,
631       Name    => N.Is_Simple_Type,
632       Action  => P.Definitions.Enumeration_Type.Is_Simple_Type'Access),
633      (Kind    => F.A_Record_Type_Definition,
634       Name    => N.Is_Simple_Type,
635       Action  => P.Definitions.Constrained_Array_Type.Is_Simple_Type'Access),
636      (Kind    => F.A_Private_Extension_Declaration,
637       Name    => N.Is_Simple_Type,
638       Action  => P.Definitions.Constrained_Array_Type.Is_Simple_Type'Access),
639      (Kind    => F.A_Derived_Type_Definition,
640       Name    => N.Is_Simple_Type,
641       Action  => P.Definitions.Derived_Type.Is_Simple_Type'Access),
642      (Kind    => F.A_Derived_Record_Extension_Definition,
643       Name    => N.Is_Simple_Type,
644       Action  => P.Definitions.Constrained_Array_Type.Is_Simple_Type'Access),
645      (Kind    => F.A_Constrained_Array_Definition,
646       Name    => N.Is_Simple_Type,
647       Action  => P.Definitions.Constrained_Array_Type.Is_Simple_Type'Access),
648      (Kind    => F.An_Unconstrained_Array_Definition,
649       Name    => N.Is_Simple_Type,
650       Action  => P.Definitions.Constrained_Array_Type.Is_Simple_Type'Access));
651
652begin
653   for X of Action_List loop
654      Self.Text.Register_Calculator (X.Kind, X.Name, X.Action);
655   end loop;
656
657   for X of Range_List loop
658      for J in X.From .. X.To loop
659         Self.Text.Register_Calculator (J, X.Name, X.Action);
660      end loop;
661   end loop;
662
663   --  Call_Convention
664   Self.Call_Convention.Register_Calculator
665     (Name   => N.Call_Convention,
666      Kind   => F.A_Function_Call,
667      Action => P.Expressions.Function_Calls.Call_Convention'Access);
668   Self.Call_Convention.Register_Calculator
669     (Name   => N.Call_Convention,
670      Kind   => F.An_Identifier,
671      Action => P.Expressions.Identifiers.Call_Convention'Access);
672   Self.Call_Convention.Register_Calculator
673     (Name   => N.Call_Convention,
674      Kind   => F.A_Function_Declaration,
675      Action => P.Declarations.Function_Declarations.Call_Convention'Access);
676   Self.Call_Convention.Register_Calculator
677     (Name   => N.Call_Convention,
678      Kind   => F.A_Function_Renaming_Declaration,
679      Action => P.Declarations.Function_Renaming_Declaration
680      .Call_Convention'Access);
681   Self.Call_Convention.Register_Calculator
682     (Name   => N.Call_Convention,
683      Kind   => F.A_Procedure_Declaration,
684      Action => P.Declarations.Procedure_Declaration.Call_Convention'Access);
685   Self.Call_Convention.Register_Calculator
686     (Name   => N.Call_Convention,
687      Kind   => F.A_Selected_Component,
688      Action => P.Expressions.Selected_Components.Call_Convention'Access);
689
690   for X in F.An_And_Operator .. F.A_Not_Operator loop
691      Self.Call_Convention.Register_Calculator
692        (Kind    => X,
693         Name    => N.Call_Convention,
694         Action  => P.Expressions.Identifiers.Call_Convention'Access);
695   end loop;
696
697   for X in F.An_Access_Attribute .. F.An_Unknown_Attribute loop
698      Self.Call_Convention.Register_Calculator
699        (Kind    => X,
700         Name    => N.Call_Convention,
701         Action  => P.Expressions.Attribute_Reference.Call_Convention'Access);
702   end loop;
703
704   for X in F.Flat_Declaration_Kinds loop
705      Self.Boolean.Register_Calculator
706        (Kind    => X,
707         Name    => N.Inside_Package,
708         Action  => P.Declarations.Inside_Package'Access);
709   end loop;
710
711   for X in F.An_And_Operator .. F.A_Not_Operator loop
712      Self.Boolean.Register_Calculator
713        (Kind    => X,
714         Name    => N.Is_Dispatching,
715         Action  => P.Expressions.Identifiers.Is_Dispatching'Access);
716   end loop;
717
718   for X of Boolean_Actions loop
719      Self.Boolean.Register_Calculator
720        (Kind    => X.Kind,
721         Name    => X.Name,
722         Action  => X.Action);
723   end loop;
724end Engines.Registry_All_Actions;
725