1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                             E X P _ D I S P                              --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2020, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26--  This package contains routines involved in tagged types and dynamic
27--  dispatching expansion.
28
29with Types; use Types;
30with Uintp; use Uintp;
31
32package Exp_Disp is
33
34   -------------------------------------
35   -- Predefined primitive operations --
36   -------------------------------------
37
38   --  The predefined primitive operations (PPOs) are subprograms generated
39   --  by GNAT for a particular tagged type. Their role is to provide support
40   --  for different Ada language features such as the attribute 'Size or
41   --  handling of dispatching triggers in select statements. PPOs are created
42   --  when a tagged type is expanded or frozen. These subprograms are later
43   --  collected and inserted into the dispatch table of a tagged type at
44   --  fixed positions. Some of the PPOs that manipulate data in tagged objects
45   --  require the generation of thunks.
46
47   --  List of predefined primitive operations
48
49   --    Leading underscores designate reserved names. Bracketed numerical
50   --    values represent dispatch table slot numbers.
51
52   --      _Size (1) - implementation of the attribute 'Size for any tagged
53   --      type. Constructs of the form Prefix'Size are converted into
54   --      Prefix._Size.
55
56   --      TSS_Stream_Read (2) - implementation of the stream attribute Read
57   --      for any tagged type.
58
59   --      TSS_Stream_Write (3) - implementation of the stream attribute Write
60   --      for any tagged type.
61
62   --      TSS_Stream_Input (4) - implementation of the stream attribute Input
63   --      for any tagged type.
64
65   --      TSS_Stream_Output (5) - implementation of the stream attribute
66   --      Output for any tagged type.
67
68   --      Op_Eq (6) - implementation of the equality operator for any non-
69   --      limited tagged type.
70
71   --      _Assign (7) - implementation of the assignment operator for any
72   --      non-limited tagged type.
73
74   --      TSS_Deep_Adjust (8) - implementation of the finalization operation
75   --      Adjust for any non-limited tagged type.
76
77   --      TSS_Deep_Finalize (9) - implementation of the finalization
78   --      operation Finalize for any non-limited tagged type.
79
80   --      Put_Image (10) - implementation of Put_Image attribute for any
81   --      tagged type.
82
83   --      _Disp_Asynchronous_Select (11) - used in the expansion of ATC with
84   --      dispatching triggers. Null implementation for limited interfaces,
85   --      full body generation for types that implement limited interfaces,
86   --      not generated for the rest of the cases. See Expand_N_Asynchronous_
87   --      Select in Exp_Ch9 for more information.
88
89   --      _Disp_Conditional_Select (12) - used in the expansion of conditional
90   --      selects with dispatching triggers. Null implementation for limited
91   --      interfaces, full body generation for types that implement limited
92   --      interfaces, not generated for the rest of the cases. See Expand_N_
93   --      Conditional_Entry_Call in Exp_Ch9 for more information.
94
95   --      _Disp_Get_Prim_Op_Kind (13) - helper routine used in the expansion
96   --      of ATC with dispatching triggers. Null implementation for limited
97   --      interfaces, full body generation for types that implement limited
98   --      interfaces, not generated for the rest of the cases.
99
100   --      _Disp_Get_Task_Id (14) - helper routine used in the expansion of
101   --      Abort, attributes 'Callable and 'Terminated for task interface
102   --      class-wide types. Full body generation for task types, null
103   --      implementation for limited interfaces, not generated for the rest
104   --      of the cases. See Expand_N_Attribute_Reference in Exp_Attr and
105   --      Expand_N_Abort_Statement in Exp_Ch9 for more information.
106
107   --      _Disp_Requeue (15) - used in the expansion of dispatching requeue
108   --      statements. Null implementation is provided for protected, task
109   --      and synchronized interfaces. Protected and task types implementing
110   --      concurrent interfaces receive full bodies. See Expand_N_Requeue_
111   --      Statement in Exp_Ch9 for more information.
112
113   --      _Disp_Timed_Select (16) - used in the expansion of timed selects
114   --      with dispatching triggers. Null implementation for limited
115   --      interfaces, full body generation for types that implement limited
116   --      interfaces, not generated for the rest of the cases. See Expand_N_
117   --      Timed_Entry_Call for more information.
118
119   --  Life cycle of predefined primitive operations
120
121   --      The specifications and bodies of the PPOs are created by
122   --      Make_Predefined_Primitive_Specs and Predefined_Primitive_Bodies
123   --      in Exp_Ch3. The generated specifications are immediately analyzed,
124   --      while the bodies are left as freeze actions to the tagged type for
125   --      which they are created.
126
127   --      PPOs are collected and added to the Primitive_Operations list of
128   --      a type by the regular analysis mechanism.
129
130   --      PPOs are frozen by Exp_Ch3.Predefined_Primitive_Freeze
131
132   --      Thunks for PPOs are created by Make_DT
133
134   --      Dispatch table positions of PPOs are set by Set_All_DT_Position
135
136   --      Calls to PPOs proceed as regular dispatching calls. If the PPO
137   --      has a thunk, a call proceeds as a regular dispatching call with
138   --      a thunk.
139
140   --  Guidelines for addition of new predefined primitive operations
141
142   --      Update the value of constant Max_Predef_Prims in a-tags.ads to
143   --      indicate the new number of PPOs.
144
145   --      Update Exp_Disp.Default_Prim_Op_Position.
146
147   --      Introduce a new predefined name for the new PPO in Snames.ads and
148   --      Snames.adb.
149
150   --      Categorize the new PPO name as predefined by adding an entry in
151   --      Is_Predefined_Dispatching_Operation in Sem_Util and Exp_Cg.
152
153   --      Generate the specification of the new PPO in Make_Predefined_
154   --      Primitive_Spec in Exp_Ch3.adb. The Is_Internal flag of the defining
155   --      identifier of the specification must be set to True.
156
157   --      Generate the body of the new PPO in Predefined_Primitive_Bodies in
158   --      Exp_Ch3.adb. The Is_Internal flag of the defining identifier of the
159   --      specification must be set to True.
160
161   --      If the new PPO requires a thunk, add an entry in Freeze_Subprogram
162   --      in Exp_Ch6.adb.
163
164   --      When generating calls to a PPO, use Find_Prim_Op from exp_util.ads
165   --      to retrieve the entity of the operation directly.
166
167   procedure Apply_Tag_Checks (Call_Node : Node_Id);
168   --  Generate checks required on dispatching calls
169
170   function Building_Static_DT (Typ : Entity_Id) return Boolean;
171   pragma Inline (Building_Static_DT);
172   --  Returns true when building statically allocated dispatch tables
173
174   function Building_Static_Secondary_DT (Typ : Entity_Id) return Boolean;
175   pragma Inline (Building_Static_Secondary_DT);
176   --  Returns true when building statically allocated secondary dispatch
177   --  tables
178
179   procedure Build_Static_Dispatch_Tables (N : Node_Id);
180   --  N is a library level package declaration or package body. Build the
181   --  static dispatch table of the tagged types defined at library level. In
182   --  case of package declarations with private part the generated nodes are
183   --  added at the end of the list of private declarations. Otherwise they are
184   --  added to the end of the list of public declarations. In case of package
185   --  bodies they are added to the end of the list of declarations of the
186   --  package body.
187
188   function Convert_Tag_To_Interface
189     (Typ : Entity_Id; Expr : Node_Id) return Node_Id;
190   pragma Inline (Convert_Tag_To_Interface);
191   --  This function is used in class-wide interface conversions; the expanded
192   --  code generated to convert a tagged object to a class-wide interface type
193   --  involves referencing the tag component containing the secondary dispatch
194   --  table associated with the interface. Given the expression Expr that
195   --  references a tag component, we cannot generate an unchecked conversion
196   --  to leave the expression decorated with the class-wide interface type Typ
197   --  because an unchecked conversion cannot be seen as a no-op. An unchecked
198   --  conversion is conceptually a function call and therefore the RM allows
199   --  the backend to obtain a copy of the value of the actual object and store
200   --  it in some other place (like a register); in such case the interface
201   --  conversion is not equivalent to a displacement of the pointer to the
202   --  interface and any further displacement fails. Although the functionality
203   --  of this function is simple and could be done directly, the purpose of
204   --  this routine is to leave well documented in the sources these
205   --  occurrences.
206
207   --  If Expr is an N_Selected_Component that references a tag generate:
208   --     type ityp is non null access Typ;
209   --     ityp!(Expr'Address).all
210
211   --  if Expr is an N_Function_Call to Ada.Tags.Displace then generate:
212   --     type ityp is non null access Typ;
213   --     ityp!(Expr).all
214
215   function CPP_Num_Prims (Typ : Entity_Id) return Nat;
216   --  Return the number of primitives of the C++ part of the dispatch table.
217   --  For types that are not derivations of CPP types return 0.
218
219   function Elab_Flag_Needed (Typ : Entity_Id) return Boolean;
220   --  Return True if the elaboration of the tagged type Typ is completed at
221   --  run time by the execution of code located in the IP routine and the
222   --  expander must generate an extra elaboration flag to avoid performing
223   --  such elaboration twice.
224
225   procedure Expand_Dispatching_Call (Call_Node : Node_Id);
226   --  Expand the call to the operation through the dispatch table and perform
227   --  the required tag checks when appropriate. For CPP types tag checks are
228   --  not relevant.
229
230   procedure Expand_Interface_Actuals (Call_Node : Node_Id);
231   --  Ada 2005 (AI-251): Displace all the actuals corresponding to class-wide
232   --  interfaces to reference the interface tag of the actual object
233
234   procedure Expand_Interface_Conversion (N : Node_Id);
235   --  Ada 2005 (AI-251): N is a type-conversion node. Displace the pointer
236   --  to the object to give access to the interface tag associated with the
237   --  dispatch table of the target type.
238
239   procedure Expand_Interface_Thunk
240     (Prim       : Node_Id;
241      Thunk_Id   : out Entity_Id;
242      Thunk_Code : out Node_Id;
243      Iface      : Entity_Id);
244   --  Ada 2005 (AI-251): When a tagged type implements abstract interfaces we
245   --  generate additional subprograms (thunks) associated with each primitive
246   --  Prim to have a layout compatible with the C++ ABI. The thunk displaces
247   --  the pointers to the actuals that depend on the controlling type before
248   --  transferring control to the target subprogram. If there is no need to
249   --  generate the thunk then Thunk_Id and Thunk_Code are set to Empty.
250   --  Otherwise they are set to the defining identifier and the subprogram
251   --  body of the generated thunk.
252
253   function Has_CPP_Constructors (Typ : Entity_Id) return Boolean;
254   --  Returns true if the type has CPP constructors
255
256   function Is_Expanded_Dispatching_Call (N : Node_Id) return Boolean;
257   --  Returns true if N is the expanded code of a dispatching call
258
259   function Make_DT (Typ : Entity_Id; N : Node_Id := Empty) return List_Id;
260   --  Expand the declarations for the Dispatch Table. The node N is the
261   --  declaration that forces the generation of the table. It is used to place
262   --  error messages when the declaration leads to the freezing of a given
263   --  primitive operation that has an incomplete non- tagged formal.
264
265   function Make_Disp_Asynchronous_Select_Body
266     (Typ : Entity_Id) return Node_Id;
267   --  Ada 2005 (AI-345): Generate the body of the primitive operation of type
268   --  Typ used for dispatching in asynchronous selects. Generate a null body
269   --  if Typ is an interface type.
270
271   function Make_Disp_Asynchronous_Select_Spec
272     (Typ : Entity_Id) return Node_Id;
273   --  Ada 2005 (AI-345): Generate the specification of the primitive operation
274   --  of type Typ used for dispatching in asynchronous selects.
275
276   function Make_Disp_Conditional_Select_Body
277     (Typ : Entity_Id) return Node_Id;
278   --  Ada 2005 (AI-345): Generate the body of the primitive operation of type
279   --  Typ used for dispatching in conditional selects. Generate a null body
280   --  if Typ is an interface type.
281
282   function Make_Disp_Conditional_Select_Spec
283     (Typ : Entity_Id) return Node_Id;
284   --  Ada 2005 (AI-345): Generate the specification of the primitive operation
285   --  of type Typ used for dispatching in conditional selects.
286
287   function Make_Disp_Get_Prim_Op_Kind_Body
288     (Typ : Entity_Id) return Node_Id;
289   --  Ada 2005 (AI-345): Generate the body of the primitive operation of type
290   --  Typ used for retrieving the callable entity kind during dispatching in
291   --  asynchronous selects. Generate a null body if Typ is an interface type.
292
293   function Make_Disp_Get_Prim_Op_Kind_Spec
294     (Typ : Entity_Id) return Node_Id;
295   --  Ada 2005 (AI-345): Generate the specification of the primitive operation
296   --  of the type Typ use for retrieving the callable entity kind during
297   --  dispatching in asynchronous selects.
298
299   function Make_Disp_Get_Task_Id_Body
300     (Typ : Entity_Id) return Node_Id;
301   --  Ada 2005 (AI-345): Generate body of the primitive operation of type Typ
302   --  used for retrieving the _task_id field of a task interface class- wide
303   --  type. Generate a null body if Typ is an interface or a non-task type.
304
305   function Make_Disp_Get_Task_Id_Spec
306     (Typ : Entity_Id) return Node_Id;
307   --  Ada 2005 (AI-345): Generate the specification of the primitive operation
308   --  of type Typ used for retrieving the _task_id field of a task interface
309   --  class-wide type.
310
311   function Make_Disp_Requeue_Body
312     (Typ : Entity_Id) return Node_Id;
313   --  Ada 2005 (AI05-0030): Generate the body of the primitive operation of
314   --  type Typ used for dispatching on requeue statements. Generate a body
315   --  containing a single null-statement if Typ is an interface type.
316
317   function Make_Disp_Requeue_Spec
318     (Typ : Entity_Id) return Node_Id;
319   --  Ada 2005 (AI05-0030): Generate the specification of the primitive
320   --  operation of type Typ used for dispatching requeue statements.
321
322   function Make_Disp_Timed_Select_Body
323     (Typ : Entity_Id) return Node_Id;
324   --  Ada 2005 (AI-345): Generate the body of the primitive operation of type
325   --  Typ used for dispatching in timed selects. Generate a body containing
326   --  a single null-statement if Typ is an interface type.
327
328   function Make_Disp_Timed_Select_Spec
329     (Typ : Entity_Id) return Node_Id;
330   --  Ada 2005 (AI-345): Generate the specification of the primitive operation
331   --  of type Typ used for dispatching in timed selects.
332
333   function Make_Select_Specific_Data_Table
334     (Typ : Entity_Id) return List_Id;
335   --  Ada 2005 (AI-345): Create and populate the auxiliary table in the TSD
336   --  of Typ used for dispatching in asynchronous, conditional and timed
337   --  selects. Generate code to set the primitive operation kinds and entry
338   --  indexes of primitive operations and primitive wrappers.
339
340   function Make_Tags (Typ : Entity_Id) return List_Id;
341   --  Generate the entities associated with the primary and secondary tags of
342   --  Typ and fill the contents of Access_Disp_Table. In case of library level
343   --  tagged types this routine imports the forward declaration of the tag
344   --  entity, that will be declared and exported by Make_DT.
345
346   function Register_Primitive
347     (Loc     : Source_Ptr;
348      Prim    : Entity_Id) return List_Id;
349   --  Build code to register Prim in the primary or secondary dispatch table.
350   --  If Prim is associated with a secondary dispatch table then generate also
351   --  its thunk and register it in the associated secondary dispatch table.
352   --  In general the dispatch tables are always generated by Make_DT and
353   --  Make_Secondary_DT; this routine is only used in two corner cases:
354   --
355   --    1) To construct the dispatch table of a tagged type whose parent
356   --       is a CPP_Class (see Build_Init_Procedure).
357   --    2) To handle late overriding of dispatching operations (see
358   --       Check_Dispatching_Operation and Make_DT).
359   --
360   --  The caller is responsible for inserting the generated code in the
361   --  proper place.
362
363   procedure Set_All_DT_Position (Typ : Entity_Id);
364   --  Set the DT_Position field for each primitive operation. In the CPP
365   --  Class case check that no pragma CPP_Virtual is missing and that the
366   --  DT_Position are coherent
367
368   procedure Set_CPP_Constructors (Typ : Entity_Id);
369   --  Typ is a CPP_Class type. Create the Init procedures of that type
370   --  required to handle its default and non-default constructors. The
371   --  functions to which pragma CPP_Constructor is applied in the sources
372   --  are functions returning this type, and having an implicit access to the
373   --  target object in its first argument; such implicit argument is explicit
374   --  in the IP procedures built here.
375
376   procedure Set_DT_Position_Value (Prim  : Entity_Id; Value : Uint);
377   --  Set the position of a dispatching primitive its dispatch table. For
378   --  subprogram wrappers propagate the value to the wrapped subprogram.
379
380   procedure Set_DTC_Entity_Value (Tagged_Type : Entity_Id; Prim : Entity_Id);
381   --  Set the definite value of the DTC_Entity value associated with a given
382   --  primitive of a tagged type. For subprogram wrappers, propagate the value
383   --  to the wrapped subprogram.
384
385   procedure Write_DT (Typ : Entity_Id);
386   pragma Export (Ada, Write_DT);
387   --  Debugging procedure (to be called within gdb)
388
389end Exp_Disp;
390