OSDN Git Service

PR fortran/23516
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_attr.ads
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ A T T R                              --
6 --                                                                          --
7 --                                 S p e c                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2005, 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 2,  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 COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 --  Attribute handling is isolated in a separate package to ease the addition
28 --  of implementation defined attributes. Logically this processing belongs
29 --  in chapter 4. See Sem_Ch4 for a description of the relation of the
30 --  Analyze and Resolve routines for expression components.
31
32 --  This spec also documents all GNAT implementation defined pragmas
33
34 with Exp_Tss; use Exp_Tss;
35 with Snames;  use Snames;
36 with Types;   use Types;
37
38 package Sem_Attr is
39
40    type Attribute_Class_Array is array (Attribute_Id) of Boolean;
41    --  Type used to build attribute classification flag arrays
42
43    -----------------------------------------
44    -- Implementation Dependent Attributes --
45    -----------------------------------------
46
47    --  This section describes the implementation dependent attributes
48    --  provided in GNAT, as well as constructing an array of flags
49    --  indicating which attributes these are.
50
51    Attribute_Impl_Def : Attribute_Class_Array := Attribute_Class_Array'(
52
53       ------------------
54       -- Abort_Signal --
55       ------------------
56
57       Attribute_Abort_Signal => True,
58       --  Standard'Abort_Signal (Standard is the only allowed prefix) provides
59       --  the entity for the special exception used to signal task abort or
60       --  asynchronous transfer of control. Normally this attribute should only
61       --  be used in the tasking runtime (it is highly peculiar, and completely
62       --  outside the normal semantics of Ada, for a user program to intercept
63       --  the abort exception).
64
65       ------------------
66       -- Address_Size --
67       ------------------
68
69       Attribute_Address_Size => True,
70       --  Standard'Address_Size (Standard is the only allowed prefix) is
71       --  a static constant giving the number of bits in an Address. It
72       --  is used primarily for constructing the definition of Memory_Size
73       --  in package Standard, but may be freely used in user programs.
74       --  This is a static attribute.
75
76       ---------------
77       -- Asm_Input --
78       ---------------
79
80       Attribute_Asm_Input => True,
81       --  Used only in conjunction with the Asm and Asm_Volatile subprograms
82       --  in package Machine_Code to construct machine instructions. See
83       --  documentation in package Machine_Code in file s-maccod.ads.
84
85       ----------------
86       -- Asm_Output --
87       ----------------
88
89       Attribute_Asm_Output => True,
90       --  Used only in conjunction with the Asm and Asm_Volatile subprograms
91       --  in package Machine_Code to construct machine instructions. See
92       --  documentation in package Machine_Code in file s-maccod.ads.
93
94       ---------------
95       -- AST_Entry --
96       ---------------
97
98       Attribute_AST_Entry => True,
99       --  E'Ast_Entry, where E is a task entry, yields a value of the
100       --  predefined type System.DEC.AST_Handler, that enables the given
101       --  entry to be called when an AST occurs. If the name to which the
102       --  attribute applies has not been specified with the pragma AST_Entry,
103       --  the attribute returns the value No_Ast_Handler, and no AST occurs.
104       --  If the entry is for a task that is not callable (T'Callable False),
105       --  the exception program error is raised. If an AST occurs for an
106       --  entry of a task that is terminated, the program is erroneous.
107       --
108       --  The attribute AST_Entry is supported only in OpenVMS versions
109       --  of GNAT. It will be rejected as illegal in other GNAT versions.
110
111       ---------
112       -- Bit --
113       ---------
114
115       Attribute_Bit => True,
116       --  Obj'Bit, where Obj is any object, yields the bit offset within the
117       --  storage unit (byte) that contains the first bit of storage allocated
118       --  for the object. The attribute value is of type Universal_Integer,
119       --  and is always a non-negative number not exceeding the value of
120       --  System.Storage_Unit.
121       --
122       --  For an object that is a variable or a constant allocated in a
123       --  register, the value is zero. (The use of this attribute does not
124       --  force the allocation of a variable to memory).
125       --
126       --  For an object that is a formal parameter, this attribute applies to
127       --  either the matching actual parameter or to a copy of the matching
128       --  actual parameter.
129       --
130       --  For an access object the value is zero. Note that Obj.all'Bit is
131       --  subject to an Access_Check for the designated object. Similarly
132       --  for a record component X.C'Bit is subject to a discriminant check
133       --  and X(I).Bit and X(I1..I2)'Bit are subject to index checks.
134       --
135       --  This attribute is designed to be compatible with the DEC Ada
136       --  definition and implementation of the Bit attribute.
137
138       ------------------
139       -- Code_Address --
140       ------------------
141
142       Attribute_Code_Address => True,
143       --  The reference subp'Code_Address, where subp is a subprogram entity,
144       --  gives the address of the first generated instruction for the sub-
145       --  program. This is often, but not always the same as the 'Address
146       --  value, which is the address to be used in a call. The differences
147       --  occur in the case of a nested procedure (where Address yields the
148       --  address of the trampoline code used to load the static link), and on
149       --  some systems which use procedure descriptors (in which case Address
150       --  yields the address of the descriptor).
151
152       -----------------------
153       -- Default_Bit_Order --
154       -----------------------
155
156       Attribute_Default_Bit_Order => True,
157       --  Standard'Default_Bit_Order (Standard is the only permissible prefix),
158       --  provides the value System.Default_Bit_Order as a Pos value (0 for
159       --  High_Order_First, 1 for Low_Order_First). This is used to construct
160       --  the definition of Default_Bit_Order in package System. This is a
161       --  static attribute.
162
163       ---------------
164       -- Elab_Body --
165       ---------------
166
167       Attribute_Elab_Body => True,
168       --  This attribute can only be applied to a program unit name. It returns
169       --  the entity for the corresponding elaboration procedure for elabor-
170       --  ating the body of the referenced unit. This is used in the main
171       --  generated elaboration procedure by the binder, and is not normally
172       --  used in any other context, but there may be specialized situations in
173       --  which it is useful to be able to call this elaboration procedure from
174       --  Ada code, e.g. if it is necessary to do selective reelaboration to
175       --  fix some error.
176
177       ---------------
178       -- Elab_Spec --
179       ---------------
180
181       Attribute_Elab_Spec => True,
182       --  This attribute can only be applied to a program unit name. It
183       --  returns the entity for the corresponding elaboration procedure
184       --  for elaborating the spec of the referenced unit. This is used
185       --  in the main generated elaboration procedure by the binder, and
186       --  is not normally used in any other context, but there may be
187       --  specialized situations in which it is useful to be able to
188       --  call this elaboration procedure from Ada code, e.g. if it
189       --  is necessary to do selective reelaboration to fix some error.
190
191       ----------------
192       -- Elaborated --
193       ----------------
194
195       Attribute_Elaborated => True,
196       --  Lunit'Elaborated, where Lunit is a library unit, yields a boolean
197       --  value indicating whether or not the body of the designated library
198       --  unit has been elaborated yet.
199
200       --------------
201       -- Enum_Rep --
202       --------------
203
204       Attribute_Enum_Rep => True,
205       --  For every enumeration subtype S, S'Enum_Rep denotes a function
206       --  with the following specification:
207       --
208       --    function S'Enum_Rep (Arg : S'Base) return universal_integer;
209       --
210       --  The function returns the representation value for the given
211       --  enumeration value. This will be equal to the 'Pos value in the
212       --  absence of an enumeration representation clause. This is a static
213       --  attribute (i.e. the result is static if the argument is static).
214
215       -----------------
216       -- Fixed_Value --
217       -----------------
218
219       Attribute_Fixed_Value => True,
220       --  For every fixed-point type S, S'Fixed_Value denotes a function
221       --  with the following specification:
222       --
223       --    function S'Fixed_Value (Arg : universal_integer) return S;
224       --
225       --  The value returned is the fixed-point value V such that
226       --
227       --    V = Arg * S'Small
228       --
229       --  The effect is thus equivalent to first converting the argument to
230       --  the integer type used to represent S, and then doing an unchecked
231       --  conversion to the fixed-point type. This attribute is primarily
232       --  intended for use in implementation of the input-output functions for
233       --  fixed-point values.
234
235       -----------------------
236       -- Has_Discriminants --
237       -----------------------
238
239       Attribute_Has_Discriminants => True,
240       --  Gtyp'Has_Discriminants, where Gtyp is a generic formal type, yields
241       --  a Boolean value indicating whether or not the actual instantiation
242       --  type has discriminants.
243
244       ---------
245       -- Img --
246       ---------
247
248       Attribute_Img => True,
249       --  The 'Img function is defined for any prefix, P, that denotes an
250       --  object of scalar type T. P'Img is equivalent to T'Image (P). This
251       --  is convenient for debugging. For example:
252       --
253       --     Put_Line ("X = " & X'Img);
254       --
255       --  has the same meaning as the more verbose:
256       --
257       --     Put_Line ("X = " & Temperature_Type'Image (X));
258       --
259       --  where Temperature_Type is the subtype of the object X.
260
261       -------------------
262       -- Integer_Value --
263       -------------------
264
265       Attribute_Integer_Value => True,
266       --  For every integer type S, S'Integer_Value denotes a function
267       --  with the following specification:
268       --
269       --    function S'Integer_Value (Arg : universal_fixed) return S;
270       --
271       --  The value returned is the integer value V, such that
272       --
273       --    Arg = V * fixed-type'Small
274       --
275       --  The effect is thus equivalent to first doing an unchecked convert
276       --  from the fixed-point type to its corresponding implementation type,
277       --  and then converting the result to the target integer type. This
278       --  attribute is primarily intended for use in implementation of the
279       --  standard input-output functions for fixed-point values.
280
281       ------------------
282       -- Machine_Size --
283       ------------------
284
285       Attribute_Machine_Size => True,
286       --  This attribute is identical to the Object_Size attribute. It is
287       --  provided for compatibility with the DEC attribute of this name.
288
289       -----------------------
290       -- Maximum_Alignment --
291       -----------------------
292
293       Attribute_Maximum_Alignment => True,
294       --  Standard'Maximum_Alignment (Standard is the only permissible prefix)
295       --  provides the maximum useful alignment value for the target. This
296       --  is a static value that can be used to specify the alignment for an
297       --  object, guaranteeing that it is properly aligned in all cases. The
298       --  time this is useful is when an external object is imported and its
299       --  alignment requirements are unknown. This is a static attribute.
300
301       --------------------
302       -- Mechanism_Code --
303       --------------------
304
305       Attribute_Mechanism_Code => True,
306       --  function'Mechanism_Code yeilds an integer code for the mechanism
307       --  used for the result of function, and subprogram'Mechanism_Code (n)
308       --  yields the mechanism used for formal parameter number n (a static
309       --  integer value, 1 = first parameter). The code returned is:
310       --
311       --     1 = by copy (value)
312       --     2 = by reference
313       --     3 = by descriptor (default descriptor type)
314       --     4 = by descriptor (UBS  unaligned bit string)
315       --     5 = by descriptor (UBSB aligned bit string with arbitrary bounds)
316       --     6 = by descriptor (UBA  unaligned bit array)
317       --     7 = by descriptor (S    string, also scalar access type parameter)
318       --     8 = by descriptor (SB   string with arbitrary bounds)
319       --     9 = by descriptor (A    contiguous array)
320       --    10 = by descriptor (NCA  non-contiguous array)
321
322       --------------------
323       -- Null_Parameter --
324       --------------------
325
326       Attribute_Null_Parameter => True,
327       --  A reference T'Null_Parameter denotes an (imaginary) object of type or
328       --  subtype T allocated at (machine) address zero. The attribute is
329       --  allowed only as the default expression of a formal parameter, or as
330       --  an actual expression of a subporgram call. In either case, the
331       --  subprogram must be imported.
332       --
333       --  The identity of the object is represented by the address zero in the
334       --  argument list, independent of the passing mechanism (explicit or
335       --  default).
336       --
337       --  The reason that this capability is needed is that for a record or
338       --  other composite object passed by reference, there is no other way of
339       --  specifying that a zero address should be passed.
340
341       -----------------
342       -- Object_Size --
343       -----------------
344
345       Attribute_Object_Size => True,
346       --  Type'Object_Size is the same as Type'Size for all types except
347       --  fixed-point types and discrete types. For fixed-point types and
348       --  discrete types, this attribute gives the size used for default
349       --  allocation of objects and components of the size. See section in
350       --  Einfo ("Handling of type'Size values") for further details.
351
352       -------------------------
353       -- Passed_By_Reference --
354       -------------------------
355
356       Attribute_Passed_By_Reference => True,
357       --  T'Passed_By_Reference for any subtype T returns a boolean value that
358       --  is true if the type is normally passed by reference and false if the
359       --  type is normally passed by copy in calls. For scalar types, the
360       --  result is always False and is static. For non-scalar types, the
361       --  result is non-static (since it is computed by Gigi).
362
363       ------------------
364       -- Range_Length --
365       ------------------
366
367       Attribute_Range_Length => True,
368       --  T'Range_Length for any discrete type T yields the number of values
369       --  represented by the subtype (zero for a null range). The result is
370       --  static for static subtypes. Note that Range_Length applied to the
371       --  index subtype of a one dimensional array always gives the same result
372       --  as Range applied to the array itself. The result is of type universal
373       --  integer.
374
375       ------------------
376       -- Storage_Unit --
377       ------------------
378
379       Attribute_Storage_Unit => True,
380       --  Standard'Storage_Unit (Standard is the only permissible prefix)
381       --  provides the value System.Storage_Unit, and is intended primarily
382       --  for constructing this definition in package System (see note above
383       --  in Default_Bit_Order description). The is a static attribute.
384
385       -----------------
386       -- Target_Name --
387       -----------------
388
389       Attribute_Target_Name => True,
390       --  Standard'Target_Name yields the string identifying the target for the
391       --  compilation, taken from Sdefault.Target_Name.
392
393       ----------------
394       -- To_Address --
395       ----------------
396
397       Attribute_To_Address => True,
398       --  System'To_Address (Address is the only permissible prefix) is a
399       --  function that takes any integer value, and converts it into an
400       --  address value. The semantics is to first convert the integer value to
401       --  type Integer_Address according to normal conversion rules, and then
402       --  to convert this to an address using the same semantics as the
403       --  System.Storage_Elements.To_Address function. The important difference
404       --  is that this is a static attribute so it can be used in
405       --  initializations in preealborate packages.
406
407       ----------------
408       -- Type_Class --
409       ----------------
410
411       Attribute_Type_Class => True,
412       --  T'Type_Class for any type or subtype T yields the value of the type
413       --  class for the full type of T. If T is a generic formal type, then the
414       --  value is the value for the corresponding actual subtype. The value of
415       --  this attribute is of type System.Aux_DEC.Type_Class, which has the
416       --  following definition:
417       --
418       --    type Type_Class is
419       --      (Type_Class_Enumeration,
420       --       Type_Class_Integer,
421       --       Type_Class_Fixed_Point,
422       --       Type_Class_Floating_Point,
423       --       Type_Class_Array,
424       --       Type_Class_Record,
425       --       Type_Class_Access,
426       --       Type_Class_Task,
427       --       Type_Class_Address);
428       --
429       --  Protected types yield the value Type_Class_Task, which thus applies
430       --  to all concurrent types. This attribute is designed to be compatible
431       --  with the DEC Ada attribute of the same name.
432       --
433       --  Note: if pragma Extend_System is used to merge the definitions of
434       --  Aux_DEC into System, then the type Type_Class can be referenced
435       --  as an entity within System, as can its enumeration literals.
436
437       -----------------
438       -- UET_Address --
439       -----------------
440
441       Attribute_UET_Address => True,
442       --  Unit'UET_Address, where Unit is a program unit, yields the address
443       --  of the unit exception table for the specified unit. This is only
444       --  used in the internal implementation of exception handling. See the
445       --  implementation of unit Ada.Exceptions for details on its use.
446
447       ------------------------------
448       -- Universal_Literal_String --
449       ------------------------------
450
451       Attribute_Universal_Literal_String => True,
452       --  The prefix of 'Universal_Literal_String must be a named number. The
453       --  static result is the string consisting of the characters of the
454       --  number as defined in the original source. This allows the user
455       --  program to access the actual text of named numbers without
456       --  intermediate conversions and without the need to enclose the strings
457       --  in quotes (which would preclude their use as numbers). This is used
458       --  internally for the construction of values of the floating-point
459       --  attributes from the file ttypef.ads, but may also be used by user
460       --  programs.
461
462       -------------------------
463       -- Unrestricted_Access --
464       -------------------------
465
466       Attribute_Unrestricted_Access => True,
467       --  The Unrestricted_Access attribute is similar to Access except that
468       --  all accessibility and aliased view checks are omitted. This is very
469       --  much a user-beware attribute. Basically its status is very similar
470       --  to Address, for which it is a desirable replacement where the value
471       --  desired is an access type. In other words, its effect is identical
472       --  to first taking 'Address and then doing an unchecked conversion to
473       --  a desired access type. Note that in GNAT, but not necessarily in
474       --  other implementations, the use of static chains for inner level
475       --  subprograms means that Unrestricted_Access applied to a subprogram
476       --  yields a value that can be called as long as the subprogram is in
477       --  scope (normal Ada 95 accessibility rules restrict this usage).
478
479       ---------------
480       -- VADS_Size --
481       ---------------
482
483       Attribute_VADS_Size => True,
484       --  Typ'VADS_Size yields the Size value typically yielded by some Ada 83
485       --  compilers. The differences between VADS_Size and Size is that for
486       --  scalar types for which no Size has been specified, VADS_Size yields
487       --  the Object_Size rather than the Value_Size. For example, while
488       --  Natural'Size is typically 31, the value of Natural'VADS_Size is 32.
489       --  For all other types, Size and VADS_Size yield the same value.
490
491       ----------------
492       -- Value_Size --
493       ----------------
494
495       Attribute_Value_Size => True,
496       --  Type'Value_Size is the number of bits required to represent value of
497       --  the given subtype. It is the same as Type'Size, but, unlike Size, may
498       --  be set for non-first subtypes. See section in Einfo ("Handling of
499       --  type'Size values") for further details.
500
501       ---------------
502       -- Word_Size --
503       ---------------
504
505       Attribute_Word_Size => True,
506       --  Standard'Word_Size (Standard is the only permissible prefix)
507       --  provides the value System.Word_Size, and is intended primarily
508       --  for constructing this definition in package System (see note above
509       --  in Default_Bit_Order description). This is a static attribute.
510
511       others => False);
512
513    -----------------
514    -- Subprograms --
515    -----------------
516
517    procedure Analyze_Attribute (N : Node_Id);
518    --  Performs bottom up semantic analysis of an attribute. Note that the
519    --  parser has already checked that type returning attributes appear only
520    --  in appropriate contexts (i.e. in subtype marks, or as prefixes for
521    --  other attributes).
522
523    procedure Resolve_Attribute (N : Node_Id; Typ : Entity_Id);
524    --  Performs type resolution of attribute. If the attribute yields a
525    --  universal value, mark its type as that of the context. On the other
526    --  hand, if the context itself is universal (as in T'Val (T'Pos (X)), mark
527    --  the type as being the largest type of that class that can be used at
528    --  run-time. This is correct since either the value gets folded (in which
529    --  case it doesn't matter what type of the class we give if, since the
530    --  folding uses universal arithmetic anyway) or it doesn't get folded (in
531    --  which case it is going to be dealt with at runtime, and the largest type
532    --  is right).
533
534    function Stream_Attribute_Available
535      (Typ          : Entity_Id;
536       Nam          : TSS_Name_Type;
537       Partial_View : Entity_Id := Empty) return Boolean;
538    --  For a limited type Typ, return True iff the given attribute is
539    --  available. For Ada 05, availability is defined by 13.13.2(36/1). For Ada
540    --  95, an attribute is considered to be available if it has been specified
541    --  using an attribute definition clause for the type, or for its full view,
542    --  or for an ancestor of either. Parameter Partial_View is used only
543    --  internally, when checking for an attribute definition clause that is not
544    --  visible (Ada 95 only).
545
546 end Sem_Attr;