1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                               S N A M E S                                --
6--                                                                          --
7--                                 B o d y                                  --
8--                                                                          --
9--          Copyright (C) 1992-2012, 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.                                     --
17--                                                                          --
18-- As a special exception under Section 7 of GPL version 3, you are granted --
19-- additional permissions described in the GCC Runtime Library Exception,   --
20-- version 3.1, as published by the Free Software Foundation.               --
21--                                                                          --
22-- You should have received a copy of the GNU General Public License and    --
23-- a copy of the GCC Runtime Library Exception along with this program;     --
24-- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
25-- <http://www.gnu.org/licenses/>.                                          --
26--                                                                          --
27-- GNAT was originally developed  by the GNAT team at  New York University. --
28-- Extensive contributions were provided by Ada Core Technologies Inc.      --
29--                                                                          --
30------------------------------------------------------------------------------
31
32with Debug; use Debug;
33with Opt;   use Opt;
34with Table;
35with Types; use Types;
36
37package body Snames is
38
39   --  Table used to record convention identifiers
40
41   type Convention_Id_Entry is record
42      Name       : Name_Id;
43      Convention : Convention_Id;
44   end record;
45
46   package Convention_Identifiers is new Table.Table (
47     Table_Component_Type => Convention_Id_Entry,
48     Table_Index_Type     => Int,
49     Table_Low_Bound      => 1,
50     Table_Initial        => 50,
51     Table_Increment      => 200,
52     Table_Name           => "Name_Convention_Identifiers");
53
54   --  Table of names to be set by Initialize. Each name is terminated by a
55   --  single #, and the end of the list is marked by a null entry, i.e. by
56   --  two # marks in succession. Note that the table does not include the
57   --  entries for a-z, since these are initialized by Namet itself.
58
59   Preset_Names : constant String :=
60!! TEMPLATE INSERTION POINT
61     "#";
62
63   ---------------------
64   -- Generated Names --
65   ---------------------
66
67   --  This section lists the various cases of generated names which are
68   --  built from existing names by adding unique leading and/or trailing
69   --  upper case letters. In some cases these names are built recursively,
70   --  in particular names built from types may be built from types which
71   --  themselves have generated names. In this list, xxx represents an
72   --  existing name to which identifying letters are prepended or appended,
73   --  and a trailing n represents a serial number in an external name that
74   --  has some semantic significance (e.g. the n'th index type of an array).
75
76   --    xxxA    access type for formal xxx in entry param record   (Exp_Ch9)
77   --    xxxB    tag table for tagged type xxx                      (Exp_Ch3)
78   --    xxxB    task body procedure for task xxx                   (Exp_Ch9)
79   --    xxxD    dispatch table for tagged type xxx                 (Exp_Ch3)
80   --    xxxD    discriminal for discriminant xxx                   (Sem_Ch3)
81   --    xxxDn   n'th discr check function for rec type xxx         (Exp_Ch3)
82   --    xxxE    elaboration boolean flag for task xxx              (Exp_Ch9)
83   --    xxxE    dispatch table pointer type for tagged type xxx    (Exp_Ch3)
84   --    xxxE    parameters for accept body for entry xxx           (Exp_Ch9)
85   --    xxxFn   n'th primitive of a tagged type (named xxx)        (Exp_Ch3)
86   --    xxxJ    tag table type index for tagged type xxx           (Exp_Ch3)
87   --    xxxM    master Id value for access type xxx                (Exp_Ch3)
88   --    xxxP    tag table pointer type for tagged type xxx         (Exp_Ch3)
89   --    xxxP    parameter record type for entry xxx                (Exp_Ch9)
90   --    xxxPA   access to parameter record type for entry xxx      (Exp_Ch9)
91   --    xxxPn   pointer type for n'th primitive of tagged type xxx (Exp_Ch3)
92   --    xxxR    dispatch table pointer for tagged type xxx         (Exp_Ch3)
93   --    xxxT    tag table type for tagged type xxx                 (Exp_Ch3)
94   --    xxxT    literal table for enumeration type xxx             (Sem_Ch3)
95   --    xxxV    type for task value record for task xxx            (Exp_Ch9)
96   --    xxxX    entry index constant                               (Exp_Ch9)
97   --    xxxY    dispatch table type for tagged type xxx            (Exp_Ch3)
98   --    xxxZ    size variable for task xxx                         (Exp_Ch9)
99
100   --  TSS names
101
102   --    xxxDA   deep adjust routine for type xxx                   (Exp_TSS)
103   --    xxxDF   deep finalize routine for type xxx                 (Exp_TSS)
104   --    xxxDI   deep initialize routine for type xxx               (Exp_TSS)
105   --    xxxEQ   composite equality routine for record type xxx     (Exp_TSS)
106   --    xxxFA   PolyORB/DSA From_Any converter for type xxx        (Exp_TSS)
107   --    xxxIP   initialization procedure for type xxx              (Exp_TSS)
108   --    xxxRA   RAS type access routine for type xxx               (Exp_TSS)
109   --    xxxRD   RAS type dereference routine for type xxx          (Exp_TSS)
110   --    xxxRP   Rep to Pos conversion for enumeration type xxx     (Exp_TSS)
111   --    xxxSA   array/slice assignment for controlled comp. arrays (Exp_TSS)
112   --    xxxSI   stream input attribute subprogram for type xxx     (Exp_TSS)
113   --    xxxSO   stream output attribute subprogram for type xxx    (Exp_TSS)
114   --    xxxSR   stream read attribute subprogram for type xxx      (Exp_TSS)
115   --    xxxSW   stream write attribute subprogram for type xxx     (Exp_TSS)
116   --    xxxTA   PolyORB/DSA To_Any converter for type xxx          (Exp_TSS)
117   --    xxxTC   PolyORB/DSA Typecode for type xxx                  (Exp_TSS)
118
119   --  Implicit type names
120
121   --    TxxxT   type of literal table for enumeration type xxx     (Sem_Ch3)
122
123   --  (Note: this list is not complete or accurate ???)
124
125   ----------------------
126   -- Get_Attribute_Id --
127   ----------------------
128
129   function Get_Attribute_Id (N : Name_Id) return Attribute_Id is
130   begin
131      if N = Name_CPU then
132         return Attribute_CPU;
133      elsif N = Name_Dispatching_Domain then
134         return Attribute_Dispatching_Domain;
135      elsif N = Name_Interrupt_Priority then
136         return Attribute_Interrupt_Priority;
137      else
138         return Attribute_Id'Val (N - First_Attribute_Name);
139      end if;
140   end Get_Attribute_Id;
141
142   -----------------------
143   -- Get_Convention_Id --
144   -----------------------
145
146   function Get_Convention_Id (N : Name_Id) return Convention_Id is
147   begin
148      case N is
149         when Name_Ada                   => return Convention_Ada;
150         when Name_Ada_Pass_By_Copy      => return Convention_Ada_Pass_By_Copy;
151         when Name_Ada_Pass_By_Reference => return
152                                              Convention_Ada_Pass_By_Reference;
153         when Name_Assembler             => return Convention_Assembler;
154         when Name_C                     => return Convention_C;
155         when Name_COBOL                 => return Convention_COBOL;
156         when Name_CPP                   => return Convention_CPP;
157         when Name_Fortran               => return Convention_Fortran;
158         when Name_Intrinsic             => return Convention_Intrinsic;
159         when Name_Stdcall               => return Convention_Stdcall;
160         when Name_Stubbed               => return Convention_Stubbed;
161
162         --  If no direct match, then we must have a convention
163         --  identifier pragma that has specified this name.
164
165         when others                     =>
166            for J in 1 .. Convention_Identifiers.Last loop
167               if N = Convention_Identifiers.Table (J).Name then
168                  return Convention_Identifiers.Table (J).Convention;
169               end if;
170            end loop;
171
172            raise Program_Error;
173      end case;
174   end Get_Convention_Id;
175
176   -------------------------
177   -- Get_Convention_Name --
178   -------------------------
179
180   function Get_Convention_Name (C : Convention_Id) return Name_Id is
181   begin
182      case C is
183         when Convention_Ada                   => return Name_Ada;
184         when Convention_Ada_Pass_By_Copy      => return Name_Ada_Pass_By_Copy;
185         when Convention_Ada_Pass_By_Reference =>
186            return Name_Ada_Pass_By_Reference;
187         when Convention_Assembler             => return Name_Assembler;
188         when Convention_C                     => return Name_C;
189         when Convention_COBOL                 => return Name_COBOL;
190         when Convention_CPP                   => return Name_CPP;
191         when Convention_Entry                 => return Name_Entry;
192         when Convention_Fortran               => return Name_Fortran;
193         when Convention_Intrinsic             => return Name_Intrinsic;
194         when Convention_Protected             => return Name_Protected;
195         when Convention_Stdcall               => return Name_Stdcall;
196         when Convention_Stubbed               => return Name_Stubbed;
197      end case;
198   end Get_Convention_Name;
199
200   ---------------------------
201   -- Get_Locking_Policy_Id --
202   ---------------------------
203
204   function Get_Locking_Policy_Id (N : Name_Id) return Locking_Policy_Id is
205   begin
206      return Locking_Policy_Id'Val (N - First_Locking_Policy_Name);
207   end Get_Locking_Policy_Id;
208
209   -------------------
210   -- Get_Pragma_Id --
211   -------------------
212
213   function Get_Pragma_Id (N : Name_Id) return Pragma_Id is
214   begin
215      case N is
216         when Name_CPU                              =>
217            return Pragma_CPU;
218         when Name_Default_Scalar_Storage_Order     =>
219            return Pragma_Default_Scalar_Storage_Order;
220         when Name_Dispatching_Domain               =>
221            return Pragma_Dispatching_Domain;
222         when Name_Fast_Math                        =>
223            return Pragma_Fast_Math;
224         when Name_Interface                        =>
225            return Pragma_Interface;
226         when Name_Interrupt_Priority               =>
227            return Pragma_Interrupt_Priority;
228         when Name_Lock_Free                        =>
229            return Pragma_Lock_Free;
230         when Name_Priority                         =>
231            return Pragma_Priority;
232         when Name_Storage_Size                     =>
233            return Pragma_Storage_Size;
234         when Name_Storage_Unit                     =>
235            return Pragma_Storage_Unit;
236         when First_Pragma_Name .. Last_Pragma_Name =>
237            return Pragma_Id'Val (N - First_Pragma_Name);
238         when others                                =>
239            return Unknown_Pragma;
240      end case;
241   end Get_Pragma_Id;
242
243   ---------------------------
244   -- Get_Queuing_Policy_Id --
245   ---------------------------
246
247   function Get_Queuing_Policy_Id (N : Name_Id) return Queuing_Policy_Id is
248   begin
249      return Queuing_Policy_Id'Val (N - First_Queuing_Policy_Name);
250   end Get_Queuing_Policy_Id;
251
252   ------------------------------------
253   -- Get_Task_Dispatching_Policy_Id --
254   ------------------------------------
255
256   function Get_Task_Dispatching_Policy_Id
257     (N : Name_Id) return Task_Dispatching_Policy_Id
258   is
259   begin
260      return Task_Dispatching_Policy_Id'Val
261        (N - First_Task_Dispatching_Policy_Name);
262   end Get_Task_Dispatching_Policy_Id;
263
264   ----------------
265   -- Initialize --
266   ----------------
267
268   procedure Initialize is
269      P_Index      : Natural;
270      Discard_Name : Name_Id;
271
272   begin
273      P_Index := Preset_Names'First;
274      loop
275         Name_Len := 0;
276         while Preset_Names (P_Index) /= '#' loop
277            Name_Len := Name_Len + 1;
278            Name_Buffer (Name_Len) := Preset_Names (P_Index);
279            P_Index := P_Index + 1;
280         end loop;
281
282         --  We do the Name_Find call to enter the name into the table, but
283         --  we don't need to do anything with the result, since we already
284         --  initialized all the preset names to have the right value (we
285         --  are depending on the order of the names and Preset_Names).
286
287         Discard_Name := Name_Find;
288         P_Index := P_Index + 1;
289         exit when Preset_Names (P_Index) = '#';
290      end loop;
291
292      --  Make sure that number of names in standard table is correct. If this
293      --  check fails, run utility program XSNAMES to construct a new properly
294      --  matching version of the body.
295
296      pragma Assert (Discard_Name = Last_Predefined_Name);
297
298      --  Initialize the convention identifiers table with the standard set of
299      --  synonyms that we recognize for conventions.
300
301      Convention_Identifiers.Init;
302
303      Convention_Identifiers.Append ((Name_Asm,         Convention_Assembler));
304      Convention_Identifiers.Append ((Name_Assembly,    Convention_Assembler));
305
306      Convention_Identifiers.Append ((Name_Default,     Convention_C));
307      Convention_Identifiers.Append ((Name_External,    Convention_C));
308
309      Convention_Identifiers.Append ((Name_C_Plus_Plus, Convention_CPP));
310
311      Convention_Identifiers.Append ((Name_DLL,         Convention_Stdcall));
312      Convention_Identifiers.Append ((Name_Win32,       Convention_Stdcall));
313   end Initialize;
314
315   -----------------------
316   -- Is_Attribute_Name --
317   -----------------------
318
319   function Is_Attribute_Name (N : Name_Id) return Boolean is
320   begin
321      --  Don't consider Name_Elab_Subp_Body to be a valid attribute name
322      --  unless we are working in CodePeer mode.
323
324      return N in First_Attribute_Name .. Last_Attribute_Name
325        and then (CodePeer_Mode or else N /= Name_Elab_Subp_Body);
326   end Is_Attribute_Name;
327
328   ----------------------------------
329   -- Is_Configuration_Pragma_Name --
330   ----------------------------------
331
332   function Is_Configuration_Pragma_Name (N : Name_Id) return Boolean is
333   begin
334      return N in First_Pragma_Name .. Last_Configuration_Pragma_Name
335        or else N = Name_Default_Scalar_Storage_Order
336        or else N = Name_Fast_Math;
337   end Is_Configuration_Pragma_Name;
338
339   ------------------------
340   -- Is_Convention_Name --
341   ------------------------
342
343   function Is_Convention_Name (N : Name_Id) return Boolean is
344   begin
345      --  Check if this is one of the standard conventions
346
347      if N in First_Convention_Name .. Last_Convention_Name
348        or else N = Name_C
349      then
350         return True;
351
352      --  Otherwise check if it is in convention identifier table
353
354      else
355         for J in 1 .. Convention_Identifiers.Last loop
356            if N = Convention_Identifiers.Table (J).Name then
357               return True;
358            end if;
359         end loop;
360
361         return False;
362      end if;
363   end Is_Convention_Name;
364
365   ------------------------------
366   -- Is_Entity_Attribute_Name --
367   ------------------------------
368
369   function Is_Entity_Attribute_Name (N : Name_Id) return Boolean is
370   begin
371      return N in First_Entity_Attribute_Name .. Last_Entity_Attribute_Name;
372   end Is_Entity_Attribute_Name;
373
374   --------------------------------
375   -- Is_Function_Attribute_Name --
376   --------------------------------
377
378   function Is_Function_Attribute_Name (N : Name_Id) return Boolean is
379   begin
380      return N in
381        First_Renamable_Function_Attribute ..
382          Last_Renamable_Function_Attribute;
383   end Is_Function_Attribute_Name;
384
385   ---------------------
386   -- Is_Keyword_Name --
387   ---------------------
388
389   function Is_Keyword_Name (N : Name_Id) return Boolean is
390   begin
391      return Get_Name_Table_Byte (N) /= 0
392        and then (Ada_Version >= Ada_95
393                   or else N not in Ada_95_Reserved_Words)
394        and then (Ada_Version >= Ada_2005
395                   or else N not in Ada_2005_Reserved_Words
396                   or else (Debug_Flag_Dot_DD and then N = Name_Overriding))
397                   --  Accept 'overriding' keywords if -gnatd.D is used,
398                   --  for compatibility with Ada 95 compilers implementing
399                   --  only this Ada 2005 extension.
400        and then (Ada_Version >= Ada_2012
401                   or else N not in Ada_2012_Reserved_Words);
402   end Is_Keyword_Name;
403
404   --------------------------------
405   -- Is_Internal_Attribute_Name --
406   --------------------------------
407
408   function Is_Internal_Attribute_Name (N : Name_Id) return Boolean is
409   begin
410      return
411        N in First_Internal_Attribute_Name .. Last_Internal_Attribute_Name;
412   end Is_Internal_Attribute_Name;
413
414   ----------------------------
415   -- Is_Locking_Policy_Name --
416   ----------------------------
417
418   function Is_Locking_Policy_Name (N : Name_Id) return Boolean is
419   begin
420      return N in First_Locking_Policy_Name .. Last_Locking_Policy_Name;
421   end Is_Locking_Policy_Name;
422
423   -------------------------------------
424   -- Is_Partition_Elaboration_Policy --
425   -------------------------------------
426
427   function Is_Partition_Elaboration_Policy_Name
428     (N : Name_Id) return Boolean
429   is
430   begin
431      return N in First_Partition_Elaboration_Policy_Name ..
432                  Last_Partition_Elaboration_Policy_Name;
433   end Is_Partition_Elaboration_Policy_Name;
434
435   -----------------------------
436   -- Is_Operator_Symbol_Name --
437   -----------------------------
438
439   function Is_Operator_Symbol_Name (N : Name_Id) return Boolean is
440   begin
441      return N in First_Operator_Name .. Last_Operator_Name;
442   end Is_Operator_Symbol_Name;
443
444   --------------------
445   -- Is_Pragma_Name --
446   --------------------
447
448   function Is_Pragma_Name (N : Name_Id) return Boolean is
449   begin
450      return N in First_Pragma_Name .. Last_Pragma_Name
451        or else N = Name_CPU
452        or else N = Name_Default_Scalar_Storage_Order
453        or else N = Name_Dispatching_Domain
454        or else N = Name_Fast_Math
455        or else N = Name_Interface
456        or else N = Name_Interrupt_Priority
457        or else N = Name_Lock_Free
458        or else N = Name_Relative_Deadline
459        or else N = Name_Priority
460        or else N = Name_Storage_Size
461        or else N = Name_Storage_Unit;
462   end Is_Pragma_Name;
463
464   ---------------------------------
465   -- Is_Procedure_Attribute_Name --
466   ---------------------------------
467
468   function Is_Procedure_Attribute_Name (N : Name_Id) return Boolean is
469   begin
470      return N in First_Procedure_Attribute .. Last_Procedure_Attribute;
471   end Is_Procedure_Attribute_Name;
472
473   ----------------------------
474   -- Is_Queuing_Policy_Name --
475   ----------------------------
476
477   function Is_Queuing_Policy_Name (N : Name_Id) return Boolean is
478   begin
479      return N in First_Queuing_Policy_Name .. Last_Queuing_Policy_Name;
480   end Is_Queuing_Policy_Name;
481
482   -------------------------------------
483   -- Is_Task_Dispatching_Policy_Name --
484   -------------------------------------
485
486   function Is_Task_Dispatching_Policy_Name (N : Name_Id) return Boolean is
487   begin
488      return N in First_Task_Dispatching_Policy_Name ..
489                  Last_Task_Dispatching_Policy_Name;
490   end Is_Task_Dispatching_Policy_Name;
491
492   ----------------------------
493   -- Is_Type_Attribute_Name --
494   ----------------------------
495
496   function Is_Type_Attribute_Name (N : Name_Id) return Boolean is
497   begin
498      return N in First_Type_Attribute_Name .. Last_Type_Attribute_Name;
499   end Is_Type_Attribute_Name;
500
501   ----------------------------------
502   -- Record_Convention_Identifier --
503   ----------------------------------
504
505   procedure Record_Convention_Identifier
506     (Id         : Name_Id;
507      Convention : Convention_Id)
508   is
509   begin
510      Convention_Identifiers.Append ((Id, Convention));
511   end Record_Convention_Identifier;
512
513end Snames;
514