OSDN Git Service

2008-03-26 Javier Miranda <miranda@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_attr.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             E X P _ A T T R                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2008, 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 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Exp_Atag; use Exp_Atag;
32 with Exp_Ch2;  use Exp_Ch2;
33 with Exp_Ch9;  use Exp_Ch9;
34 with Exp_Imgv; use Exp_Imgv;
35 with Exp_Pakd; use Exp_Pakd;
36 with Exp_Strm; use Exp_Strm;
37 with Exp_Tss;  use Exp_Tss;
38 with Exp_Util; use Exp_Util;
39 with Exp_VFpt; use Exp_VFpt;
40 with Freeze;   use Freeze;
41 with Gnatvsn;  use Gnatvsn;
42 with Itypes;   use Itypes;
43 with Lib;      use Lib;
44 with Namet;    use Namet;
45 with Nmake;    use Nmake;
46 with Nlists;   use Nlists;
47 with Opt;      use Opt;
48 with Restrict; use Restrict;
49 with Rident;   use Rident;
50 with Rtsfind;  use Rtsfind;
51 with Sem;      use Sem;
52 with Sem_Ch6;  use Sem_Ch6;
53 with Sem_Ch7;  use Sem_Ch7;
54 with Sem_Ch8;  use Sem_Ch8;
55 with Sem_Eval; use Sem_Eval;
56 with Sem_Res;  use Sem_Res;
57 with Sem_Util; use Sem_Util;
58 with Sinfo;    use Sinfo;
59 with Snames;   use Snames;
60 with Stand;    use Stand;
61 with Stringt;  use Stringt;
62 with Targparm; use Targparm;
63 with Tbuild;   use Tbuild;
64 with Ttypes;   use Ttypes;
65 with Uintp;    use Uintp;
66 with Uname;    use Uname;
67 with Validsw;  use Validsw;
68
69 package body Exp_Attr is
70
71    -----------------------
72    -- Local Subprograms --
73    -----------------------
74
75    procedure Compile_Stream_Body_In_Scope
76      (N     : Node_Id;
77       Decl  : Node_Id;
78       Arr   : Entity_Id;
79       Check : Boolean);
80    --  The body for a stream subprogram may be generated outside of the scope
81    --  of the type. If the type is fully private, it may depend on the full
82    --  view of other types (e.g. indices) that are currently private as well.
83    --  We install the declarations of the package in which the type is declared
84    --  before compiling the body in what is its proper environment. The Check
85    --  parameter indicates if checks are to be suppressed for the stream body.
86    --  We suppress checks for array/record reads, since the rule is that these
87    --  are like assignments, out of range values due to uninitialized storage,
88    --  or other invalid values do NOT cause a Constraint_Error to be raised.
89
90    procedure Expand_Access_To_Protected_Op
91      (N    : Node_Id;
92       Pref : Node_Id;
93       Typ  : Entity_Id);
94
95    --  An attribute reference to a protected subprogram is transformed into
96    --  a pair of pointers: one to the object, and one to the operations.
97    --  This expansion is performed for 'Access and for 'Unrestricted_Access.
98
99    procedure Expand_Fpt_Attribute
100      (N    : Node_Id;
101       Pkg  : RE_Id;
102       Nam  : Name_Id;
103       Args : List_Id);
104    --  This procedure expands a call to a floating-point attribute function.
105    --  N is the attribute reference node, and Args is a list of arguments to
106    --  be passed to the function call. Pkg identifies the package containing
107    --  the appropriate instantiation of System.Fat_Gen. Float arguments in Args
108    --  have already been converted to the floating-point type for which Pkg was
109    --  instantiated. The Nam argument is the relevant attribute processing
110    --  routine to be called. This is the same as the attribute name, except in
111    --  the Unaligned_Valid case.
112
113    procedure Expand_Fpt_Attribute_R (N : Node_Id);
114    --  This procedure expands a call to a floating-point attribute function
115    --  that takes a single floating-point argument. The function to be called
116    --  is always the same as the attribute name.
117
118    procedure Expand_Fpt_Attribute_RI (N : Node_Id);
119    --  This procedure expands a call to a floating-point attribute function
120    --  that takes one floating-point argument and one integer argument. The
121    --  function to be called is always the same as the attribute name.
122
123    procedure Expand_Fpt_Attribute_RR (N : Node_Id);
124    --  This procedure expands a call to a floating-point attribute function
125    --  that takes two floating-point arguments. The function to be called
126    --  is always the same as the attribute name.
127
128    procedure Expand_Pred_Succ (N : Node_Id);
129    --  Handles expansion of Pred or Succ attributes for case of non-real
130    --  operand with overflow checking required.
131
132    function Get_Index_Subtype (N : Node_Id) return Entity_Id;
133    --  Used for Last, Last, and Length, when the prefix is an array type.
134    --  Obtains the corresponding index subtype.
135
136    procedure Find_Fat_Info
137      (T        : Entity_Id;
138       Fat_Type : out Entity_Id;
139       Fat_Pkg  : out RE_Id);
140    --  Given a floating-point type T, identifies the package containing the
141    --  attributes for this type (returned in Fat_Pkg), and the corresponding
142    --  type for which this package was instantiated from Fat_Gen. Error if T
143    --  is not a floating-point type.
144
145    function Find_Stream_Subprogram
146      (Typ : Entity_Id;
147       Nam : TSS_Name_Type) return Entity_Id;
148    --  Returns the stream-oriented subprogram attribute for Typ. For tagged
149    --  types, the corresponding primitive operation is looked up, else the
150    --  appropriate TSS from the type itself, or from its closest ancestor
151    --  defining it, is returned. In both cases, inheritance of representation
152    --  aspects is thus taken into account.
153
154    function Get_Stream_Convert_Pragma (T : Entity_Id) return Node_Id;
155    --  Given a type, find a corresponding stream convert pragma that applies to
156    --  the implementation base type of this type (Typ). If found, return the
157    --  pragma node, otherwise return Empty if no pragma is found.
158
159    function Is_Constrained_Packed_Array (Typ : Entity_Id) return Boolean;
160    --  Utility for array attributes, returns true on packed constrained
161    --  arrays, and on access to same.
162
163    function Is_Inline_Floating_Point_Attribute (N : Node_Id) return Boolean;
164    --  Returns true iff the given node refers to an attribute call that
165    --  can be expanded directly by the back end and does not need front end
166    --  expansion. Typically used for rounding and truncation attributes that
167    --  appear directly inside a conversion to integer.
168
169    ----------------------------------
170    -- Compile_Stream_Body_In_Scope --
171    ----------------------------------
172
173    procedure Compile_Stream_Body_In_Scope
174      (N     : Node_Id;
175       Decl  : Node_Id;
176       Arr   : Entity_Id;
177       Check : Boolean)
178    is
179       Installed : Boolean := False;
180       Scop      : constant Entity_Id := Scope (Arr);
181       Curr      : constant Entity_Id := Current_Scope;
182
183    begin
184       if Is_Hidden (Arr)
185         and then not In_Open_Scopes (Scop)
186         and then Ekind (Scop) = E_Package
187       then
188          Push_Scope (Scop);
189          Install_Visible_Declarations (Scop);
190          Install_Private_Declarations (Scop);
191          Installed := True;
192
193          --  The entities in the package are now visible, but the generated
194          --  stream entity must appear in the current scope (usually an
195          --  enclosing stream function) so that itypes all have their proper
196          --  scopes.
197
198          Push_Scope (Curr);
199       end if;
200
201       if Check then
202          Insert_Action (N, Decl);
203       else
204          Insert_Action (N, Decl, Suppress => All_Checks);
205       end if;
206
207       if Installed then
208
209          --  Remove extra copy of current scope, and package itself
210
211          Pop_Scope;
212          End_Package_Scope (Scop);
213       end if;
214    end Compile_Stream_Body_In_Scope;
215
216    -----------------------------------
217    -- Expand_Access_To_Protected_Op --
218    -----------------------------------
219
220    procedure Expand_Access_To_Protected_Op
221      (N    : Node_Id;
222       Pref : Node_Id;
223       Typ  : Entity_Id)
224    is
225       --  The value of the attribute_reference is a record containing two
226       --  fields: an access to the protected object, and an access to the
227       --  subprogram itself. The prefix is a selected component.
228
229       Loc     : constant Source_Ptr := Sloc (N);
230       Agg     : Node_Id;
231       Btyp    : constant Entity_Id := Base_Type (Typ);
232       Sub     : Entity_Id;
233       E_T     : constant Entity_Id := Equivalent_Type (Btyp);
234       Acc     : constant Entity_Id :=
235                   Etype (Next_Component (First_Component (E_T)));
236       Obj_Ref : Node_Id;
237       Curr    : Entity_Id;
238
239       function May_Be_External_Call return Boolean;
240       --  If the 'Access is to a local operation, but appears in a context
241       --  where it may lead to a call from outside the object, we must treat
242       --  this as an external call. Clearly we cannot tell without full
243       --  flow analysis, and a subsequent call that uses this 'Access may
244       --  lead to a bounded error (trying to seize locks twice, e.g.). For
245       --  now we treat 'Access as a potential external call if it is an actual
246       --  in a call to an outside subprogram.
247
248       --------------------------
249       -- May_Be_External_Call --
250       --------------------------
251
252       function May_Be_External_Call return Boolean is
253          Subp : Entity_Id;
254       begin
255          if (Nkind (Parent (N)) = N_Procedure_Call_Statement
256               or else Nkind (Parent (N)) = N_Function_Call)
257             and then Is_Entity_Name (Name (Parent (N)))
258          then
259             Subp := Entity (Name (Parent (N)));
260             return not In_Open_Scopes (Scope (Subp));
261          else
262             return False;
263          end if;
264       end May_Be_External_Call;
265
266    --  Start of processing for Expand_Access_To_Protected_Op
267
268    begin
269       --  Within the body of the protected type, the prefix
270       --  designates a local operation, and the object is the first
271       --  parameter of the corresponding protected body of the
272       --  current enclosing operation.
273
274       if Is_Entity_Name (Pref) then
275          pragma Assert (In_Open_Scopes (Scope (Entity (Pref))));
276
277          if May_Be_External_Call then
278             Sub :=
279               New_Occurrence_Of
280                 (External_Subprogram (Entity (Pref)), Loc);
281          else
282             Sub :=
283               New_Occurrence_Of
284                 (Protected_Body_Subprogram (Entity (Pref)), Loc);
285          end if;
286
287          Curr := Current_Scope;
288          while Scope (Curr) /= Scope (Entity (Pref)) loop
289             Curr := Scope (Curr);
290          end loop;
291
292          --  In case of protected entries the first formal of its Protected_
293          --  Body_Subprogram is the address of the object.
294
295          if Ekind (Curr) = E_Entry then
296             Obj_Ref :=
297                New_Occurrence_Of
298                  (First_Formal
299                    (Protected_Body_Subprogram (Curr)), Loc);
300
301          --  In case of protected subprograms the first formal of its
302          --  Protected_Body_Subprogram is the object and we get its address.
303
304          else
305             Obj_Ref :=
306               Make_Attribute_Reference (Loc,
307                 Prefix =>
308                    New_Occurrence_Of
309                      (First_Formal
310                         (Protected_Body_Subprogram (Curr)), Loc),
311                 Attribute_Name => Name_Address);
312          end if;
313
314       --  Case where the prefix is not an entity name. Find the
315       --  version of the protected operation to be called from
316       --  outside the protected object.
317
318       else
319          Sub :=
320            New_Occurrence_Of
321              (External_Subprogram
322                (Entity (Selector_Name (Pref))), Loc);
323
324          Obj_Ref :=
325            Make_Attribute_Reference (Loc,
326              Prefix => Relocate_Node (Prefix (Pref)),
327                Attribute_Name => Name_Address);
328       end if;
329
330       Agg :=
331         Make_Aggregate (Loc,
332           Expressions =>
333             New_List (
334               Obj_Ref,
335               Unchecked_Convert_To (Acc,
336                 Make_Attribute_Reference (Loc,
337                   Prefix => Sub,
338                   Attribute_Name => Name_Address))));
339
340       Rewrite (N, Agg);
341
342       Analyze_And_Resolve (N, E_T);
343
344       --  For subsequent analysis,  the node must retain its type.
345       --  The backend will replace it with the equivalent type where
346       --  needed.
347
348       Set_Etype (N, Typ);
349    end Expand_Access_To_Protected_Op;
350
351    --------------------------
352    -- Expand_Fpt_Attribute --
353    --------------------------
354
355    procedure Expand_Fpt_Attribute
356      (N    : Node_Id;
357       Pkg  : RE_Id;
358       Nam  : Name_Id;
359       Args : List_Id)
360    is
361       Loc : constant Source_Ptr := Sloc (N);
362       Typ : constant Entity_Id  := Etype (N);
363       Fnm : Node_Id;
364
365    begin
366       --  The function name is the selected component Attr_xxx.yyy where
367       --  Attr_xxx is the package name, and yyy is the argument Nam.
368
369       --  Note: it would be more usual to have separate RE entries for each
370       --  of the entities in the Fat packages, but first they have identical
371       --  names (so we would have to have lots of renaming declarations to
372       --  meet the normal RE rule of separate names for all runtime entities),
373       --  and second there would be an awful lot of them!
374
375       Fnm :=
376         Make_Selected_Component (Loc,
377           Prefix        => New_Reference_To (RTE (Pkg), Loc),
378           Selector_Name => Make_Identifier (Loc, Nam));
379
380       --  The generated call is given the provided set of parameters, and then
381       --  wrapped in a conversion which converts the result to the target type
382       --  We use the base type as the target because a range check may be
383       --  required.
384
385       Rewrite (N,
386         Unchecked_Convert_To (Base_Type (Etype (N)),
387           Make_Function_Call (Loc,
388             Name                   => Fnm,
389             Parameter_Associations => Args)));
390
391       Analyze_And_Resolve (N, Typ);
392    end Expand_Fpt_Attribute;
393
394    ----------------------------
395    -- Expand_Fpt_Attribute_R --
396    ----------------------------
397
398    --  The single argument is converted to its root type to call the
399    --  appropriate runtime function, with the actual call being built
400    --  by Expand_Fpt_Attribute
401
402    procedure Expand_Fpt_Attribute_R (N : Node_Id) is
403       E1  : constant Node_Id    := First (Expressions (N));
404       Ftp : Entity_Id;
405       Pkg : RE_Id;
406    begin
407       Find_Fat_Info (Etype (E1), Ftp, Pkg);
408       Expand_Fpt_Attribute
409         (N, Pkg, Attribute_Name (N),
410          New_List (Unchecked_Convert_To (Ftp, Relocate_Node (E1))));
411    end Expand_Fpt_Attribute_R;
412
413    -----------------------------
414    -- Expand_Fpt_Attribute_RI --
415    -----------------------------
416
417    --  The first argument is converted to its root type and the second
418    --  argument is converted to standard long long integer to call the
419    --  appropriate runtime function, with the actual call being built
420    --  by Expand_Fpt_Attribute
421
422    procedure Expand_Fpt_Attribute_RI (N : Node_Id) is
423       E1  : constant Node_Id   := First (Expressions (N));
424       Ftp : Entity_Id;
425       Pkg : RE_Id;
426       E2  : constant Node_Id   := Next (E1);
427    begin
428       Find_Fat_Info (Etype (E1), Ftp, Pkg);
429       Expand_Fpt_Attribute
430         (N, Pkg, Attribute_Name (N),
431          New_List (
432            Unchecked_Convert_To (Ftp, Relocate_Node (E1)),
433            Unchecked_Convert_To (Standard_Integer, Relocate_Node (E2))));
434    end Expand_Fpt_Attribute_RI;
435
436    -----------------------------
437    -- Expand_Fpt_Attribute_RR --
438    -----------------------------
439
440    --  The two arguments are converted to their root types to call the
441    --  appropriate runtime function, with the actual call being built
442    --  by Expand_Fpt_Attribute
443
444    procedure Expand_Fpt_Attribute_RR (N : Node_Id) is
445       E1  : constant Node_Id   := First (Expressions (N));
446       Ftp : Entity_Id;
447       Pkg : RE_Id;
448       E2  : constant Node_Id   := Next (E1);
449    begin
450       Find_Fat_Info (Etype (E1), Ftp, Pkg);
451       Expand_Fpt_Attribute
452         (N, Pkg, Attribute_Name (N),
453          New_List (
454            Unchecked_Convert_To (Ftp, Relocate_Node (E1)),
455            Unchecked_Convert_To (Ftp, Relocate_Node (E2))));
456    end Expand_Fpt_Attribute_RR;
457
458    ----------------------------------
459    -- Expand_N_Attribute_Reference --
460    ----------------------------------
461
462    procedure Expand_N_Attribute_Reference (N : Node_Id) is
463       Loc   : constant Source_Ptr   := Sloc (N);
464       Typ   : constant Entity_Id    := Etype (N);
465       Btyp  : constant Entity_Id    := Base_Type (Typ);
466       Pref  : constant Node_Id      := Prefix (N);
467       Exprs : constant List_Id      := Expressions (N);
468       Id    : constant Attribute_Id := Get_Attribute_Id (Attribute_Name (N));
469
470       procedure Rewrite_Stream_Proc_Call (Pname : Entity_Id);
471       --  Rewrites a stream attribute for Read, Write or Output with the
472       --  procedure call. Pname is the entity for the procedure to call.
473
474       ------------------------------
475       -- Rewrite_Stream_Proc_Call --
476       ------------------------------
477
478       procedure Rewrite_Stream_Proc_Call (Pname : Entity_Id) is
479          Item       : constant Node_Id   := Next (First (Exprs));
480          Formal     : constant Entity_Id := Next_Formal (First_Formal (Pname));
481          Formal_Typ : constant Entity_Id := Etype (Formal);
482          Is_Written : constant Boolean   := (Ekind (Formal) /= E_In_Parameter);
483
484       begin
485          --  The expansion depends on Item, the second actual, which is
486          --  the object being streamed in or out.
487
488          --  If the item is a component of a packed array type, and
489          --  a conversion is needed on exit, we introduce a temporary to
490          --  hold the value, because otherwise the packed reference will
491          --  not be properly expanded.
492
493          if Nkind (Item) = N_Indexed_Component
494            and then Is_Packed (Base_Type (Etype (Prefix (Item))))
495            and then Base_Type (Etype (Item)) /= Base_Type (Formal_Typ)
496            and then Is_Written
497          then
498             declare
499                Temp : constant Entity_Id :=
500                         Make_Defining_Identifier
501                           (Loc, New_Internal_Name ('V'));
502                Decl : Node_Id;
503                Assn : Node_Id;
504
505             begin
506                Decl :=
507                  Make_Object_Declaration (Loc,
508                    Defining_Identifier => Temp,
509                    Object_Definition    =>
510                      New_Occurrence_Of (Formal_Typ, Loc));
511                Set_Etype (Temp, Formal_Typ);
512
513                Assn :=
514                  Make_Assignment_Statement (Loc,
515                    Name => New_Copy_Tree (Item),
516                    Expression =>
517                      Unchecked_Convert_To
518                        (Etype (Item), New_Occurrence_Of (Temp, Loc)));
519
520                Rewrite (Item, New_Occurrence_Of (Temp, Loc));
521                Insert_Actions (N,
522                  New_List (
523                    Decl,
524                    Make_Procedure_Call_Statement (Loc,
525                      Name => New_Occurrence_Of (Pname, Loc),
526                      Parameter_Associations => Exprs),
527                    Assn));
528
529                Rewrite (N, Make_Null_Statement (Loc));
530                return;
531             end;
532          end if;
533
534          --  For the class-wide dispatching cases, and for cases in which
535          --  the base type of the second argument matches the base type of
536          --  the corresponding formal parameter (that is to say the stream
537          --  operation is not inherited), we are all set, and can use the
538          --  argument unchanged.
539
540          --  For all other cases we do an unchecked conversion of the second
541          --  parameter to the type of the formal of the procedure we are
542          --  calling. This deals with the private type cases, and with going
543          --  to the root type as required in elementary type case.
544
545          if not Is_Class_Wide_Type (Entity (Pref))
546            and then not Is_Class_Wide_Type (Etype (Item))
547            and then Base_Type (Etype (Item)) /= Base_Type (Formal_Typ)
548          then
549             Rewrite (Item,
550               Unchecked_Convert_To (Formal_Typ, Relocate_Node (Item)));
551
552             --  For untagged derived types set Assignment_OK, to prevent
553             --  copies from being created when the unchecked conversion
554             --  is expanded (which would happen in Remove_Side_Effects
555             --  if Expand_N_Unchecked_Conversion were allowed to call
556             --  Force_Evaluation). The copy could violate Ada semantics
557             --  in cases such as an actual that is an out parameter.
558             --  Note that this approach is also used in exp_ch7 for calls
559             --  to controlled type operations to prevent problems with
560             --  actuals wrapped in unchecked conversions.
561
562             if Is_Untagged_Derivation (Etype (Expression (Item))) then
563                Set_Assignment_OK (Item);
564             end if;
565          end if;
566
567          --  And now rewrite the call
568
569          Rewrite (N,
570            Make_Procedure_Call_Statement (Loc,
571              Name => New_Occurrence_Of (Pname, Loc),
572              Parameter_Associations => Exprs));
573
574          Analyze (N);
575       end Rewrite_Stream_Proc_Call;
576
577    --  Start of processing for Expand_N_Attribute_Reference
578
579    begin
580       --  Do required validity checking, if enabled. Do not apply check to
581       --  output parameters of an Asm instruction, since the value of this
582       --  is not set till after the attribute has been elaborated.
583
584       if Validity_Checks_On and then Validity_Check_Operands
585         and then Id /= Attribute_Asm_Output
586       then
587          declare
588             Expr : Node_Id;
589          begin
590             Expr := First (Expressions (N));
591             while Present (Expr) loop
592                Ensure_Valid (Expr);
593                Next (Expr);
594             end loop;
595          end;
596       end if;
597
598       --  Remaining processing depends on specific attribute
599
600       case Id is
601
602       ------------
603       -- Access --
604       ------------
605
606       when Attribute_Access              |
607            Attribute_Unchecked_Access    |
608            Attribute_Unrestricted_Access =>
609
610          Access_Cases : declare
611             Btyp_DDT   : constant Entity_Id := Directly_Designated_Type (Btyp);
612             Ref_Object : constant Node_Id := Get_Referenced_Object (Pref);
613
614          begin
615             --  In order to improve the text of error messages, the designated
616             --  type of access-to-subprogram itypes is set by the semantics as
617             --  the associated subprogram entity (see sem_attr). Now we replace
618             --  such node with the proper E_Subprogram_Type itype.
619
620             if Id = Attribute_Unrestricted_Access
621               and then Is_Subprogram (Directly_Designated_Type (Typ))
622             then
623                --  The following assertion ensures that this special management
624                --  is done only for "Address!(Prim'Unrestricted_Access)" nodes.
625                --  At this stage other cases in which the designated type is
626                --  still a subprogram (instead of an E_Subprogram_Type) are
627                --  wrong because the semantics must have overriden the type of
628                --  the node with the type imposed by the context.
629
630                pragma Assert (Nkind (Parent (N)) = N_Unchecked_Type_Conversion
631                  and then Etype (Parent (N)) = RTE (RE_Address));
632
633                declare
634                   Subp : constant Entity_Id := Directly_Designated_Type (Typ);
635
636                   Extra      : Entity_Id := Empty;
637                   New_Formal : Entity_Id;
638                   Old_Formal : Entity_Id := First_Formal (Subp);
639                   Subp_Typ   : Entity_Id;
640
641                begin
642                   Subp_Typ := Create_Itype (E_Subprogram_Type, N);
643                   Set_Etype (Subp_Typ, Etype (Subp));
644                   Set_Returns_By_Ref (Subp_Typ, Returns_By_Ref (Subp));
645
646                   if Present (Old_Formal) then
647                      New_Formal := New_Copy (Old_Formal);
648                      Set_First_Entity (Subp_Typ, New_Formal);
649
650                      loop
651                         Set_Scope (New_Formal, Subp_Typ);
652
653                         --  Handle itypes
654
655                         if Is_Itype (Etype (New_Formal)) then
656                            Extra := New_Copy (Etype (New_Formal));
657
658                            if Ekind (Extra) = E_Record_Subtype
659                              or else Ekind (Extra) = E_Class_Wide_Subtype
660                            then
661                               Set_Cloned_Subtype (Extra,
662                                 Etype (New_Formal));
663                            end if;
664
665                            Set_Etype (New_Formal, Extra);
666                            Set_Scope (Etype (New_Formal), Subp_Typ);
667                         end if;
668
669                         Extra := New_Formal;
670                         Next_Formal (Old_Formal);
671                         exit when No (Old_Formal);
672
673                         Set_Next_Entity (New_Formal,
674                           New_Copy (Old_Formal));
675                         Next_Entity (New_Formal);
676                      end loop;
677
678                      Set_Next_Entity (New_Formal, Empty);
679                      Set_Last_Entity (Subp_Typ, Extra);
680                   end if;
681
682                   --  Now that the explicit formals have been duplicated,
683                   --  any extra formals needed by the subprogram must be
684                   --  created.
685
686                   if Present (Extra) then
687                      Set_Extra_Formal (Extra, Empty);
688                   end if;
689
690                   Create_Extra_Formals (Subp_Typ);
691                   Set_Directly_Designated_Type (Typ, Subp_Typ);
692
693                   --  Complete decoration of access-to-subprogram itype to
694                   --  indicate to the backend that this itype corresponds to
695                   --  a statically allocated dispatch table.
696
697                   --  ??? more comments on structure here, three level parent
698                   --  references are worrisome!
699
700                   if Nkind (Ref_Object) in N_Has_Entity
701                     and then Is_Dispatching_Operation (Entity (Ref_Object))
702                     and then Present (Parent (Parent (N)))
703                     and then Nkind (Parent (Parent (N))) = N_Aggregate
704                     and then Present (Parent (Parent (Parent (N))))
705                   then
706                      declare
707                         P    : constant Node_Id :=
708                                  Parent (Parent (Parent (N)));
709                         Prim : constant Entity_Id := Entity (Ref_Object);
710
711                      begin
712                         Set_Is_Static_Dispatch_Table_Entity (Typ,
713                            (Is_Predefined_Dispatching_Operation (Prim)
714                               and then Nkind (P) = N_Object_Declaration
715                               and then Is_Static_Dispatch_Table_Entity
716                                          (Defining_Identifier (P)))
717                           or else
718                            (not Is_Predefined_Dispatching_Operation (Prim)
719                               and then Nkind (P) = N_Aggregate
720                               and then Present (Parent (P))
721                               and then Nkind (Parent (P))
722                                          = N_Object_Declaration
723                               and then Is_Static_Dispatch_Table_Entity
724                                          (Defining_Identifier (Parent (P)))));
725                      end;
726                   end if;
727                end;
728             end if;
729
730             if Is_Access_Protected_Subprogram_Type (Btyp) then
731                Expand_Access_To_Protected_Op (N, Pref, Typ);
732
733             --  If prefix is a type name, this is a reference to the current
734             --  instance of the type, within its initialization procedure.
735
736             elsif Is_Entity_Name (Pref)
737               and then Is_Type (Entity (Pref))
738             then
739                declare
740                   Par    : Node_Id;
741                   Formal : Entity_Id;
742
743                begin
744                   --  If the current instance name denotes a task type, then
745                   --  the access attribute is rewritten to be the name of the
746                   --  "_task" parameter associated with the task type's task
747                   --  procedure. An unchecked conversion is applied to ensure
748                   --  a type match in cases of expander-generated calls (e.g.
749                   --  init procs).
750
751                   if Is_Task_Type (Entity (Pref)) then
752                      Formal :=
753                        First_Entity (Get_Task_Body_Procedure (Entity (Pref)));
754                      while Present (Formal) loop
755                         exit when Chars (Formal) = Name_uTask;
756                         Next_Entity (Formal);
757                      end loop;
758
759                      pragma Assert (Present (Formal));
760
761                      Rewrite (N,
762                        Unchecked_Convert_To (Typ,
763                          New_Occurrence_Of (Formal, Loc)));
764                      Set_Etype (N, Typ);
765
766                      --  The expression must appear in a default expression,
767                      --  (which in the initialization procedure is the
768                      --  right-hand side of an assignment), and not in a
769                      --  discriminant constraint.
770
771                   else
772                      Par := Parent (N);
773                      while Present (Par) loop
774                         exit when Nkind (Par) = N_Assignment_Statement;
775
776                         if Nkind (Par) = N_Component_Declaration then
777                            return;
778                         end if;
779
780                         Par := Parent (Par);
781                      end loop;
782
783                      if Present (Par) then
784                         Rewrite (N,
785                           Make_Attribute_Reference (Loc,
786                             Prefix => Make_Identifier (Loc, Name_uInit),
787                             Attribute_Name  => Attribute_Name (N)));
788
789                         Analyze_And_Resolve (N, Typ);
790                      end if;
791                   end if;
792                end;
793
794             --  If the prefix of an Access attribute is a dereference of an
795             --  access parameter (or a renaming of such a dereference) and
796             --  the context is a general access type (but not an anonymous
797             --  access type), then rewrite the attribute as a conversion of
798             --  the access parameter to the context access type. This will
799             --  result in an accessibility check being performed, if needed.
800
801             --    (X.all'Access => Acc_Type (X))
802
803             --  Note: Limit the expansion of an attribute applied to a
804             --  dereference of an access parameter so that it's only done
805             --  for 'Access. This fixes a problem with 'Unrestricted_Access
806             --  that leads to errors in the case where the attribute type
807             --  is access-to-variable and the access parameter is
808             --  access-to-constant. The conversion is only done to get
809             --  accessibility checks, so it makes sense to limit it to
810             --  'Access.
811
812             elsif Nkind (Ref_Object) = N_Explicit_Dereference
813               and then Is_Entity_Name (Prefix (Ref_Object))
814               and then Ekind (Btyp) = E_General_Access_Type
815               and then Ekind (Entity (Prefix (Ref_Object))) in Formal_Kind
816               and then Ekind (Etype (Entity (Prefix (Ref_Object))))
817                          = E_Anonymous_Access_Type
818               and then Present (Extra_Accessibility
819                                 (Entity (Prefix (Ref_Object))))
820             then
821                Rewrite (N,
822                  Convert_To (Typ, New_Copy_Tree (Prefix (Ref_Object))));
823                Analyze_And_Resolve (N, Typ);
824
825             --  Ada 2005 (AI-251): If the designated type is an interface we
826             --  add an implicit conversion to force the displacement of the
827             --  pointer to reference the secondary dispatch table.
828
829             elsif Is_Interface (Btyp_DDT)
830               and then (Comes_From_Source (N)
831                          or else Comes_From_Source (Ref_Object)
832                          or else (Nkind (Ref_Object) in N_Has_Chars
833                                    and then Chars (Ref_Object) = Name_uInit))
834             then
835                if Nkind (Ref_Object) /= N_Explicit_Dereference then
836
837                   --  No implicit conversion required if types match
838
839                   if Btyp_DDT /= Etype (Ref_Object) then
840                      Rewrite (Prefix (N),
841                        Convert_To (Directly_Designated_Type (Typ),
842                          New_Copy_Tree (Prefix (N))));
843
844                      Analyze_And_Resolve (Prefix (N),
845                                           Directly_Designated_Type (Typ));
846                   end if;
847
848                --  When the object is an explicit dereference, convert the
849                --  dereference's prefix.
850
851                else
852                   declare
853                      Obj_DDT : constant Entity_Id :=
854                                  Base_Type
855                                    (Directly_Designated_Type
856                                      (Etype (Prefix (Ref_Object))));
857                   begin
858                      --  No implicit conversion required if designated types
859                      --  match.
860
861                      if Obj_DDT /= Btyp_DDT
862                        and then not (Is_Class_Wide_Type (Obj_DDT)
863                                        and then Etype (Obj_DDT) = Btyp_DDT)
864                      then
865                         Rewrite (N,
866                           Convert_To (Typ,
867                             New_Copy_Tree (Prefix (Ref_Object))));
868                         Analyze_And_Resolve (N, Typ);
869                      end if;
870                   end;
871                end if;
872             end if;
873          end Access_Cases;
874
875       --------------
876       -- Adjacent --
877       --------------
878
879       --  Transforms 'Adjacent into a call to the floating-point attribute
880       --  function Adjacent in Fat_xxx (where xxx is the root type)
881
882       when Attribute_Adjacent =>
883          Expand_Fpt_Attribute_RR (N);
884
885       -------------
886       -- Address --
887       -------------
888
889       when Attribute_Address => Address : declare
890          Task_Proc : Entity_Id;
891
892       begin
893          --  If the prefix is a task or a task type, the useful address is that
894          --  of the procedure for the task body, i.e. the actual program unit.
895          --  We replace the original entity with that of the procedure.
896
897          if Is_Entity_Name (Pref)
898            and then Is_Task_Type (Entity (Pref))
899          then
900             Task_Proc := Next_Entity (Root_Type (Etype (Pref)));
901
902             while Present (Task_Proc) loop
903                exit when Ekind (Task_Proc) = E_Procedure
904                  and then Etype (First_Formal (Task_Proc)) =
905                                   Corresponding_Record_Type (Etype (Pref));
906                Next_Entity (Task_Proc);
907             end loop;
908
909             if Present (Task_Proc) then
910                Set_Entity (Pref, Task_Proc);
911                Set_Etype  (Pref, Etype (Task_Proc));
912             end if;
913
914          --  Similarly, the address of a protected operation is the address
915          --  of the corresponding protected body, regardless of the protected
916          --  object from which it is selected.
917
918          elsif Nkind (Pref) = N_Selected_Component
919            and then Is_Subprogram (Entity (Selector_Name (Pref)))
920            and then Is_Protected_Type (Scope (Entity (Selector_Name (Pref))))
921          then
922             Rewrite (Pref,
923               New_Occurrence_Of (
924                 External_Subprogram (Entity (Selector_Name (Pref))), Loc));
925
926          elsif Nkind (Pref) = N_Explicit_Dereference
927            and then Ekind (Etype (Pref)) = E_Subprogram_Type
928            and then Convention (Etype (Pref)) = Convention_Protected
929          then
930             --  The prefix is be a dereference of an access_to_protected_
931             --  subprogram. The desired address is the second component of
932             --  the record that represents the access.
933
934             declare
935                Addr : constant Entity_Id := Etype (N);
936                Ptr  : constant Node_Id   := Prefix (Pref);
937                T    : constant Entity_Id :=
938                         Equivalent_Type (Base_Type (Etype (Ptr)));
939
940             begin
941                Rewrite (N,
942                  Unchecked_Convert_To (Addr,
943                    Make_Selected_Component (Loc,
944                      Prefix => Unchecked_Convert_To (T, Ptr),
945                      Selector_Name => New_Occurrence_Of (
946                        Next_Entity (First_Entity (T)), Loc))));
947
948                Analyze_And_Resolve (N, Addr);
949             end;
950
951          --  Ada 2005 (AI-251): Class-wide interface objects are always
952          --  "displaced" to reference the tag associated with the interface
953          --  type. In order to obtain the real address of such objects we
954          --  generate a call to a run-time subprogram that returns the base
955          --  address of the object.
956
957          --  This processing is not needed in the VM case, where dispatching
958          --  issues are taken care of by the virtual machine.
959
960          elsif Is_Class_Wide_Type (Etype (Pref))
961            and then Is_Interface (Etype (Pref))
962            and then VM_Target = No_VM
963            and then not (Nkind (Pref) in N_Has_Entity
964                           and then Is_Subprogram (Entity (Pref)))
965          then
966             Rewrite (N,
967               Make_Function_Call (Loc,
968                 Name => New_Reference_To (RTE (RE_Base_Address), Loc),
969                 Parameter_Associations => New_List (
970                   Relocate_Node (N))));
971             Analyze (N);
972             return;
973          end if;
974
975          --  Deal with packed array reference, other cases are handled by gigi
976
977          if Involves_Packed_Array_Reference (Pref) then
978             Expand_Packed_Address_Reference (N);
979          end if;
980       end Address;
981
982       ---------------
983       -- Alignment --
984       ---------------
985
986       when Attribute_Alignment => Alignment : declare
987          Ptyp     : constant Entity_Id := Etype (Pref);
988          New_Node : Node_Id;
989
990       begin
991          --  For class-wide types, X'Class'Alignment is transformed into a
992          --  direct reference to the Alignment of the class type, so that the
993          --  back end does not have to deal with the X'Class'Alignment
994          --  reference.
995
996          if Is_Entity_Name (Pref)
997            and then Is_Class_Wide_Type (Entity (Pref))
998          then
999             Rewrite (Prefix (N), New_Occurrence_Of (Entity (Pref), Loc));
1000             return;
1001
1002          --  For x'Alignment applied to an object of a class wide type,
1003          --  transform X'Alignment into a call to the predefined primitive
1004          --  operation _Alignment applied to X.
1005
1006          elsif Is_Class_Wide_Type (Ptyp) then
1007
1008             --  No need to do anything else compiling under restriction
1009             --  No_Dispatching_Calls. During the semantic analysis we
1010             --  already notified such violation.
1011
1012             if Restriction_Active (No_Dispatching_Calls) then
1013                return;
1014             end if;
1015
1016             New_Node :=
1017               Make_Function_Call (Loc,
1018                 Name => New_Reference_To
1019                   (Find_Prim_Op (Ptyp, Name_uAlignment), Loc),
1020                 Parameter_Associations => New_List (Pref));
1021
1022             if Typ /= Standard_Integer then
1023
1024                --  The context is a specific integer type with which the
1025                --  original attribute was compatible. The function has a
1026                --  specific type as well, so to preserve the compatibility
1027                --  we must convert explicitly.
1028
1029                New_Node := Convert_To (Typ, New_Node);
1030             end if;
1031
1032             Rewrite (N, New_Node);
1033             Analyze_And_Resolve (N, Typ);
1034             return;
1035
1036          --  For all other cases, we just have to deal with the case of
1037          --  the fact that the result can be universal.
1038
1039          else
1040             Apply_Universal_Integer_Attribute_Checks (N);
1041          end if;
1042       end Alignment;
1043
1044       ---------------
1045       -- AST_Entry --
1046       ---------------
1047
1048       when Attribute_AST_Entry => AST_Entry : declare
1049          Ttyp : Entity_Id;
1050          T_Id : Node_Id;
1051          Eent : Entity_Id;
1052
1053          Entry_Ref : Node_Id;
1054          --  The reference to the entry or entry family
1055
1056          Index : Node_Id;
1057          --  The index expression for an entry family reference, or
1058          --  the Empty if Entry_Ref references a simple entry.
1059
1060       begin
1061          if Nkind (Pref) = N_Indexed_Component then
1062             Entry_Ref := Prefix (Pref);
1063             Index := First (Expressions (Pref));
1064          else
1065             Entry_Ref := Pref;
1066             Index := Empty;
1067          end if;
1068
1069          --  Get expression for Task_Id and the entry entity
1070
1071          if Nkind (Entry_Ref) = N_Selected_Component then
1072             T_Id :=
1073               Make_Attribute_Reference (Loc,
1074                 Attribute_Name => Name_Identity,
1075                 Prefix         => Prefix (Entry_Ref));
1076
1077             Ttyp := Etype (Prefix (Entry_Ref));
1078             Eent := Entity (Selector_Name (Entry_Ref));
1079
1080          else
1081             T_Id :=
1082               Make_Function_Call (Loc,
1083                 Name => New_Occurrence_Of (RTE (RE_Current_Task), Loc));
1084
1085             Eent  := Entity (Entry_Ref);
1086
1087             --  We have to find the enclosing task to get the task type
1088             --  There must be one, since we already validated this earlier
1089
1090             Ttyp := Current_Scope;
1091             while not Is_Task_Type (Ttyp) loop
1092                Ttyp := Scope (Ttyp);
1093             end loop;
1094          end if;
1095
1096          --  Now rewrite the attribute with a call to Create_AST_Handler
1097
1098          Rewrite (N,
1099            Make_Function_Call (Loc,
1100              Name => New_Occurrence_Of (RTE (RE_Create_AST_Handler), Loc),
1101              Parameter_Associations => New_List (
1102                T_Id,
1103                Entry_Index_Expression (Loc, Eent, Index, Ttyp))));
1104
1105          Analyze_And_Resolve (N, RTE (RE_AST_Handler));
1106       end AST_Entry;
1107
1108       ------------------
1109       -- Bit_Position --
1110       ------------------
1111
1112       --  We compute this if a component clause was present, otherwise
1113       --  we leave the computation up to Gigi, since we don't know what
1114       --  layout will be chosen.
1115
1116       --  Note that the attribute can apply to a naked record component
1117       --  in generated code (i.e. the prefix is an identifier that
1118       --  references the component or discriminant entity).
1119
1120       when Attribute_Bit_Position => Bit_Position :
1121       declare
1122          CE : Entity_Id;
1123
1124       begin
1125          if Nkind (Pref) = N_Identifier then
1126             CE := Entity (Pref);
1127          else
1128             CE := Entity (Selector_Name (Pref));
1129          end if;
1130
1131          if Known_Static_Component_Bit_Offset (CE) then
1132             Rewrite (N,
1133               Make_Integer_Literal (Loc,
1134                 Intval => Component_Bit_Offset (CE)));
1135             Analyze_And_Resolve (N, Typ);
1136
1137          else
1138             Apply_Universal_Integer_Attribute_Checks (N);
1139          end if;
1140       end Bit_Position;
1141
1142       ------------------
1143       -- Body_Version --
1144       ------------------
1145
1146       --  A reference to P'Body_Version or P'Version is expanded to
1147
1148       --     Vnn : Unsigned;
1149       --     pragma Import (C, Vnn, "uuuuT";
1150       --     ...
1151       --     Get_Version_String (Vnn)
1152
1153       --  where uuuu is the unit name (dots replaced by double underscore)
1154       --  and T is B for the cases of Body_Version, or Version applied to a
1155       --  subprogram acting as its own spec, and S for Version applied to a
1156       --  subprogram spec or package. This sequence of code references the
1157       --  the unsigned constant created in the main program by the binder.
1158
1159       --  A special exception occurs for Standard, where the string
1160       --  returned is a copy of the library string in gnatvsn.ads.
1161
1162       when Attribute_Body_Version | Attribute_Version => Version : declare
1163          E    : constant Entity_Id :=
1164                   Make_Defining_Identifier (Loc, New_Internal_Name ('V'));
1165          Pent : Entity_Id;
1166          S    : String_Id;
1167
1168       begin
1169          --  If not library unit, get to containing library unit
1170
1171          Pent := Entity (Pref);
1172          while Pent /= Standard_Standard
1173            and then Scope (Pent) /= Standard_Standard
1174            and then not Is_Child_Unit (Pent)
1175          loop
1176             Pent := Scope (Pent);
1177          end loop;
1178
1179          --  Special case Standard and Standard.ASCII
1180
1181          if Pent = Standard_Standard or else Pent = Standard_ASCII then
1182             Rewrite (N,
1183               Make_String_Literal (Loc,
1184                 Strval => Verbose_Library_Version));
1185
1186          --  All other cases
1187
1188          else
1189             --  Build required string constant
1190
1191             Get_Name_String (Get_Unit_Name (Pent));
1192
1193             Start_String;
1194             for J in 1 .. Name_Len - 2 loop
1195                if Name_Buffer (J) = '.' then
1196                   Store_String_Chars ("__");
1197                else
1198                   Store_String_Char (Get_Char_Code (Name_Buffer (J)));
1199                end if;
1200             end loop;
1201
1202             --  Case of subprogram acting as its own spec, always use body
1203
1204             if Nkind (Declaration_Node (Pent)) in N_Subprogram_Specification
1205               and then Nkind (Parent (Declaration_Node (Pent))) =
1206                                                           N_Subprogram_Body
1207               and then Acts_As_Spec (Parent (Declaration_Node (Pent)))
1208             then
1209                Store_String_Chars ("B");
1210
1211             --  Case of no body present, always use spec
1212
1213             elsif not Unit_Requires_Body (Pent) then
1214                Store_String_Chars ("S");
1215
1216             --  Otherwise use B for Body_Version, S for spec
1217
1218             elsif Id = Attribute_Body_Version then
1219                Store_String_Chars ("B");
1220             else
1221                Store_String_Chars ("S");
1222             end if;
1223
1224             S := End_String;
1225             Lib.Version_Referenced (S);
1226
1227             --  Insert the object declaration
1228
1229             Insert_Actions (N, New_List (
1230               Make_Object_Declaration (Loc,
1231                 Defining_Identifier => E,
1232                 Object_Definition   =>
1233                   New_Occurrence_Of (RTE (RE_Unsigned), Loc))));
1234
1235             --  Set entity as imported with correct external name
1236
1237             Set_Is_Imported (E);
1238             Set_Interface_Name (E, Make_String_Literal (Loc, S));
1239
1240             --  Set entity as internal to ensure proper Sprint output of its
1241             --  implicit importation.
1242
1243             Set_Is_Internal (E);
1244
1245             --  And now rewrite original reference
1246
1247             Rewrite (N,
1248               Make_Function_Call (Loc,
1249                 Name => New_Reference_To (RTE (RE_Get_Version_String), Loc),
1250                 Parameter_Associations => New_List (
1251                   New_Occurrence_Of (E, Loc))));
1252          end if;
1253
1254          Analyze_And_Resolve (N, RTE (RE_Version_String));
1255       end Version;
1256
1257       -------------
1258       -- Ceiling --
1259       -------------
1260
1261       --  Transforms 'Ceiling into a call to the floating-point attribute
1262       --  function Ceiling in Fat_xxx (where xxx is the root type)
1263
1264       when Attribute_Ceiling =>
1265          Expand_Fpt_Attribute_R (N);
1266
1267       --------------
1268       -- Callable --
1269       --------------
1270
1271       --  Transforms 'Callable attribute into a call to the Callable function
1272
1273       when Attribute_Callable => Callable :
1274       begin
1275          --  We have an object of a task interface class-wide type as a prefix
1276          --  to Callable. Generate:
1277
1278          --    callable (Task_Id (Pref._disp_get_task_id));
1279
1280          if Ada_Version >= Ada_05
1281            and then Ekind (Etype (Pref)) = E_Class_Wide_Type
1282            and then Is_Interface (Etype (Pref))
1283            and then Is_Task_Interface (Etype (Pref))
1284          then
1285             Rewrite (N,
1286               Make_Function_Call (Loc,
1287                 Name =>
1288                   New_Reference_To (RTE (RE_Callable), Loc),
1289                 Parameter_Associations => New_List (
1290                   Make_Unchecked_Type_Conversion (Loc,
1291                     Subtype_Mark =>
1292                       New_Reference_To (RTE (RO_ST_Task_Id), Loc),
1293                     Expression =>
1294                       Make_Selected_Component (Loc,
1295                         Prefix =>
1296                           New_Copy_Tree (Pref),
1297                         Selector_Name =>
1298                           Make_Identifier (Loc, Name_uDisp_Get_Task_Id))))));
1299
1300          else
1301             Rewrite (N,
1302               Build_Call_With_Task (Pref, RTE (RE_Callable)));
1303          end if;
1304
1305          Analyze_And_Resolve (N, Standard_Boolean);
1306       end Callable;
1307
1308       ------------
1309       -- Caller --
1310       ------------
1311
1312       --  Transforms 'Caller attribute into a call to either the
1313       --  Task_Entry_Caller or the Protected_Entry_Caller function.
1314
1315       when Attribute_Caller => Caller : declare
1316          Id_Kind    : constant Entity_Id := RTE (RO_AT_Task_Id);
1317          Ent        : constant Entity_Id := Entity (Pref);
1318          Conctype   : constant Entity_Id := Scope (Ent);
1319          Nest_Depth : Integer := 0;
1320          Name       : Node_Id;
1321          S          : Entity_Id;
1322
1323       begin
1324          --  Protected case
1325
1326          if Is_Protected_Type (Conctype) then
1327             case Corresponding_Runtime_Package (Conctype) is
1328                when System_Tasking_Protected_Objects_Entries =>
1329                   Name :=
1330                     New_Reference_To
1331                       (RTE (RE_Protected_Entry_Caller), Loc);
1332
1333                when System_Tasking_Protected_Objects_Single_Entry =>
1334                   Name :=
1335                     New_Reference_To
1336                       (RTE (RE_Protected_Single_Entry_Caller), Loc);
1337
1338                when others =>
1339                   raise Program_Error;
1340             end case;
1341
1342             Rewrite (N,
1343               Unchecked_Convert_To (Id_Kind,
1344                 Make_Function_Call (Loc,
1345                   Name => Name,
1346                   Parameter_Associations => New_List
1347                     (New_Reference_To (
1348                       Object_Ref
1349                         (Corresponding_Body (Parent (Conctype))), Loc)))));
1350
1351          --  Task case
1352
1353          else
1354             --  Determine the nesting depth of the E'Caller attribute, that
1355             --  is, how many accept statements are nested within the accept
1356             --  statement for E at the point of E'Caller. The runtime uses
1357             --  this depth to find the specified entry call.
1358
1359             for J in reverse 0 .. Scope_Stack.Last loop
1360                S := Scope_Stack.Table (J).Entity;
1361
1362                --  We should not reach the scope of the entry, as it should
1363                --  already have been checked in Sem_Attr that this attribute
1364                --  reference is within a matching accept statement.
1365
1366                pragma Assert (S /= Conctype);
1367
1368                if S = Ent then
1369                   exit;
1370
1371                elsif Is_Entry (S) then
1372                   Nest_Depth := Nest_Depth + 1;
1373                end if;
1374             end loop;
1375
1376             Rewrite (N,
1377               Unchecked_Convert_To (Id_Kind,
1378                 Make_Function_Call (Loc,
1379                   Name => New_Reference_To (
1380                     RTE (RE_Task_Entry_Caller), Loc),
1381                   Parameter_Associations => New_List (
1382                     Make_Integer_Literal (Loc,
1383                       Intval => Int (Nest_Depth))))));
1384          end if;
1385
1386          Analyze_And_Resolve (N, Id_Kind);
1387       end Caller;
1388
1389       -------------
1390       -- Compose --
1391       -------------
1392
1393       --  Transforms 'Compose into a call to the floating-point attribute
1394       --  function Compose in Fat_xxx (where xxx is the root type)
1395
1396       --  Note: we strictly should have special code here to deal with the
1397       --  case of absurdly negative arguments (less than Integer'First)
1398       --  which will return a (signed) zero value, but it hardly seems
1399       --  worth the effort. Absurdly large positive arguments will raise
1400       --  constraint error which is fine.
1401
1402       when Attribute_Compose =>
1403          Expand_Fpt_Attribute_RI (N);
1404
1405       -----------------
1406       -- Constrained --
1407       -----------------
1408
1409       when Attribute_Constrained => Constrained : declare
1410          Formal_Ent : constant Entity_Id := Param_Entity (Pref);
1411          Typ        : constant Entity_Id := Etype (Pref);
1412
1413          function Is_Constrained_Aliased_View (Obj : Node_Id) return Boolean;
1414          --  Ada 2005 (AI-363): Returns True if the object name Obj denotes a
1415          --  view of an aliased object whose subtype is constrained.
1416
1417          ---------------------------------
1418          -- Is_Constrained_Aliased_View --
1419          ---------------------------------
1420
1421          function Is_Constrained_Aliased_View (Obj : Node_Id) return Boolean is
1422             E : Entity_Id;
1423
1424          begin
1425             if Is_Entity_Name (Obj) then
1426                E := Entity (Obj);
1427
1428                if Present (Renamed_Object (E)) then
1429                   return Is_Constrained_Aliased_View (Renamed_Object (E));
1430
1431                else
1432                   return Is_Aliased (E) and then Is_Constrained (Etype (E));
1433                end if;
1434
1435             else
1436                return Is_Aliased_View (Obj)
1437                         and then
1438                       (Is_Constrained (Etype (Obj))
1439                          or else (Nkind (Obj) = N_Explicit_Dereference
1440                                     and then
1441                                       not Has_Constrained_Partial_View
1442                                             (Base_Type (Etype (Obj)))));
1443             end if;
1444          end Is_Constrained_Aliased_View;
1445
1446       --  Start of processing for Constrained
1447
1448       begin
1449          --  Reference to a parameter where the value is passed as an extra
1450          --  actual, corresponding to the extra formal referenced by the
1451          --  Extra_Constrained field of the corresponding formal. If this
1452          --  is an entry in-parameter, it is replaced by a constant renaming
1453          --  for which Extra_Constrained is never created.
1454
1455          if Present (Formal_Ent)
1456            and then Ekind (Formal_Ent) /= E_Constant
1457            and then Present (Extra_Constrained (Formal_Ent))
1458          then
1459             Rewrite (N,
1460               New_Occurrence_Of
1461                 (Extra_Constrained (Formal_Ent), Sloc (N)));
1462
1463          --  For variables with a Extra_Constrained field, we use the
1464          --  corresponding entity.
1465
1466          elsif Nkind (Pref) = N_Identifier
1467            and then Ekind (Entity (Pref)) = E_Variable
1468            and then Present (Extra_Constrained (Entity (Pref)))
1469          then
1470             Rewrite (N,
1471               New_Occurrence_Of
1472                 (Extra_Constrained (Entity (Pref)), Sloc (N)));
1473
1474          --  For all other entity names, we can tell at compile time
1475
1476          elsif Is_Entity_Name (Pref) then
1477             declare
1478                Ent : constant Entity_Id   := Entity (Pref);
1479                Res : Boolean;
1480
1481             begin
1482                --  (RM J.4) obsolescent cases
1483
1484                if Is_Type (Ent) then
1485
1486                   --  Private type
1487
1488                   if Is_Private_Type (Ent) then
1489                      Res := not Has_Discriminants (Ent)
1490                               or else Is_Constrained (Ent);
1491
1492                   --  It not a private type, must be a generic actual type
1493                   --  that corresponded to a private type. We know that this
1494                   --  correspondence holds, since otherwise the reference
1495                   --  within the generic template would have been illegal.
1496
1497                   else
1498                      if Is_Composite_Type (Underlying_Type (Ent)) then
1499                         Res := Is_Constrained (Ent);
1500                      else
1501                         Res := True;
1502                      end if;
1503                   end if;
1504
1505                --  If the prefix is not a variable or is aliased, then
1506                --  definitely true; if it's a formal parameter without
1507                --  an associated extra formal, then treat it as constrained.
1508
1509                --  Ada 2005 (AI-363): An aliased prefix must be known to be
1510                --  constrained in order to set the attribute to True.
1511
1512                elsif not Is_Variable (Pref)
1513                  or else Present (Formal_Ent)
1514                  or else (Ada_Version < Ada_05
1515                             and then Is_Aliased_View (Pref))
1516                  or else (Ada_Version >= Ada_05
1517                             and then Is_Constrained_Aliased_View (Pref))
1518                then
1519                   Res := True;
1520
1521                --  Variable case, just look at type to see if it is
1522                --  constrained. Note that the one case where this is
1523                --  not accurate (the procedure formal case), has been
1524                --  handled above.
1525
1526                --  We use the Underlying_Type here (and below) in case the
1527                --  type is private without discriminants, but the full type
1528                --  has discriminants. This case is illegal, but we generate it
1529                --  internally for passing to the Extra_Constrained parameter.
1530
1531                else
1532                   Res := Is_Constrained (Underlying_Type (Etype (Ent)));
1533                end if;
1534
1535                Rewrite (N,
1536                  New_Reference_To (Boolean_Literals (Res), Loc));
1537             end;
1538
1539          --  Prefix is not an entity name. These are also cases where
1540          --  we can always tell at compile time by looking at the form
1541          --  and type of the prefix. If an explicit dereference of an
1542          --  object with constrained partial view, this is unconstrained
1543          --  (Ada 2005 AI-363).
1544
1545          else
1546             Rewrite (N,
1547               New_Reference_To (
1548                 Boolean_Literals (
1549                   not Is_Variable (Pref)
1550                     or else
1551                      (Nkind (Pref) = N_Explicit_Dereference
1552                         and then
1553                           not Has_Constrained_Partial_View (Base_Type (Typ)))
1554                     or else Is_Constrained (Underlying_Type (Typ))),
1555                 Loc));
1556          end if;
1557
1558          Analyze_And_Resolve (N, Standard_Boolean);
1559       end Constrained;
1560
1561       ---------------
1562       -- Copy_Sign --
1563       ---------------
1564
1565       --  Transforms 'Copy_Sign into a call to the floating-point attribute
1566       --  function Copy_Sign in Fat_xxx (where xxx is the root type)
1567
1568       when Attribute_Copy_Sign =>
1569          Expand_Fpt_Attribute_RR (N);
1570
1571       -----------
1572       -- Count --
1573       -----------
1574
1575       --  Transforms 'Count attribute into a call to the Count function
1576
1577       when Attribute_Count => Count :
1578       declare
1579          Entnam  : Node_Id;
1580          Index   : Node_Id;
1581          Name    : Node_Id;
1582          Call    : Node_Id;
1583          Conctyp : Entity_Id;
1584
1585       begin
1586          --  If the prefix is a member of an entry family, retrieve both
1587          --  entry name and index. For a simple entry there is no index.
1588
1589          if Nkind (Pref) = N_Indexed_Component then
1590             Entnam := Prefix (Pref);
1591             Index := First (Expressions (Pref));
1592          else
1593             Entnam := Pref;
1594             Index := Empty;
1595          end if;
1596
1597          --  Find the concurrent type in which this attribute is referenced
1598          --  (there had better be one).
1599
1600          Conctyp := Current_Scope;
1601          while not Is_Concurrent_Type (Conctyp) loop
1602             Conctyp := Scope (Conctyp);
1603          end loop;
1604
1605          --  Protected case
1606
1607          if Is_Protected_Type (Conctyp) then
1608
1609             case Corresponding_Runtime_Package (Conctyp) is
1610                when System_Tasking_Protected_Objects_Entries =>
1611                   Name := New_Reference_To (RTE (RE_Protected_Count), Loc);
1612
1613                   Call :=
1614                     Make_Function_Call (Loc,
1615                       Name => Name,
1616                       Parameter_Associations => New_List (
1617                         New_Reference_To (
1618                           Object_Ref (
1619                             Corresponding_Body (Parent (Conctyp))), Loc),
1620                         Entry_Index_Expression (Loc,
1621                           Entity (Entnam), Index, Scope (Entity (Entnam)))));
1622
1623                when System_Tasking_Protected_Objects_Single_Entry =>
1624                   Name := New_Reference_To
1625                            (RTE (RE_Protected_Count_Entry), Loc);
1626
1627                   Call :=
1628                     Make_Function_Call (Loc,
1629                       Name => Name,
1630                       Parameter_Associations => New_List (
1631                         New_Reference_To (
1632                           Object_Ref (
1633                             Corresponding_Body (Parent (Conctyp))), Loc)));
1634                when others =>
1635                   raise Program_Error;
1636
1637             end case;
1638
1639          --  Task case
1640
1641          else
1642             Call :=
1643               Make_Function_Call (Loc,
1644                 Name => New_Reference_To (RTE (RE_Task_Count), Loc),
1645                 Parameter_Associations => New_List (
1646                   Entry_Index_Expression
1647                     (Loc, Entity (Entnam), Index, Scope (Entity (Entnam)))));
1648          end if;
1649
1650          --  The call returns type Natural but the context is universal integer
1651          --  so any integer type is allowed. The attribute was already resolved
1652          --  so its Etype is the required result type. If the base type of the
1653          --  context type is other than Standard.Integer we put in a conversion
1654          --  to the required type. This can be a normal typed conversion since
1655          --  both input and output types of the conversion are integer types
1656
1657          if Base_Type (Typ) /= Base_Type (Standard_Integer) then
1658             Rewrite (N, Convert_To (Typ, Call));
1659          else
1660             Rewrite (N, Call);
1661          end if;
1662
1663          Analyze_And_Resolve (N, Typ);
1664       end Count;
1665
1666       ---------------
1667       -- Elab_Body --
1668       ---------------
1669
1670       --  This processing is shared by Elab_Spec
1671
1672       --  What we do is to insert the following declarations
1673
1674       --     procedure tnn;
1675       --     pragma Import (C, enn, "name___elabb/s");
1676
1677       --  and then the Elab_Body/Spec attribute is replaced by a reference
1678       --  to this defining identifier.
1679
1680       when Attribute_Elab_Body |
1681            Attribute_Elab_Spec =>
1682
1683          Elab_Body : declare
1684             Ent  : constant Entity_Id :=
1685                      Make_Defining_Identifier (Loc,
1686                        New_Internal_Name ('E'));
1687             Str  : String_Id;
1688             Lang : Node_Id;
1689
1690             procedure Make_Elab_String (Nod : Node_Id);
1691             --  Given Nod, an identifier, or a selected component, put the
1692             --  image into the current string literal, with double underline
1693             --  between components.
1694
1695             ----------------------
1696             -- Make_Elab_String --
1697             ----------------------
1698
1699             procedure Make_Elab_String (Nod : Node_Id) is
1700             begin
1701                if Nkind (Nod) = N_Selected_Component then
1702                   Make_Elab_String (Prefix (Nod));
1703
1704                   case VM_Target is
1705                      when JVM_Target =>
1706                         Store_String_Char ('$');
1707                      when CLI_Target =>
1708                         Store_String_Char ('.');
1709                      when No_VM =>
1710                         Store_String_Char ('_');
1711                         Store_String_Char ('_');
1712                   end case;
1713
1714                   Get_Name_String (Chars (Selector_Name (Nod)));
1715
1716                else
1717                   pragma Assert (Nkind (Nod) = N_Identifier);
1718                   Get_Name_String (Chars (Nod));
1719                end if;
1720
1721                Store_String_Chars (Name_Buffer (1 .. Name_Len));
1722             end Make_Elab_String;
1723
1724          --  Start of processing for Elab_Body/Elab_Spec
1725
1726          begin
1727             --  First we need to prepare the string literal for the name of
1728             --  the elaboration routine to be referenced.
1729
1730             Start_String;
1731             Make_Elab_String (Pref);
1732
1733             if VM_Target = No_VM then
1734                Store_String_Chars ("___elab");
1735                Lang := Make_Identifier (Loc, Name_C);
1736             else
1737                Store_String_Chars ("._elab");
1738                Lang := Make_Identifier (Loc, Name_Ada);
1739             end if;
1740
1741             if Id = Attribute_Elab_Body then
1742                Store_String_Char ('b');
1743             else
1744                Store_String_Char ('s');
1745             end if;
1746
1747             Str := End_String;
1748
1749             Insert_Actions (N, New_List (
1750               Make_Subprogram_Declaration (Loc,
1751                 Specification =>
1752                   Make_Procedure_Specification (Loc,
1753                     Defining_Unit_Name => Ent)),
1754
1755               Make_Pragma (Loc,
1756                 Chars => Name_Import,
1757                 Pragma_Argument_Associations => New_List (
1758                   Make_Pragma_Argument_Association (Loc,
1759                     Expression => Lang),
1760
1761                   Make_Pragma_Argument_Association (Loc,
1762                     Expression =>
1763                       Make_Identifier (Loc, Chars (Ent))),
1764
1765                   Make_Pragma_Argument_Association (Loc,
1766                     Expression =>
1767                       Make_String_Literal (Loc, Str))))));
1768
1769             Set_Entity (N, Ent);
1770             Rewrite (N, New_Occurrence_Of (Ent, Loc));
1771          end Elab_Body;
1772
1773       ----------------
1774       -- Elaborated --
1775       ----------------
1776
1777       --  Elaborated is always True for preelaborated units, predefined
1778       --  units, pure units and units which have Elaborate_Body pragmas.
1779       --  These units have no elaboration entity.
1780
1781       --  Note: The Elaborated attribute is never passed through to Gigi
1782
1783       when Attribute_Elaborated => Elaborated : declare
1784          Ent : constant Entity_Id := Entity (Pref);
1785
1786       begin
1787          if Present (Elaboration_Entity (Ent)) then
1788             Rewrite (N,
1789               New_Occurrence_Of (Elaboration_Entity (Ent), Loc));
1790          else
1791             Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
1792          end if;
1793       end Elaborated;
1794
1795       --------------
1796       -- Enum_Rep --
1797       --------------
1798
1799       when Attribute_Enum_Rep => Enum_Rep :
1800       begin
1801          --  X'Enum_Rep (Y) expands to
1802
1803          --    target-type (Y)
1804
1805          --  This is simply a direct conversion from the enumeration type
1806          --  to the target integer type, which is treated by Gigi as a normal
1807          --  integer conversion, treating the enumeration type as an integer,
1808          --  which is exactly what we want! We set Conversion_OK to make sure
1809          --  that the analyzer does not complain about what otherwise might
1810          --  be an illegal conversion.
1811
1812          if Is_Non_Empty_List (Exprs) then
1813             Rewrite (N,
1814               OK_Convert_To (Typ, Relocate_Node (First (Exprs))));
1815
1816          --  X'Enum_Rep where X is an enumeration literal is replaced by
1817          --  the literal value.
1818
1819          elsif Ekind (Entity (Pref)) = E_Enumeration_Literal then
1820             Rewrite (N,
1821               Make_Integer_Literal (Loc, Enumeration_Rep (Entity (Pref))));
1822
1823          --  If this is a renaming of a literal, recover the representation
1824          --  of the original.
1825
1826          elsif Ekind (Entity (Pref)) = E_Constant
1827            and then Present (Renamed_Object (Entity (Pref)))
1828            and then
1829              Ekind (Entity (Renamed_Object (Entity (Pref))))
1830                = E_Enumeration_Literal
1831          then
1832             Rewrite (N,
1833               Make_Integer_Literal (Loc,
1834                 Enumeration_Rep (Entity (Renamed_Object (Entity (Pref))))));
1835
1836          --  X'Enum_Rep where X is an object does a direct unchecked conversion
1837          --  of the object value, as described for the type case above.
1838
1839          else
1840             Rewrite (N,
1841               OK_Convert_To (Typ, Relocate_Node (Pref)));
1842          end if;
1843
1844          Set_Etype (N, Typ);
1845          Analyze_And_Resolve (N, Typ);
1846
1847       end Enum_Rep;
1848
1849       --------------
1850       -- Exponent --
1851       --------------
1852
1853       --  Transforms 'Exponent into a call to the floating-point attribute
1854       --  function Exponent in Fat_xxx (where xxx is the root type)
1855
1856       when Attribute_Exponent =>
1857          Expand_Fpt_Attribute_R (N);
1858
1859       ------------------
1860       -- External_Tag --
1861       ------------------
1862
1863       --  transforme X'External_Tag into Ada.Tags.External_Tag (X'tag)
1864
1865       when Attribute_External_Tag => External_Tag :
1866       begin
1867          Rewrite (N,
1868            Make_Function_Call (Loc,
1869              Name => New_Reference_To (RTE (RE_External_Tag), Loc),
1870              Parameter_Associations => New_List (
1871                Make_Attribute_Reference (Loc,
1872                  Attribute_Name => Name_Tag,
1873                  Prefix => Prefix (N)))));
1874
1875          Analyze_And_Resolve (N, Standard_String);
1876       end External_Tag;
1877
1878       -----------
1879       -- First --
1880       -----------
1881
1882       when Attribute_First => declare
1883          Ptyp : constant Entity_Id := Etype (Pref);
1884
1885       begin
1886          --  If the prefix type is a constrained packed array type which
1887          --  already has a Packed_Array_Type representation defined, then
1888          --  replace this attribute with a direct reference to 'First of the
1889          --  appropriate index subtype (since otherwise Gigi will try to give
1890          --  us the value of 'First for this implementation type).
1891
1892          if Is_Constrained_Packed_Array (Ptyp) then
1893             Rewrite (N,
1894               Make_Attribute_Reference (Loc,
1895                 Attribute_Name => Name_First,
1896                 Prefix => New_Reference_To (Get_Index_Subtype (N), Loc)));
1897             Analyze_And_Resolve (N, Typ);
1898
1899          elsif Is_Access_Type (Ptyp) then
1900             Apply_Access_Check (N);
1901          end if;
1902       end;
1903
1904       ---------------
1905       -- First_Bit --
1906       ---------------
1907
1908       --  We compute this if a component clause was present, otherwise
1909       --  we leave the computation up to Gigi, since we don't know what
1910       --  layout will be chosen.
1911
1912       when Attribute_First_Bit => First_Bit :
1913       declare
1914          CE : constant Entity_Id := Entity (Selector_Name (Pref));
1915
1916       begin
1917          if Known_Static_Component_Bit_Offset (CE) then
1918             Rewrite (N,
1919               Make_Integer_Literal (Loc,
1920                 Component_Bit_Offset (CE) mod System_Storage_Unit));
1921
1922             Analyze_And_Resolve (N, Typ);
1923
1924          else
1925             Apply_Universal_Integer_Attribute_Checks (N);
1926          end if;
1927       end First_Bit;
1928
1929       -----------------
1930       -- Fixed_Value --
1931       -----------------
1932
1933       --  We transform:
1934
1935       --     fixtype'Fixed_Value (integer-value)
1936
1937       --  into
1938
1939       --     fixtype(integer-value)
1940
1941       --  we do all the required analysis of the conversion here, because
1942       --  we do not want this to go through the fixed-point conversion
1943       --  circuits. Note that gigi always treats fixed-point as equivalent
1944       --  to the corresponding integer type anyway.
1945
1946       when Attribute_Fixed_Value => Fixed_Value :
1947       begin
1948          Rewrite (N,
1949            Make_Type_Conversion (Loc,
1950              Subtype_Mark => New_Occurrence_Of (Entity (Pref), Loc),
1951              Expression   => Relocate_Node (First (Exprs))));
1952          Set_Etype (N, Entity (Pref));
1953          Set_Analyzed (N);
1954
1955       --  Note: it might appear that a properly analyzed unchecked conversion
1956       --  would be just fine here, but that's not the case, since the full
1957       --  range checks performed by the following call are critical!
1958
1959          Apply_Type_Conversion_Checks (N);
1960       end Fixed_Value;
1961
1962       -----------
1963       -- Floor --
1964       -----------
1965
1966       --  Transforms 'Floor into a call to the floating-point attribute
1967       --  function Floor in Fat_xxx (where xxx is the root type)
1968
1969       when Attribute_Floor =>
1970          Expand_Fpt_Attribute_R (N);
1971
1972       ----------
1973       -- Fore --
1974       ----------
1975
1976       --  For the fixed-point type Typ:
1977
1978       --    Typ'Fore
1979
1980       --  expands into
1981
1982       --    Result_Type (System.Fore (Universal_Real (Type'First)),
1983       --                              Universal_Real (Type'Last))
1984
1985       --  Note that we know that the type is a non-static subtype, or Fore
1986       --  would have itself been computed dynamically in Eval_Attribute.
1987
1988       when Attribute_Fore => Fore :
1989       declare
1990          Ptyp : constant Entity_Id := Etype (Pref);
1991
1992       begin
1993          Rewrite (N,
1994            Convert_To (Typ,
1995              Make_Function_Call (Loc,
1996                Name => New_Reference_To (RTE (RE_Fore), Loc),
1997
1998                Parameter_Associations => New_List (
1999                  Convert_To (Universal_Real,
2000                    Make_Attribute_Reference (Loc,
2001                      Prefix => New_Reference_To (Ptyp, Loc),
2002                      Attribute_Name => Name_First)),
2003
2004                  Convert_To (Universal_Real,
2005                    Make_Attribute_Reference (Loc,
2006                      Prefix => New_Reference_To (Ptyp, Loc),
2007                      Attribute_Name => Name_Last))))));
2008
2009          Analyze_And_Resolve (N, Typ);
2010       end Fore;
2011
2012       --------------
2013       -- Fraction --
2014       --------------
2015
2016       --  Transforms 'Fraction into a call to the floating-point attribute
2017       --  function Fraction in Fat_xxx (where xxx is the root type)
2018
2019       when Attribute_Fraction =>
2020          Expand_Fpt_Attribute_R (N);
2021
2022       --------------
2023       -- Identity --
2024       --------------
2025
2026       --  For an exception returns a reference to the exception data:
2027       --      Exception_Id!(Prefix'Reference)
2028
2029       --  For a task it returns a reference to the _task_id component of
2030       --  corresponding record:
2031
2032       --    taskV!(Prefix)._Task_Id, converted to the type Task_Id defined
2033
2034       --  in Ada.Task_Identification
2035
2036       when Attribute_Identity => Identity : declare
2037          Id_Kind : Entity_Id;
2038
2039       begin
2040          if Etype (Pref) = Standard_Exception_Type then
2041             Id_Kind := RTE (RE_Exception_Id);
2042
2043             if Present (Renamed_Object (Entity (Pref))) then
2044                Set_Entity (Pref, Renamed_Object (Entity (Pref)));
2045             end if;
2046
2047             Rewrite (N,
2048               Unchecked_Convert_To (Id_Kind, Make_Reference (Loc, Pref)));
2049          else
2050             Id_Kind := RTE (RO_AT_Task_Id);
2051
2052             --  If the prefix is a task interface, the Task_Id is obtained
2053             --  dynamically through a dispatching call, as for other task
2054             --  attributes applied to interfaces.
2055
2056             if Ada_Version >= Ada_05
2057               and then Ekind (Etype (Pref)) = E_Class_Wide_Type
2058               and then Is_Interface (Etype (Pref))
2059               and then Is_Task_Interface (Etype (Pref))
2060             then
2061                Rewrite (N,
2062                  Unchecked_Convert_To (Id_Kind,
2063                    Make_Selected_Component (Loc,
2064                      Prefix =>
2065                        New_Copy_Tree (Pref),
2066                      Selector_Name =>
2067                        Make_Identifier (Loc, Name_uDisp_Get_Task_Id))));
2068
2069             else
2070                Rewrite (N,
2071                  Unchecked_Convert_To (Id_Kind, Concurrent_Ref (Pref)));
2072             end if;
2073          end if;
2074
2075          Analyze_And_Resolve (N, Id_Kind);
2076       end Identity;
2077
2078       -----------
2079       -- Image --
2080       -----------
2081
2082       --  Image attribute is handled in separate unit Exp_Imgv
2083
2084       when Attribute_Image =>
2085          Exp_Imgv.Expand_Image_Attribute (N);
2086
2087       ---------
2088       -- Img --
2089       ---------
2090
2091       --  X'Img is expanded to typ'Image (X), where typ is the type of X
2092
2093       when Attribute_Img => Img :
2094       begin
2095          Rewrite (N,
2096            Make_Attribute_Reference (Loc,
2097              Prefix => New_Reference_To (Etype (Pref), Loc),
2098              Attribute_Name => Name_Image,
2099              Expressions => New_List (Relocate_Node (Pref))));
2100
2101          Analyze_And_Resolve (N, Standard_String);
2102       end Img;
2103
2104       -----------
2105       -- Input --
2106       -----------
2107
2108       when Attribute_Input => Input : declare
2109          P_Type : constant Entity_Id := Entity (Pref);
2110          B_Type : constant Entity_Id := Base_Type (P_Type);
2111          U_Type : constant Entity_Id := Underlying_Type (P_Type);
2112          Strm   : constant Node_Id   := First (Exprs);
2113          Fname  : Entity_Id;
2114          Decl   : Node_Id;
2115          Call   : Node_Id;
2116          Prag   : Node_Id;
2117          Arg2   : Node_Id;
2118          Rfunc  : Node_Id;
2119
2120          Cntrl  : Node_Id := Empty;
2121          --  Value for controlling argument in call. Always Empty except in
2122          --  the dispatching (class-wide type) case, where it is a reference
2123          --  to the dummy object initialized to the right internal tag.
2124
2125          procedure Freeze_Stream_Subprogram (F : Entity_Id);
2126          --  The expansion of the attribute reference may generate a call to
2127          --  a user-defined stream subprogram that is frozen by the call. This
2128          --  can lead to access-before-elaboration problem if the reference
2129          --  appears in an object declaration and the subprogram body has not
2130          --  been seen. The freezing of the subprogram requires special code
2131          --  because it appears in an expanded context where expressions do
2132          --  not freeze their constituents.
2133
2134          ------------------------------
2135          -- Freeze_Stream_Subprogram --
2136          ------------------------------
2137
2138          procedure Freeze_Stream_Subprogram (F : Entity_Id) is
2139             Decl : constant Node_Id := Unit_Declaration_Node (F);
2140             Bod  : Node_Id;
2141
2142          begin
2143             --  If this is user-defined subprogram, the corresponding
2144             --  stream function appears as a renaming-as-body, and the
2145             --  user subprogram must be retrieved by tree traversal.
2146
2147             if Present (Decl)
2148               and then Nkind (Decl) = N_Subprogram_Declaration
2149               and then Present (Corresponding_Body (Decl))
2150             then
2151                Bod := Corresponding_Body (Decl);
2152
2153                if Nkind (Unit_Declaration_Node (Bod)) =
2154                  N_Subprogram_Renaming_Declaration
2155                then
2156                   Set_Is_Frozen (Entity (Name (Unit_Declaration_Node (Bod))));
2157                end if;
2158             end if;
2159          end Freeze_Stream_Subprogram;
2160
2161       --  Start of processing for Input
2162
2163       begin
2164          --  If no underlying type, we have an error that will be diagnosed
2165          --  elsewhere, so here we just completely ignore the expansion.
2166
2167          if No (U_Type) then
2168             return;
2169          end if;
2170
2171          --  If there is a TSS for Input, just call it
2172
2173          Fname := Find_Stream_Subprogram (P_Type, TSS_Stream_Input);
2174
2175          if Present (Fname) then
2176             null;
2177
2178          else
2179             --  If there is a Stream_Convert pragma, use it, we rewrite
2180
2181             --     sourcetyp'Input (stream)
2182
2183             --  as
2184
2185             --     sourcetyp (streamread (strmtyp'Input (stream)));
2186
2187             --  where stmrearead is the given Read function that converts
2188             --  an argument of type strmtyp to type sourcetyp or a type
2189             --  from which it is derived. The extra conversion is required
2190             --  for the derived case.
2191
2192             Prag := Get_Stream_Convert_Pragma (P_Type);
2193
2194             if Present (Prag) then
2195                Arg2  := Next (First (Pragma_Argument_Associations (Prag)));
2196                Rfunc := Entity (Expression (Arg2));
2197
2198                Rewrite (N,
2199                  Convert_To (B_Type,
2200                    Make_Function_Call (Loc,
2201                      Name => New_Occurrence_Of (Rfunc, Loc),
2202                      Parameter_Associations => New_List (
2203                        Make_Attribute_Reference (Loc,
2204                          Prefix =>
2205                            New_Occurrence_Of
2206                              (Etype (First_Formal (Rfunc)), Loc),
2207                          Attribute_Name => Name_Input,
2208                          Expressions => Exprs)))));
2209
2210                Analyze_And_Resolve (N, B_Type);
2211                return;
2212
2213             --  Elementary types
2214
2215             elsif Is_Elementary_Type (U_Type) then
2216
2217                --  A special case arises if we have a defined _Read routine,
2218                --  since in this case we are required to call this routine.
2219
2220                if Present (TSS (Base_Type (U_Type), TSS_Stream_Read)) then
2221                   Build_Record_Or_Elementary_Input_Function
2222                     (Loc, U_Type, Decl, Fname);
2223                   Insert_Action (N, Decl);
2224
2225                --  For normal cases, we call the I_xxx routine directly
2226
2227                else
2228                   Rewrite (N, Build_Elementary_Input_Call (N));
2229                   Analyze_And_Resolve (N, P_Type);
2230                   return;
2231                end if;
2232
2233             --  Array type case
2234
2235             elsif Is_Array_Type (U_Type) then
2236                Build_Array_Input_Function (Loc, U_Type, Decl, Fname);
2237                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
2238
2239             --  Dispatching case with class-wide type
2240
2241             elsif Is_Class_Wide_Type (P_Type) then
2242
2243                --  No need to do anything else compiling under restriction
2244                --  No_Dispatching_Calls. During the semantic analysis we
2245                --  already notified such violation.
2246
2247                if Restriction_Active (No_Dispatching_Calls) then
2248                   return;
2249                end if;
2250
2251                declare
2252                   Rtyp : constant Entity_Id := Root_Type (P_Type);
2253                   Dnn  : Entity_Id;
2254                   Decl : Node_Id;
2255
2256                begin
2257                   --  Read the internal tag (RM 13.13.2(34)) and use it to
2258                   --  initialize a dummy tag object:
2259
2260                   --    Dnn : Ada.Tags.Tag
2261                   --           := Descendant_Tag (String'Input (Strm), P_Type);
2262
2263                   --  This dummy object is used only to provide a controlling
2264                   --  argument for the eventual _Input call. Descendant_Tag is
2265                   --  called rather than Internal_Tag to ensure that we have a
2266                   --  tag for a type that is descended from the prefix type and
2267                   --  declared at the same accessibility level (the exception
2268                   --  Tag_Error will be raised otherwise). The level check is
2269                   --  required for Ada 2005 because tagged types can be
2270                   --  extended in nested scopes (AI-344).
2271
2272                   Dnn :=
2273                     Make_Defining_Identifier (Loc,
2274                       Chars => New_Internal_Name ('D'));
2275
2276                   Decl :=
2277                     Make_Object_Declaration (Loc,
2278                       Defining_Identifier => Dnn,
2279                       Object_Definition =>
2280                         New_Occurrence_Of (RTE (RE_Tag), Loc),
2281                       Expression =>
2282                         Make_Function_Call (Loc,
2283                           Name =>
2284                             New_Occurrence_Of (RTE (RE_Descendant_Tag), Loc),
2285                           Parameter_Associations => New_List (
2286                             Make_Attribute_Reference (Loc,
2287                               Prefix =>
2288                                 New_Occurrence_Of (Standard_String, Loc),
2289                               Attribute_Name => Name_Input,
2290                               Expressions => New_List (
2291                                 Relocate_Node
2292                                   (Duplicate_Subexpr (Strm)))),
2293                             Make_Attribute_Reference (Loc,
2294                               Prefix => New_Reference_To (P_Type, Loc),
2295                               Attribute_Name => Name_Tag))));
2296
2297                   Insert_Action (N, Decl);
2298
2299                   --  Now we need to get the entity for the call, and construct
2300                   --  a function call node, where we preset a reference to Dnn
2301                   --  as the controlling argument (doing an unchecked convert
2302                   --  to the class-wide tagged type to make it look like a real
2303                   --  tagged object).
2304
2305                   Fname := Find_Prim_Op (Rtyp, TSS_Stream_Input);
2306                   Cntrl := Unchecked_Convert_To (P_Type,
2307                              New_Occurrence_Of (Dnn, Loc));
2308                   Set_Etype (Cntrl, P_Type);
2309                   Set_Parent (Cntrl, N);
2310                end;
2311
2312             --  For tagged types, use the primitive Input function
2313
2314             elsif Is_Tagged_Type (U_Type) then
2315                Fname := Find_Prim_Op (U_Type, TSS_Stream_Input);
2316
2317             --  All other record type cases, including protected records. The
2318             --  latter only arise for expander generated code for handling
2319             --  shared passive partition access.
2320
2321             else
2322                pragma Assert
2323                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
2324
2325                --  Ada 2005 (AI-216): Program_Error is raised when executing
2326                --  the default implementation of the Input attribute of an
2327                --  unchecked union type if the type lacks default discriminant
2328                --  values.
2329
2330                if Is_Unchecked_Union (Base_Type (U_Type))
2331                  and then No (Discriminant_Constraint (U_Type))
2332                then
2333                   Insert_Action (N,
2334                     Make_Raise_Program_Error (Loc,
2335                       Reason => PE_Unchecked_Union_Restriction));
2336
2337                   return;
2338                end if;
2339
2340                Build_Record_Or_Elementary_Input_Function
2341                  (Loc, Base_Type (U_Type), Decl, Fname);
2342                Insert_Action (N, Decl);
2343
2344                if Nkind (Parent (N)) = N_Object_Declaration
2345                  and then Is_Record_Type (U_Type)
2346                then
2347                   --  The stream function may contain calls to user-defined
2348                   --  Read procedures for individual components.
2349
2350                   declare
2351                      Comp : Entity_Id;
2352                      Func : Entity_Id;
2353
2354                   begin
2355                      Comp := First_Component (U_Type);
2356                      while Present (Comp) loop
2357                         Func :=
2358                           Find_Stream_Subprogram
2359                             (Etype (Comp), TSS_Stream_Read);
2360
2361                         if Present (Func) then
2362                            Freeze_Stream_Subprogram (Func);
2363                         end if;
2364
2365                         Next_Component (Comp);
2366                      end loop;
2367                   end;
2368                end if;
2369             end if;
2370          end if;
2371
2372          --  If we fall through, Fname is the function to be called. The result
2373          --  is obtained by calling the appropriate function, then converting
2374          --  the result. The conversion does a subtype check.
2375
2376          Call :=
2377            Make_Function_Call (Loc,
2378              Name => New_Occurrence_Of (Fname, Loc),
2379              Parameter_Associations => New_List (
2380                 Relocate_Node (Strm)));
2381
2382          Set_Controlling_Argument (Call, Cntrl);
2383          Rewrite (N, Unchecked_Convert_To (P_Type, Call));
2384          Analyze_And_Resolve (N, P_Type);
2385
2386          if Nkind (Parent (N)) = N_Object_Declaration then
2387             Freeze_Stream_Subprogram (Fname);
2388          end if;
2389       end Input;
2390
2391       -------------------
2392       -- Integer_Value --
2393       -------------------
2394
2395       --  We transform
2396
2397       --    inttype'Fixed_Value (fixed-value)
2398
2399       --  into
2400
2401       --    inttype(integer-value))
2402
2403       --  we do all the required analysis of the conversion here, because
2404       --  we do not want this to go through the fixed-point conversion
2405       --  circuits. Note that gigi always treats fixed-point as equivalent
2406       --  to the corresponding integer type anyway.
2407
2408       when Attribute_Integer_Value => Integer_Value :
2409       begin
2410          Rewrite (N,
2411            Make_Type_Conversion (Loc,
2412              Subtype_Mark => New_Occurrence_Of (Entity (Pref), Loc),
2413              Expression   => Relocate_Node (First (Exprs))));
2414          Set_Etype (N, Entity (Pref));
2415          Set_Analyzed (N);
2416
2417       --  Note: it might appear that a properly analyzed unchecked conversion
2418       --  would be just fine here, but that's not the case, since the full
2419       --  range checks performed by the following call are critical!
2420
2421          Apply_Type_Conversion_Checks (N);
2422       end Integer_Value;
2423
2424       ----------
2425       -- Last --
2426       ----------
2427
2428       when Attribute_Last => declare
2429          Ptyp : constant Entity_Id := Etype (Pref);
2430
2431       begin
2432          --  If the prefix type is a constrained packed array type which
2433          --  already has a Packed_Array_Type representation defined, then
2434          --  replace this attribute with a direct reference to 'Last of the
2435          --  appropriate index subtype (since otherwise Gigi will try to give
2436          --  us the value of 'Last for this implementation type).
2437
2438          if Is_Constrained_Packed_Array (Ptyp) then
2439             Rewrite (N,
2440               Make_Attribute_Reference (Loc,
2441                 Attribute_Name => Name_Last,
2442                 Prefix => New_Reference_To (Get_Index_Subtype (N), Loc)));
2443             Analyze_And_Resolve (N, Typ);
2444
2445          elsif Is_Access_Type (Ptyp) then
2446             Apply_Access_Check (N);
2447          end if;
2448       end;
2449
2450       --------------
2451       -- Last_Bit --
2452       --------------
2453
2454       --  We compute this if a component clause was present, otherwise
2455       --  we leave the computation up to Gigi, since we don't know what
2456       --  layout will be chosen.
2457
2458       when Attribute_Last_Bit => Last_Bit :
2459       declare
2460          CE : constant Entity_Id := Entity (Selector_Name (Pref));
2461
2462       begin
2463          if Known_Static_Component_Bit_Offset (CE)
2464            and then Known_Static_Esize (CE)
2465          then
2466             Rewrite (N,
2467               Make_Integer_Literal (Loc,
2468                Intval => (Component_Bit_Offset (CE) mod System_Storage_Unit)
2469                                 + Esize (CE) - 1));
2470
2471             Analyze_And_Resolve (N, Typ);
2472
2473          else
2474             Apply_Universal_Integer_Attribute_Checks (N);
2475          end if;
2476       end Last_Bit;
2477
2478       ------------------
2479       -- Leading_Part --
2480       ------------------
2481
2482       --  Transforms 'Leading_Part into a call to the floating-point attribute
2483       --  function Leading_Part in Fat_xxx (where xxx is the root type)
2484
2485       --  Note: strictly, we should have special case code to deal with
2486       --  absurdly large positive arguments (greater than Integer'Last), which
2487       --  result in returning the first argument unchanged, but it hardly seems
2488       --  worth the effort. We raise constraint error for absurdly negative
2489       --  arguments which is fine.
2490
2491       when Attribute_Leading_Part =>
2492          Expand_Fpt_Attribute_RI (N);
2493
2494       ------------
2495       -- Length --
2496       ------------
2497
2498       when Attribute_Length => declare
2499          Ptyp : constant Entity_Id := Etype (Pref);
2500          Ityp : Entity_Id;
2501          Xnum : Uint;
2502
2503       begin
2504          --  Processing for packed array types
2505
2506          if Is_Array_Type (Ptyp) and then Is_Packed (Ptyp) then
2507             Ityp := Get_Index_Subtype (N);
2508
2509             --  If the index type, Ityp, is an enumeration type with
2510             --  holes, then we calculate X'Length explicitly using
2511
2512             --     Typ'Max
2513             --       (0, Ityp'Pos (X'Last  (N)) -
2514             --           Ityp'Pos (X'First (N)) + 1);
2515
2516             --  Since the bounds in the template are the representation
2517             --  values and gigi would get the wrong value.
2518
2519             if Is_Enumeration_Type (Ityp)
2520               and then Present (Enum_Pos_To_Rep (Base_Type (Ityp)))
2521             then
2522                if No (Exprs) then
2523                   Xnum := Uint_1;
2524                else
2525                   Xnum := Expr_Value (First (Expressions (N)));
2526                end if;
2527
2528                Rewrite (N,
2529                  Make_Attribute_Reference (Loc,
2530                    Prefix         => New_Occurrence_Of (Typ, Loc),
2531                    Attribute_Name => Name_Max,
2532                    Expressions    => New_List
2533                      (Make_Integer_Literal (Loc, 0),
2534
2535                       Make_Op_Add (Loc,
2536                         Left_Opnd =>
2537                           Make_Op_Subtract (Loc,
2538                             Left_Opnd =>
2539                               Make_Attribute_Reference (Loc,
2540                                 Prefix => New_Occurrence_Of (Ityp, Loc),
2541                                 Attribute_Name => Name_Pos,
2542
2543                                 Expressions => New_List (
2544                                   Make_Attribute_Reference (Loc,
2545                                     Prefix => Duplicate_Subexpr (Pref),
2546                                    Attribute_Name => Name_Last,
2547                                     Expressions => New_List (
2548                                       Make_Integer_Literal (Loc, Xnum))))),
2549
2550                             Right_Opnd =>
2551                               Make_Attribute_Reference (Loc,
2552                                 Prefix => New_Occurrence_Of (Ityp, Loc),
2553                                 Attribute_Name => Name_Pos,
2554
2555                                 Expressions => New_List (
2556                                   Make_Attribute_Reference (Loc,
2557                                     Prefix =>
2558                                       Duplicate_Subexpr_No_Checks (Pref),
2559                                    Attribute_Name => Name_First,
2560                                     Expressions => New_List (
2561                                       Make_Integer_Literal (Loc, Xnum)))))),
2562
2563                         Right_Opnd => Make_Integer_Literal (Loc, 1)))));
2564
2565                Analyze_And_Resolve (N, Typ, Suppress => All_Checks);
2566                return;
2567
2568             --  If the prefix type is a constrained packed array type which
2569             --  already has a Packed_Array_Type representation defined, then
2570             --  replace this attribute with a direct reference to 'Range_Length
2571             --  of the appropriate index subtype (since otherwise Gigi will try
2572             --  to give us the value of 'Length for this implementation type).
2573
2574             elsif Is_Constrained (Ptyp) then
2575                Rewrite (N,
2576                  Make_Attribute_Reference (Loc,
2577                    Attribute_Name => Name_Range_Length,
2578                    Prefix => New_Reference_To (Ityp, Loc)));
2579                Analyze_And_Resolve (N, Typ);
2580             end if;
2581
2582          --  If we have a packed array that is not bit packed, which was
2583
2584          --  Access type case
2585
2586          elsif Is_Access_Type (Ptyp) then
2587             Apply_Access_Check (N);
2588
2589             --  If the designated type is a packed array type, then we
2590             --  convert the reference to:
2591
2592             --    typ'Max (0, 1 +
2593             --                xtyp'Pos (Pref'Last (Expr)) -
2594             --                xtyp'Pos (Pref'First (Expr)));
2595
2596             --  This is a bit complex, but it is the easiest thing to do
2597             --  that works in all cases including enum types with holes
2598             --  xtyp here is the appropriate index type.
2599
2600             declare
2601                Dtyp : constant Entity_Id := Designated_Type (Ptyp);
2602                Xtyp : Entity_Id;
2603
2604             begin
2605                if Is_Array_Type (Dtyp) and then Is_Packed (Dtyp) then
2606                   Xtyp := Get_Index_Subtype (N);
2607
2608                   Rewrite (N,
2609                     Make_Attribute_Reference (Loc,
2610                       Prefix         => New_Occurrence_Of (Typ, Loc),
2611                       Attribute_Name => Name_Max,
2612                       Expressions    => New_List (
2613                         Make_Integer_Literal (Loc, 0),
2614
2615                         Make_Op_Add (Loc,
2616                           Make_Integer_Literal (Loc, 1),
2617                           Make_Op_Subtract (Loc,
2618                             Left_Opnd =>
2619                               Make_Attribute_Reference (Loc,
2620                                 Prefix => New_Occurrence_Of (Xtyp, Loc),
2621                                 Attribute_Name => Name_Pos,
2622                                 Expressions    => New_List (
2623                                   Make_Attribute_Reference (Loc,
2624                                     Prefix => Duplicate_Subexpr (Pref),
2625                                     Attribute_Name => Name_Last,
2626                                     Expressions =>
2627                                       New_Copy_List (Exprs)))),
2628
2629                             Right_Opnd =>
2630                               Make_Attribute_Reference (Loc,
2631                                 Prefix => New_Occurrence_Of (Xtyp, Loc),
2632                                 Attribute_Name => Name_Pos,
2633                                 Expressions    => New_List (
2634                                   Make_Attribute_Reference (Loc,
2635                                     Prefix =>
2636                                       Duplicate_Subexpr_No_Checks (Pref),
2637                                     Attribute_Name => Name_First,
2638                                     Expressions =>
2639                                       New_Copy_List (Exprs)))))))));
2640
2641                   Analyze_And_Resolve (N, Typ);
2642                end if;
2643             end;
2644
2645          --  Otherwise leave it to gigi
2646
2647          else
2648             Apply_Universal_Integer_Attribute_Checks (N);
2649          end if;
2650       end;
2651
2652       -------------
2653       -- Machine --
2654       -------------
2655
2656       --  Transforms 'Machine into a call to the floating-point attribute
2657       --  function Machine in Fat_xxx (where xxx is the root type)
2658
2659       when Attribute_Machine =>
2660          Expand_Fpt_Attribute_R (N);
2661
2662       ----------------------
2663       -- Machine_Rounding --
2664       ----------------------
2665
2666       --  Transforms 'Machine_Rounding into a call to the floating-point
2667       --  attribute function Machine_Rounding in Fat_xxx (where xxx is the root
2668       --  type). Expansion is avoided for cases the back end can handle
2669       --  directly.
2670
2671       when Attribute_Machine_Rounding =>
2672          if not Is_Inline_Floating_Point_Attribute (N) then
2673             Expand_Fpt_Attribute_R (N);
2674          end if;
2675
2676       ------------------
2677       -- Machine_Size --
2678       ------------------
2679
2680       --  Machine_Size is equivalent to Object_Size, so transform it into
2681       --  Object_Size and that way Gigi never sees Machine_Size.
2682
2683       when Attribute_Machine_Size =>
2684          Rewrite (N,
2685            Make_Attribute_Reference (Loc,
2686              Prefix => Prefix (N),
2687              Attribute_Name => Name_Object_Size));
2688
2689          Analyze_And_Resolve (N, Typ);
2690
2691       --------------
2692       -- Mantissa --
2693       --------------
2694
2695       --  The only case that can get this far is the dynamic case of the old
2696       --  Ada 83 Mantissa attribute for the fixed-point case. For this case, we
2697       --  expand:
2698
2699       --    typ'Mantissa
2700
2701       --  into
2702
2703       --    ityp (System.Mantissa.Mantissa_Value
2704       --           (Integer'Integer_Value (typ'First),
2705       --            Integer'Integer_Value (typ'Last)));
2706
2707       when Attribute_Mantissa => Mantissa : declare
2708          Ptyp : constant Entity_Id := Etype (Pref);
2709
2710       begin
2711          Rewrite (N,
2712            Convert_To (Typ,
2713              Make_Function_Call (Loc,
2714                Name => New_Occurrence_Of (RTE (RE_Mantissa_Value), Loc),
2715
2716                Parameter_Associations => New_List (
2717
2718                  Make_Attribute_Reference (Loc,
2719                    Prefix => New_Occurrence_Of (Standard_Integer, Loc),
2720                    Attribute_Name => Name_Integer_Value,
2721                    Expressions => New_List (
2722
2723                      Make_Attribute_Reference (Loc,
2724                        Prefix => New_Occurrence_Of (Ptyp, Loc),
2725                        Attribute_Name => Name_First))),
2726
2727                  Make_Attribute_Reference (Loc,
2728                    Prefix => New_Occurrence_Of (Standard_Integer, Loc),
2729                    Attribute_Name => Name_Integer_Value,
2730                    Expressions => New_List (
2731
2732                      Make_Attribute_Reference (Loc,
2733                        Prefix => New_Occurrence_Of (Ptyp, Loc),
2734                        Attribute_Name => Name_Last)))))));
2735
2736          Analyze_And_Resolve (N, Typ);
2737       end Mantissa;
2738
2739       --------------------
2740       -- Mechanism_Code --
2741       --------------------
2742
2743       when Attribute_Mechanism_Code =>
2744
2745          --  We must replace the prefix in the renamed case
2746
2747          if Is_Entity_Name (Pref)
2748            and then Present (Alias (Entity (Pref)))
2749          then
2750             Set_Renamed_Subprogram (Pref, Alias (Entity (Pref)));
2751          end if;
2752
2753       ---------
2754       -- Mod --
2755       ---------
2756
2757       when Attribute_Mod => Mod_Case : declare
2758          Arg  : constant Node_Id := Relocate_Node (First (Exprs));
2759          Hi   : constant Node_Id := Type_High_Bound (Etype (Arg));
2760          Modv : constant Uint    := Modulus (Btyp);
2761
2762       begin
2763
2764          --  This is not so simple. The issue is what type to use for the
2765          --  computation of the modular value.
2766
2767          --  The easy case is when the modulus value is within the bounds
2768          --  of the signed integer type of the argument. In this case we can
2769          --  just do the computation in that signed integer type, and then
2770          --  do an ordinary conversion to the target type.
2771
2772          if Modv <= Expr_Value (Hi) then
2773             Rewrite (N,
2774               Convert_To (Btyp,
2775                 Make_Op_Mod (Loc,
2776                   Left_Opnd  => Arg,
2777                   Right_Opnd => Make_Integer_Literal (Loc, Modv))));
2778
2779          --  Here we know that the modulus is larger than type'Last of the
2780          --  integer type. There are two cases to consider:
2781
2782          --    a) The integer value is non-negative. In this case, it is
2783          --    returned as the result (since it is less than the modulus).
2784
2785          --    b) The integer value is negative. In this case, we know that the
2786          --    result is modulus + value, where the value might be as small as
2787          --    -modulus. The trouble is what type do we use to do the subtract.
2788          --    No type will do, since modulus can be as big as 2**64, and no
2789          --    integer type accomodates this value. Let's do bit of algebra
2790
2791          --         modulus + value
2792          --      =  modulus - (-value)
2793          --      =  (modulus - 1) - (-value - 1)
2794
2795          --    Now modulus - 1 is certainly in range of the modular type.
2796          --    -value is in the range 1 .. modulus, so -value -1 is in the
2797          --    range 0 .. modulus-1 which is in range of the modular type.
2798          --    Furthermore, (-value - 1) can be expressed as -(value + 1)
2799          --    which we can compute using the integer base type.
2800
2801          --  Once this is done we analyze the conditional expression without
2802          --  range checks, because we know everything is in range, and we
2803          --  want to prevent spurious warnings on either branch.
2804
2805          else
2806             Rewrite (N,
2807               Make_Conditional_Expression (Loc,
2808                 Expressions => New_List (
2809                   Make_Op_Ge (Loc,
2810                     Left_Opnd  => Duplicate_Subexpr (Arg),
2811                     Right_Opnd => Make_Integer_Literal (Loc, 0)),
2812
2813                   Convert_To (Btyp,
2814                     Duplicate_Subexpr_No_Checks (Arg)),
2815
2816                   Make_Op_Subtract (Loc,
2817                     Left_Opnd =>
2818                       Make_Integer_Literal (Loc,
2819                         Intval => Modv - 1),
2820                     Right_Opnd =>
2821                       Convert_To (Btyp,
2822                         Make_Op_Minus (Loc,
2823                           Right_Opnd =>
2824                             Make_Op_Add (Loc,
2825                               Left_Opnd  => Duplicate_Subexpr_No_Checks (Arg),
2826                               Right_Opnd =>
2827                                 Make_Integer_Literal (Loc,
2828                                   Intval => 1))))))));
2829
2830          end if;
2831
2832          Analyze_And_Resolve (N, Btyp, Suppress => All_Checks);
2833       end Mod_Case;
2834
2835       -----------
2836       -- Model --
2837       -----------
2838
2839       --  Transforms 'Model into a call to the floating-point attribute
2840       --  function Model in Fat_xxx (where xxx is the root type)
2841
2842       when Attribute_Model =>
2843          Expand_Fpt_Attribute_R (N);
2844
2845       -----------------
2846       -- Object_Size --
2847       -----------------
2848
2849       --  The processing for Object_Size shares the processing for Size
2850
2851       ---------
2852       -- Old --
2853       ---------
2854
2855       when Attribute_Old => Old : declare
2856          Tnn     : constant Entity_Id :=
2857                      Make_Defining_Identifier (Loc,
2858                        Chars => New_Internal_Name ('T'));
2859          Subp    : Node_Id;
2860          Asn_Stm : Node_Id;
2861
2862       begin
2863          Subp := N;
2864          loop
2865             Subp := Parent (Subp);
2866             exit when Nkind (Subp) = N_Subprogram_Body;
2867          end loop;
2868
2869          Asn_Stm :=
2870            Make_Object_Declaration (Loc,
2871              Defining_Identifier => Tnn,
2872              Constant_Present    => True,
2873              Object_Definition   => New_Occurrence_Of (Etype (N), Loc),
2874              Expression          => Pref);
2875
2876          if Is_Empty_List (Declarations (Subp)) then
2877             Set_Declarations (Subp, New_List (Asn_Stm));
2878             Analyze (Asn_Stm);
2879          else
2880             Insert_Action (First (Declarations (Subp)), Asn_Stm);
2881          end if;
2882
2883          Rewrite (N, New_Occurrence_Of (Tnn, Loc));
2884       end Old;
2885
2886       ------------
2887       -- Output --
2888       ------------
2889
2890       when Attribute_Output => Output : declare
2891          P_Type : constant Entity_Id := Entity (Pref);
2892          U_Type : constant Entity_Id := Underlying_Type (P_Type);
2893          Pname  : Entity_Id;
2894          Decl   : Node_Id;
2895          Prag   : Node_Id;
2896          Arg3   : Node_Id;
2897          Wfunc  : Node_Id;
2898
2899       begin
2900          --  If no underlying type, we have an error that will be diagnosed
2901          --  elsewhere, so here we just completely ignore the expansion.
2902
2903          if No (U_Type) then
2904             return;
2905          end if;
2906
2907          --  If TSS for Output is present, just call it
2908
2909          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Output);
2910
2911          if Present (Pname) then
2912             null;
2913
2914          else
2915             --  If there is a Stream_Convert pragma, use it, we rewrite
2916
2917             --     sourcetyp'Output (stream, Item)
2918
2919             --  as
2920
2921             --     strmtyp'Output (Stream, strmwrite (acttyp (Item)));
2922
2923             --  where strmwrite is the given Write function that converts an
2924             --  argument of type sourcetyp or a type acctyp, from which it is
2925             --  derived to type strmtyp. The conversion to acttyp is required
2926             --  for the derived case.
2927
2928             Prag := Get_Stream_Convert_Pragma (P_Type);
2929
2930             if Present (Prag) then
2931                Arg3 :=
2932                  Next (Next (First (Pragma_Argument_Associations (Prag))));
2933                Wfunc := Entity (Expression (Arg3));
2934
2935                Rewrite (N,
2936                  Make_Attribute_Reference (Loc,
2937                    Prefix => New_Occurrence_Of (Etype (Wfunc), Loc),
2938                    Attribute_Name => Name_Output,
2939                    Expressions => New_List (
2940                    Relocate_Node (First (Exprs)),
2941                      Make_Function_Call (Loc,
2942                        Name => New_Occurrence_Of (Wfunc, Loc),
2943                        Parameter_Associations => New_List (
2944                          OK_Convert_To (Etype (First_Formal (Wfunc)),
2945                            Relocate_Node (Next (First (Exprs)))))))));
2946
2947                Analyze (N);
2948                return;
2949
2950             --  For elementary types, we call the W_xxx routine directly.
2951             --  Note that the effect of Write and Output is identical for
2952             --  the case of an elementary type, since there are no
2953             --  discriminants or bounds.
2954
2955             elsif Is_Elementary_Type (U_Type) then
2956
2957                --  A special case arises if we have a defined _Write routine,
2958                --  since in this case we are required to call this routine.
2959
2960                if Present (TSS (Base_Type (U_Type), TSS_Stream_Write)) then
2961                   Build_Record_Or_Elementary_Output_Procedure
2962                     (Loc, U_Type, Decl, Pname);
2963                   Insert_Action (N, Decl);
2964
2965                --  For normal cases, we call the W_xxx routine directly
2966
2967                else
2968                   Rewrite (N, Build_Elementary_Write_Call (N));
2969                   Analyze (N);
2970                   return;
2971                end if;
2972
2973             --  Array type case
2974
2975             elsif Is_Array_Type (U_Type) then
2976                Build_Array_Output_Procedure (Loc, U_Type, Decl, Pname);
2977                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
2978
2979             --  Class-wide case, first output external tag, then dispatch
2980             --  to the appropriate primitive Output function (RM 13.13.2(31)).
2981
2982             elsif Is_Class_Wide_Type (P_Type) then
2983
2984                --  No need to do anything else compiling under restriction
2985                --  No_Dispatching_Calls. During the semantic analysis we
2986                --  already notified such violation.
2987
2988                if Restriction_Active (No_Dispatching_Calls) then
2989                   return;
2990                end if;
2991
2992                Tag_Write : declare
2993                   Strm : constant Node_Id := First (Exprs);
2994                   Item : constant Node_Id := Next (Strm);
2995
2996                begin
2997                   --  Ada 2005 (AI-344): Check that the accessibility level
2998                   --  of the type of the output object is not deeper than
2999                   --  that of the attribute's prefix type.
3000
3001                   --  if Get_Access_Level (Item'Tag)
3002                   --       /= Get_Access_Level (P_Type'Tag)
3003                   --  then
3004                   --     raise Tag_Error;
3005                   --  end if;
3006
3007                   --  String'Output (Strm, External_Tag (Item'Tag));
3008
3009                   --  We cannot figure out a practical way to implement this
3010                   --  accessibility check on virtual machines, so we omit it.
3011
3012                   if Ada_Version >= Ada_05
3013                     and then VM_Target = No_VM
3014                   then
3015                      Insert_Action (N,
3016                        Make_Implicit_If_Statement (N,
3017                          Condition =>
3018                            Make_Op_Ne (Loc,
3019                              Left_Opnd  =>
3020                                Build_Get_Access_Level (Loc,
3021                                  Make_Attribute_Reference (Loc,
3022                                    Prefix         =>
3023                                      Relocate_Node (
3024                                        Duplicate_Subexpr (Item,
3025                                          Name_Req => True)),
3026                                    Attribute_Name => Name_Tag)),
3027
3028                              Right_Opnd =>
3029                                Make_Integer_Literal (Loc,
3030                                  Type_Access_Level (P_Type))),
3031
3032                          Then_Statements =>
3033                            New_List (Make_Raise_Statement (Loc,
3034                                        New_Occurrence_Of (
3035                                          RTE (RE_Tag_Error), Loc)))));
3036                   end if;
3037
3038                   Insert_Action (N,
3039                     Make_Attribute_Reference (Loc,
3040                       Prefix => New_Occurrence_Of (Standard_String, Loc),
3041                       Attribute_Name => Name_Output,
3042                       Expressions => New_List (
3043                         Relocate_Node (Duplicate_Subexpr (Strm)),
3044                         Make_Function_Call (Loc,
3045                           Name =>
3046                             New_Occurrence_Of (RTE (RE_External_Tag), Loc),
3047                           Parameter_Associations => New_List (
3048                            Make_Attribute_Reference (Loc,
3049                              Prefix =>
3050                                Relocate_Node
3051                                  (Duplicate_Subexpr (Item, Name_Req => True)),
3052                              Attribute_Name => Name_Tag))))));
3053                end Tag_Write;
3054
3055                Pname := Find_Prim_Op (U_Type, TSS_Stream_Output);
3056
3057             --  Tagged type case, use the primitive Output function
3058
3059             elsif Is_Tagged_Type (U_Type) then
3060                Pname := Find_Prim_Op (U_Type, TSS_Stream_Output);
3061
3062             --  All other record type cases, including protected records.
3063             --  The latter only arise for expander generated code for
3064             --  handling shared passive partition access.
3065
3066             else
3067                pragma Assert
3068                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
3069
3070                --  Ada 2005 (AI-216): Program_Error is raised when executing
3071                --  the default implementation of the Output attribute of an
3072                --  unchecked union type if the type lacks default discriminant
3073                --  values.
3074
3075                if Is_Unchecked_Union (Base_Type (U_Type))
3076                  and then No (Discriminant_Constraint (U_Type))
3077                then
3078                   Insert_Action (N,
3079                     Make_Raise_Program_Error (Loc,
3080                       Reason => PE_Unchecked_Union_Restriction));
3081
3082                   return;
3083                end if;
3084
3085                Build_Record_Or_Elementary_Output_Procedure
3086                  (Loc, Base_Type (U_Type), Decl, Pname);
3087                Insert_Action (N, Decl);
3088             end if;
3089          end if;
3090
3091          --  If we fall through, Pname is the name of the procedure to call
3092
3093          Rewrite_Stream_Proc_Call (Pname);
3094       end Output;
3095
3096       ---------
3097       -- Pos --
3098       ---------
3099
3100       --  For enumeration types with a standard representation, Pos is
3101       --  handled by Gigi.
3102
3103       --  For enumeration types, with a non-standard representation we
3104       --  generate a call to the _Rep_To_Pos function created when the
3105       --  type was frozen. The call has the form
3106
3107       --    _rep_to_pos (expr, flag)
3108
3109       --  The parameter flag is True if range checks are enabled, causing
3110       --  Program_Error to be raised if the expression has an invalid
3111       --  representation, and False if range checks are suppressed.
3112
3113       --  For integer types, Pos is equivalent to a simple integer
3114       --  conversion and we rewrite it as such
3115
3116       when Attribute_Pos => Pos :
3117       declare
3118          Etyp : Entity_Id := Base_Type (Entity (Pref));
3119
3120       begin
3121          --  Deal with zero/non-zero boolean values
3122
3123          if Is_Boolean_Type (Etyp) then
3124             Adjust_Condition (First (Exprs));
3125             Etyp := Standard_Boolean;
3126             Set_Prefix (N, New_Occurrence_Of (Standard_Boolean, Loc));
3127          end if;
3128
3129          --  Case of enumeration type
3130
3131          if Is_Enumeration_Type (Etyp) then
3132
3133             --  Non-standard enumeration type (generate call)
3134
3135             if Present (Enum_Pos_To_Rep (Etyp)) then
3136                Append_To (Exprs, Rep_To_Pos_Flag (Etyp, Loc));
3137                Rewrite (N,
3138                  Convert_To (Typ,
3139                    Make_Function_Call (Loc,
3140                      Name =>
3141                        New_Reference_To (TSS (Etyp, TSS_Rep_To_Pos), Loc),
3142                      Parameter_Associations => Exprs)));
3143
3144                Analyze_And_Resolve (N, Typ);
3145
3146             --  Standard enumeration type (do universal integer check)
3147
3148             else
3149                Apply_Universal_Integer_Attribute_Checks (N);
3150             end if;
3151
3152          --  Deal with integer types (replace by conversion)
3153
3154          elsif Is_Integer_Type (Etyp) then
3155             Rewrite (N, Convert_To (Typ, First (Exprs)));
3156             Analyze_And_Resolve (N, Typ);
3157          end if;
3158
3159       end Pos;
3160
3161       --------------
3162       -- Position --
3163       --------------
3164
3165       --  We compute this if a component clause was present, otherwise
3166       --  we leave the computation up to Gigi, since we don't know what
3167       --  layout will be chosen.
3168
3169       when Attribute_Position => Position :
3170       declare
3171          CE : constant Entity_Id := Entity (Selector_Name (Pref));
3172
3173       begin
3174          if Present (Component_Clause (CE)) then
3175             Rewrite (N,
3176               Make_Integer_Literal (Loc,
3177                 Intval => Component_Bit_Offset (CE) / System_Storage_Unit));
3178             Analyze_And_Resolve (N, Typ);
3179
3180          else
3181             Apply_Universal_Integer_Attribute_Checks (N);
3182          end if;
3183       end Position;
3184
3185       ----------
3186       -- Pred --
3187       ----------
3188
3189       --  1. Deal with enumeration types with holes
3190       --  2. For floating-point, generate call to attribute function
3191       --  3. For other cases, deal with constraint checking
3192
3193       when Attribute_Pred => Pred :
3194       declare
3195          Ptyp : constant Entity_Id := Base_Type (Etype (Pref));
3196
3197       begin
3198          --  For enumeration types with non-standard representations, we
3199          --  expand typ'Pred (x) into
3200
3201          --    Pos_To_Rep (Rep_To_Pos (x) - 1)
3202
3203          --    If the representation is contiguous, we compute instead
3204          --    Lit1 + Rep_to_Pos (x -1), to catch invalid representations.
3205
3206          if Is_Enumeration_Type (Ptyp)
3207            and then Present (Enum_Pos_To_Rep (Ptyp))
3208          then
3209             if Has_Contiguous_Rep (Ptyp) then
3210                Rewrite (N,
3211                   Unchecked_Convert_To (Ptyp,
3212                      Make_Op_Add (Loc,
3213                         Left_Opnd  =>
3214                          Make_Integer_Literal (Loc,
3215                            Enumeration_Rep (First_Literal (Ptyp))),
3216                         Right_Opnd =>
3217                           Make_Function_Call (Loc,
3218                             Name =>
3219                               New_Reference_To
3220                                (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
3221
3222                             Parameter_Associations =>
3223                               New_List (
3224                                 Unchecked_Convert_To (Ptyp,
3225                                   Make_Op_Subtract (Loc,
3226                                     Left_Opnd =>
3227                                      Unchecked_Convert_To (Standard_Integer,
3228                                        Relocate_Node (First (Exprs))),
3229                                     Right_Opnd =>
3230                                       Make_Integer_Literal (Loc, 1))),
3231                                 Rep_To_Pos_Flag (Ptyp, Loc))))));
3232
3233             else
3234                --  Add Boolean parameter True, to request program errror if
3235                --  we have a bad representation on our hands. If checks are
3236                --  suppressed, then add False instead
3237
3238                Append_To (Exprs, Rep_To_Pos_Flag (Ptyp, Loc));
3239                Rewrite (N,
3240                  Make_Indexed_Component (Loc,
3241                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Ptyp), Loc),
3242                    Expressions => New_List (
3243                      Make_Op_Subtract (Loc,
3244                     Left_Opnd =>
3245                       Make_Function_Call (Loc,
3246                         Name =>
3247                           New_Reference_To (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
3248                           Parameter_Associations => Exprs),
3249                     Right_Opnd => Make_Integer_Literal (Loc, 1)))));
3250             end if;
3251
3252             Analyze_And_Resolve (N, Typ);
3253
3254          --  For floating-point, we transform 'Pred into a call to the Pred
3255          --  floating-point attribute function in Fat_xxx (xxx is root type)
3256
3257          elsif Is_Floating_Point_Type (Ptyp) then
3258             Expand_Fpt_Attribute_R (N);
3259             Analyze_And_Resolve (N, Typ);
3260
3261          --  For modular types, nothing to do (no overflow, since wraps)
3262
3263          elsif Is_Modular_Integer_Type (Ptyp) then
3264             null;
3265
3266          --  For other types, if range checking is enabled, we must generate
3267          --  a check if overflow checking is enabled.
3268
3269          elsif not Overflow_Checks_Suppressed (Ptyp) then
3270             Expand_Pred_Succ (N);
3271          end if;
3272       end Pred;
3273
3274       --------------
3275       -- Priority --
3276       --------------
3277
3278       --  Ada 2005 (AI-327): Dynamic ceiling priorities
3279
3280       --  We rewrite X'Priority as the following run-time call:
3281
3282       --     Get_Ceiling (X._Object)
3283
3284       --  Note that although X'Priority is notionally an object, it is quite
3285       --  deliberately not defined as an aliased object in the RM. This means
3286       --  that it works fine to rewrite it as a call, without having to worry
3287       --  about complications that would other arise from X'Priority'Access,
3288       --  which is illegal, because of the lack of aliasing.
3289
3290       when Attribute_Priority =>
3291          declare
3292             Call           : Node_Id;
3293             Conctyp        : Entity_Id;
3294             Object_Parm    : Node_Id;
3295             Subprg         : Entity_Id;
3296             RT_Subprg_Name : Node_Id;
3297
3298          begin
3299             --  Look for the enclosing concurrent type
3300
3301             Conctyp := Current_Scope;
3302             while not Is_Concurrent_Type (Conctyp) loop
3303                Conctyp := Scope (Conctyp);
3304             end loop;
3305
3306             pragma Assert (Is_Protected_Type (Conctyp));
3307
3308             --  Generate the actual of the call
3309
3310             Subprg := Current_Scope;
3311             while not Present (Protected_Body_Subprogram (Subprg)) loop
3312                Subprg := Scope (Subprg);
3313             end loop;
3314
3315             --  Use of 'Priority inside protected entries and barriers (in
3316             --  both cases the type of the first formal of their expanded
3317             --  subprogram is Address)
3318
3319             if Etype (First_Entity (Protected_Body_Subprogram (Subprg)))
3320               = RTE (RE_Address)
3321             then
3322                declare
3323                   New_Itype : Entity_Id;
3324
3325                begin
3326                   --  In the expansion of protected entries the type of the
3327                   --  first formal of the Protected_Body_Subprogram is an
3328                   --  Address. In order to reference the _object component
3329                   --  we generate:
3330
3331                   --    type T is access p__ptTV;
3332                   --    freeze T []
3333
3334                   New_Itype := Create_Itype (E_Access_Type, N);
3335                   Set_Etype (New_Itype, New_Itype);
3336                   Init_Esize (New_Itype);
3337                   Init_Size_Align (New_Itype);
3338                   Set_Directly_Designated_Type (New_Itype,
3339                     Corresponding_Record_Type (Conctyp));
3340                   Freeze_Itype (New_Itype, N);
3341
3342                   --  Generate:
3343                   --    T!(O)._object'unchecked_access
3344
3345                   Object_Parm :=
3346                     Make_Attribute_Reference (Loc,
3347                        Prefix =>
3348                          Make_Selected_Component (Loc,
3349                            Prefix =>
3350                              Unchecked_Convert_To (New_Itype,
3351                                New_Reference_To
3352                                  (First_Entity
3353                                    (Protected_Body_Subprogram (Subprg)),
3354                                   Loc)),
3355                            Selector_Name =>
3356                              Make_Identifier (Loc, Name_uObject)),
3357                        Attribute_Name => Name_Unchecked_Access);
3358                end;
3359
3360             --  Use of 'Priority inside a protected subprogram
3361
3362             else
3363                Object_Parm :=
3364                  Make_Attribute_Reference (Loc,
3365                     Prefix =>
3366                       Make_Selected_Component (Loc,
3367                         Prefix => New_Reference_To
3368                                     (First_Entity
3369                                       (Protected_Body_Subprogram (Subprg)),
3370                                        Loc),
3371                         Selector_Name =>
3372                           Make_Identifier (Loc, Name_uObject)),
3373                     Attribute_Name => Name_Unchecked_Access);
3374             end if;
3375
3376             --  Select the appropriate run-time subprogram
3377
3378             if Number_Entries (Conctyp) = 0 then
3379                RT_Subprg_Name :=
3380                  New_Reference_To (RTE (RE_Get_Ceiling), Loc);
3381             else
3382                RT_Subprg_Name :=
3383                  New_Reference_To (RTE (RO_PE_Get_Ceiling), Loc);
3384             end if;
3385
3386             Call :=
3387               Make_Function_Call (Loc,
3388                 Name => RT_Subprg_Name,
3389                 Parameter_Associations => New_List (Object_Parm));
3390
3391             Rewrite (N, Call);
3392
3393             --  Avoid the generation of extra checks on the pointer to the
3394             --  protected object.
3395
3396             Analyze_And_Resolve (N, Typ, Suppress => Access_Check);
3397          end;
3398
3399       ------------------
3400       -- Range_Length --
3401       ------------------
3402
3403       when Attribute_Range_Length => Range_Length : declare
3404          P_Type : constant Entity_Id := Etype (Pref);
3405
3406       begin
3407          --  The only special processing required is for the case where
3408          --  Range_Length is applied to an enumeration type with holes.
3409          --  In this case we transform
3410
3411          --     X'Range_Length
3412
3413          --  to
3414
3415          --     X'Pos (X'Last) - X'Pos (X'First) + 1
3416
3417          --  So that the result reflects the proper Pos values instead
3418          --  of the underlying representations.
3419
3420          if Is_Enumeration_Type (P_Type)
3421            and then Has_Non_Standard_Rep (P_Type)
3422          then
3423             Rewrite (N,
3424               Make_Op_Add (Loc,
3425                 Left_Opnd =>
3426                   Make_Op_Subtract (Loc,
3427                     Left_Opnd =>
3428                       Make_Attribute_Reference (Loc,
3429                         Attribute_Name => Name_Pos,
3430                         Prefix => New_Occurrence_Of (P_Type, Loc),
3431                         Expressions => New_List (
3432                           Make_Attribute_Reference (Loc,
3433                             Attribute_Name => Name_Last,
3434                             Prefix => New_Occurrence_Of (P_Type, Loc)))),
3435
3436                     Right_Opnd =>
3437                       Make_Attribute_Reference (Loc,
3438                         Attribute_Name => Name_Pos,
3439                         Prefix => New_Occurrence_Of (P_Type, Loc),
3440                         Expressions => New_List (
3441                           Make_Attribute_Reference (Loc,
3442                             Attribute_Name => Name_First,
3443                             Prefix => New_Occurrence_Of (P_Type, Loc))))),
3444
3445                 Right_Opnd =>
3446                   Make_Integer_Literal (Loc, 1)));
3447
3448             Analyze_And_Resolve (N, Typ);
3449
3450          --  For all other cases, attribute is handled by Gigi, but we need
3451          --  to deal with the case of the range check on a universal integer.
3452
3453          else
3454             Apply_Universal_Integer_Attribute_Checks (N);
3455          end if;
3456       end Range_Length;
3457
3458       ----------
3459       -- Read --
3460       ----------
3461
3462       when Attribute_Read => Read : declare
3463          P_Type : constant Entity_Id := Entity (Pref);
3464          B_Type : constant Entity_Id := Base_Type (P_Type);
3465          U_Type : constant Entity_Id := Underlying_Type (P_Type);
3466          Pname  : Entity_Id;
3467          Decl   : Node_Id;
3468          Prag   : Node_Id;
3469          Arg2   : Node_Id;
3470          Rfunc  : Node_Id;
3471          Lhs    : Node_Id;
3472          Rhs    : Node_Id;
3473
3474       begin
3475          --  If no underlying type, we have an error that will be diagnosed
3476          --  elsewhere, so here we just completely ignore the expansion.
3477
3478          if No (U_Type) then
3479             return;
3480          end if;
3481
3482          --  The simple case, if there is a TSS for Read, just call it
3483
3484          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Read);
3485
3486          if Present (Pname) then
3487             null;
3488
3489          else
3490             --  If there is a Stream_Convert pragma, use it, we rewrite
3491
3492             --     sourcetyp'Read (stream, Item)
3493
3494             --  as
3495
3496             --     Item := sourcetyp (strmread (strmtyp'Input (Stream)));
3497
3498             --  where strmread is the given Read function that converts an
3499             --  argument of type strmtyp to type sourcetyp or a type from which
3500             --  it is derived. The conversion to sourcetyp is required in the
3501             --  latter case.
3502
3503             --  A special case arises if Item is a type conversion in which
3504             --  case, we have to expand to:
3505
3506             --     Itemx := typex (strmread (strmtyp'Input (Stream)));
3507
3508             --  where Itemx is the expression of the type conversion (i.e.
3509             --  the actual object), and typex is the type of Itemx.
3510
3511             Prag := Get_Stream_Convert_Pragma (P_Type);
3512
3513             if Present (Prag) then
3514                Arg2  := Next (First (Pragma_Argument_Associations (Prag)));
3515                Rfunc := Entity (Expression (Arg2));
3516                Lhs := Relocate_Node (Next (First (Exprs)));
3517                Rhs :=
3518                  OK_Convert_To (B_Type,
3519                    Make_Function_Call (Loc,
3520                      Name => New_Occurrence_Of (Rfunc, Loc),
3521                      Parameter_Associations => New_List (
3522                        Make_Attribute_Reference (Loc,
3523                          Prefix =>
3524                            New_Occurrence_Of
3525                              (Etype (First_Formal (Rfunc)), Loc),
3526                          Attribute_Name => Name_Input,
3527                          Expressions => New_List (
3528                            Relocate_Node (First (Exprs)))))));
3529
3530                if Nkind (Lhs) = N_Type_Conversion then
3531                   Lhs := Expression (Lhs);
3532                   Rhs := Convert_To (Etype (Lhs), Rhs);
3533                end if;
3534
3535                Rewrite (N,
3536                  Make_Assignment_Statement (Loc,
3537                    Name       => Lhs,
3538                    Expression => Rhs));
3539                Set_Assignment_OK (Lhs);
3540                Analyze (N);
3541                return;
3542
3543             --  For elementary types, we call the I_xxx routine using the first
3544             --  parameter and then assign the result into the second parameter.
3545             --  We set Assignment_OK to deal with the conversion case.
3546
3547             elsif Is_Elementary_Type (U_Type) then
3548                declare
3549                   Lhs : Node_Id;
3550                   Rhs : Node_Id;
3551
3552                begin
3553                   Lhs := Relocate_Node (Next (First (Exprs)));
3554                   Rhs := Build_Elementary_Input_Call (N);
3555
3556                   if Nkind (Lhs) = N_Type_Conversion then
3557                      Lhs := Expression (Lhs);
3558                      Rhs := Convert_To (Etype (Lhs), Rhs);
3559                   end if;
3560
3561                   Set_Assignment_OK (Lhs);
3562
3563                   Rewrite (N,
3564                     Make_Assignment_Statement (Loc,
3565                       Name => Lhs,
3566                       Expression => Rhs));
3567
3568                   Analyze (N);
3569                   return;
3570                end;
3571
3572             --  Array type case
3573
3574             elsif Is_Array_Type (U_Type) then
3575                Build_Array_Read_Procedure (N, U_Type, Decl, Pname);
3576                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
3577
3578             --  Tagged type case, use the primitive Read function. Note that
3579             --  this will dispatch in the class-wide case which is what we want
3580
3581             elsif Is_Tagged_Type (U_Type) then
3582                Pname := Find_Prim_Op (U_Type, TSS_Stream_Read);
3583
3584             --  All other record type cases, including protected records. The
3585             --  latter only arise for expander generated code for handling
3586             --  shared passive partition access.
3587
3588             else
3589                pragma Assert
3590                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
3591
3592                --  Ada 2005 (AI-216): Program_Error is raised when executing
3593                --  the default implementation of the Read attribute of an
3594                --  Unchecked_Union type.
3595
3596                if Is_Unchecked_Union (Base_Type (U_Type)) then
3597                   Insert_Action (N,
3598                     Make_Raise_Program_Error (Loc,
3599                       Reason => PE_Unchecked_Union_Restriction));
3600                end if;
3601
3602                if Has_Discriminants (U_Type)
3603                  and then Present
3604                    (Discriminant_Default_Value (First_Discriminant (U_Type)))
3605                then
3606                   Build_Mutable_Record_Read_Procedure
3607                     (Loc, Base_Type (U_Type), Decl, Pname);
3608                else
3609                   Build_Record_Read_Procedure
3610                     (Loc, Base_Type (U_Type), Decl, Pname);
3611                end if;
3612
3613                --  Suppress checks, uninitialized or otherwise invalid
3614                --  data does not cause constraint errors to be raised for
3615                --  a complete record read.
3616
3617                Insert_Action (N, Decl, All_Checks);
3618             end if;
3619          end if;
3620
3621          Rewrite_Stream_Proc_Call (Pname);
3622       end Read;
3623
3624       ---------------
3625       -- Remainder --
3626       ---------------
3627
3628       --  Transforms 'Remainder into a call to the floating-point attribute
3629       --  function Remainder in Fat_xxx (where xxx is the root type)
3630
3631       when Attribute_Remainder =>
3632          Expand_Fpt_Attribute_RR (N);
3633
3634       -----------
3635       -- Round --
3636       -----------
3637
3638       --  The handling of the Round attribute is quite delicate. The processing
3639       --  in Sem_Attr introduced a conversion to universal real, reflecting the
3640       --  semantics of Round, but we do not want anything to do with universal
3641       --  real at runtime, since this corresponds to using floating-point
3642       --  arithmetic.
3643
3644       --  What we have now is that the Etype of the Round attribute correctly
3645       --  indicates the final result type. The operand of the Round is the
3646       --  conversion to universal real, described above, and the operand of
3647       --  this conversion is the actual operand of Round, which may be the
3648       --  special case of a fixed point multiplication or division (Etype =
3649       --  universal fixed)
3650
3651       --  The exapander will expand first the operand of the conversion, then
3652       --  the conversion, and finally the round attribute itself, since we
3653       --  always work inside out. But we cannot simply process naively in this
3654       --  order. In the semantic world where universal fixed and real really
3655       --  exist and have infinite precision, there is no problem, but in the
3656       --  implementation world, where universal real is a floating-point type,
3657       --  we would get the wrong result.
3658
3659       --  So the approach is as follows. First, when expanding a multiply or
3660       --  divide whose type is universal fixed, we do nothing at all, instead
3661       --  deferring the operation till later.
3662
3663       --  The actual processing is done in Expand_N_Type_Conversion which
3664       --  handles the special case of Round by looking at its parent to see if
3665       --  it is a Round attribute, and if it is, handling the conversion (or
3666       --  its fixed multiply/divide child) in an appropriate manner.
3667
3668       --  This means that by the time we get to expanding the Round attribute
3669       --  itself, the Round is nothing more than a type conversion (and will
3670       --  often be a null type conversion), so we just replace it with the
3671       --  appropriate conversion operation.
3672
3673       when Attribute_Round =>
3674          Rewrite (N,
3675            Convert_To (Etype (N), Relocate_Node (First (Exprs))));
3676          Analyze_And_Resolve (N);
3677
3678       --------------
3679       -- Rounding --
3680       --------------
3681
3682       --  Transforms 'Rounding into a call to the floating-point attribute
3683       --  function Rounding in Fat_xxx (where xxx is the root type)
3684
3685       when Attribute_Rounding =>
3686          Expand_Fpt_Attribute_R (N);
3687
3688       -------------
3689       -- Scaling --
3690       -------------
3691
3692       --  Transforms 'Scaling into a call to the floating-point attribute
3693       --  function Scaling in Fat_xxx (where xxx is the root type)
3694
3695       when Attribute_Scaling =>
3696          Expand_Fpt_Attribute_RI (N);
3697
3698       ----------
3699       -- Size --
3700       ----------
3701
3702       when Attribute_Size        |
3703            Attribute_Object_Size |
3704            Attribute_Value_Size  |
3705            Attribute_VADS_Size   => Size :
3706
3707       declare
3708          Ptyp     : constant Entity_Id := Etype (Pref);
3709          Siz      : Uint;
3710          New_Node : Node_Id;
3711
3712       begin
3713          --  Processing for VADS_Size case. Note that this processing removes
3714          --  all traces of VADS_Size from the tree, and completes all required
3715          --  processing for VADS_Size by translating the attribute reference
3716          --  to an appropriate Size or Object_Size reference.
3717
3718          if Id = Attribute_VADS_Size
3719            or else (Use_VADS_Size and then Id = Attribute_Size)
3720          then
3721             --  If the size is specified, then we simply use the specified
3722             --  size. This applies to both types and objects. The size of an
3723             --  object can be specified in the following ways:
3724
3725             --    An explicit size object is given for an object
3726             --    A component size is specified for an indexed component
3727             --    A component clause is specified for a selected component
3728             --    The object is a component of a packed composite object
3729
3730             --  If the size is specified, then VADS_Size of an object
3731
3732             if (Is_Entity_Name (Pref)
3733                  and then Present (Size_Clause (Entity (Pref))))
3734               or else
3735                 (Nkind (Pref) = N_Component_Clause
3736                   and then (Present (Component_Clause
3737                                      (Entity (Selector_Name (Pref))))
3738                              or else Is_Packed (Etype (Prefix (Pref)))))
3739               or else
3740                 (Nkind (Pref) = N_Indexed_Component
3741                   and then (Component_Size (Etype (Prefix (Pref))) /= 0
3742                              or else Is_Packed (Etype (Prefix (Pref)))))
3743             then
3744                Set_Attribute_Name (N, Name_Size);
3745
3746             --  Otherwise if we have an object rather than a type, then the
3747             --  VADS_Size attribute applies to the type of the object, rather
3748             --  than the object itself. This is one of the respects in which
3749             --  VADS_Size differs from Size.
3750
3751             else
3752                if (not Is_Entity_Name (Pref)
3753                     or else not Is_Type (Entity (Pref)))
3754                  and then (Is_Scalar_Type (Etype (Pref))
3755                             or else Is_Constrained (Etype (Pref)))
3756                then
3757                   Rewrite (Pref, New_Occurrence_Of (Etype (Pref), Loc));
3758                end if;
3759
3760                --  For a scalar type for which no size was explicitly given,
3761                --  VADS_Size means Object_Size. This is the other respect in
3762                --  which VADS_Size differs from Size.
3763
3764                if Is_Scalar_Type (Etype (Pref))
3765                  and then No (Size_Clause (Etype (Pref)))
3766                then
3767                   Set_Attribute_Name (N, Name_Object_Size);
3768
3769                --  In all other cases, Size and VADS_Size are the sane
3770
3771                else
3772                   Set_Attribute_Name (N, Name_Size);
3773                end if;
3774             end if;
3775          end if;
3776
3777          --  For class-wide types,  X'Class'Size is transformed into a
3778          --  direct reference to the Size of the class type, so that gigi
3779          --  does not have to deal with the X'Class'Size reference.
3780
3781          if Is_Entity_Name (Pref)
3782            and then Is_Class_Wide_Type (Entity (Pref))
3783          then
3784             Rewrite (Prefix (N), New_Occurrence_Of (Entity (Pref), Loc));
3785             return;
3786
3787          --  For X'Size applied to an object of a class-wide type, transform
3788          --  X'Size into a call to the primitive operation _Size applied to X.
3789
3790          elsif Is_Class_Wide_Type (Ptyp) then
3791
3792             --  No need to do anything else compiling under restriction
3793             --  No_Dispatching_Calls. During the semantic analysis we
3794             --  already notified such violation.
3795
3796             if Restriction_Active (No_Dispatching_Calls) then
3797                return;
3798             end if;
3799
3800             New_Node :=
3801               Make_Function_Call (Loc,
3802                 Name => New_Reference_To
3803                   (Find_Prim_Op (Ptyp, Name_uSize), Loc),
3804                 Parameter_Associations => New_List (Pref));
3805
3806             if Typ /= Standard_Long_Long_Integer then
3807
3808                --  The context is a specific integer type with which the
3809                --  original attribute was compatible. The function has a
3810                --  specific type as well, so to preserve the compatibility
3811                --  we must convert explicitly.
3812
3813                New_Node := Convert_To (Typ, New_Node);
3814             end if;
3815
3816             Rewrite (N, New_Node);
3817             Analyze_And_Resolve (N, Typ);
3818                return;
3819
3820          --  Case of known RM_Size of a type
3821
3822          elsif (Id = Attribute_Size or else Id = Attribute_Value_Size)
3823            and then Is_Entity_Name (Pref)
3824            and then Is_Type (Entity (Pref))
3825            and then Known_Static_RM_Size (Entity (Pref))
3826          then
3827             Siz := RM_Size (Entity (Pref));
3828
3829          --  Case of known Esize of a type
3830
3831          elsif Id = Attribute_Object_Size
3832            and then Is_Entity_Name (Pref)
3833            and then Is_Type (Entity (Pref))
3834            and then Known_Static_Esize (Entity (Pref))
3835          then
3836             Siz := Esize (Entity (Pref));
3837
3838          --  Case of known size of object
3839
3840          elsif Id = Attribute_Size
3841            and then Is_Entity_Name (Pref)
3842            and then Is_Object (Entity (Pref))
3843            and then Known_Esize (Entity (Pref))
3844            and then Known_Static_Esize (Entity (Pref))
3845          then
3846             Siz := Esize (Entity (Pref));
3847
3848          --  For an array component, we can do Size in the front end
3849          --  if the component_size of the array is set.
3850
3851          elsif Nkind (Pref) = N_Indexed_Component then
3852             Siz := Component_Size (Etype (Prefix (Pref)));
3853
3854          --  For a record component, we can do Size in the front end if there
3855          --  is a component clause, or if the record is packed and the
3856          --  component's size is known at compile time.
3857
3858          elsif Nkind (Pref) = N_Selected_Component then
3859             declare
3860                Rec  : constant Entity_Id := Etype (Prefix (Pref));
3861                Comp : constant Entity_Id := Entity (Selector_Name (Pref));
3862
3863             begin
3864                if Present (Component_Clause (Comp)) then
3865                   Siz := Esize (Comp);
3866
3867                elsif Is_Packed (Rec) then
3868                   Siz := RM_Size (Ptyp);
3869
3870                else
3871                   Apply_Universal_Integer_Attribute_Checks (N);
3872                   return;
3873                end if;
3874             end;
3875
3876          --  All other cases are handled by Gigi
3877
3878          else
3879             Apply_Universal_Integer_Attribute_Checks (N);
3880
3881             --  If Size is applied to a formal parameter that is of a packed
3882             --  array subtype, then apply Size to the actual subtype.
3883
3884             if Is_Entity_Name (Pref)
3885               and then Is_Formal (Entity (Pref))
3886               and then Is_Array_Type (Etype (Pref))
3887               and then Is_Packed (Etype (Pref))
3888             then
3889                Rewrite (N,
3890                  Make_Attribute_Reference (Loc,
3891                    Prefix =>
3892                      New_Occurrence_Of (Get_Actual_Subtype (Pref), Loc),
3893                    Attribute_Name => Name_Size));
3894                Analyze_And_Resolve (N, Typ);
3895             end if;
3896
3897             --  If Size applies to a dereference of an access to unconstrained
3898             --  packed array, GIGI needs to see its unconstrained nominal type,
3899             --  but also a hint to the actual constrained type.
3900
3901             if Nkind (Pref) = N_Explicit_Dereference
3902               and then Is_Array_Type (Etype (Pref))
3903               and then not Is_Constrained (Etype (Pref))
3904               and then Is_Packed (Etype (Pref))
3905             then
3906                Set_Actual_Designated_Subtype (Pref,
3907                  Get_Actual_Subtype (Pref));
3908             end if;
3909
3910             return;
3911          end if;
3912
3913          --  Common processing for record and array component case
3914
3915          if Siz /= No_Uint and then Siz /= 0 then
3916             declare
3917                CS : constant Boolean := Comes_From_Source (N);
3918
3919             begin
3920                Rewrite (N, Make_Integer_Literal (Loc, Siz));
3921
3922                --  This integer literal is not a static expression. We do not
3923                --  call Analyze_And_Resolve here, because this would activate
3924                --  the circuit for deciding that a static value was out of
3925                --  range, and we don't want that.
3926
3927                --  So just manually set the type, mark the expression as non-
3928                --  static, and then ensure that the result is checked properly
3929                --  if the attribute comes from source (if it was internally
3930                --  generated, we never need a constraint check).
3931
3932                Set_Etype (N, Typ);
3933                Set_Is_Static_Expression (N, False);
3934
3935                if CS then
3936                   Apply_Constraint_Check (N, Typ);
3937                end if;
3938             end;
3939          end if;
3940       end Size;
3941
3942       ------------------
3943       -- Storage_Pool --
3944       ------------------
3945
3946       when Attribute_Storage_Pool =>
3947          Rewrite (N,
3948            Make_Type_Conversion (Loc,
3949              Subtype_Mark => New_Reference_To (Etype (N), Loc),
3950              Expression   => New_Reference_To (Entity (N), Loc)));
3951          Analyze_And_Resolve (N, Typ);
3952
3953       ------------------
3954       -- Storage_Size --
3955       ------------------
3956
3957       when Attribute_Storage_Size => Storage_Size :
3958       declare
3959          Ptyp : constant Entity_Id := Etype (Pref);
3960
3961       begin
3962          --  Access type case, always go to the root type
3963
3964          --  The case of access types results in a value of zero for the case
3965          --  where no storage size attribute clause has been given. If a
3966          --  storage size has been given, then the attribute is converted
3967          --  to a reference to the variable used to hold this value.
3968
3969          if Is_Access_Type (Ptyp) then
3970             if Present (Storage_Size_Variable (Root_Type (Ptyp))) then
3971                Rewrite (N,
3972                  Make_Attribute_Reference (Loc,
3973                    Prefix => New_Reference_To (Typ, Loc),
3974                    Attribute_Name => Name_Max,
3975                    Expressions => New_List (
3976                      Make_Integer_Literal (Loc, 0),
3977                      Convert_To (Typ,
3978                        New_Reference_To
3979                          (Storage_Size_Variable (Root_Type (Ptyp)), Loc)))));
3980
3981             elsif Present (Associated_Storage_Pool (Root_Type (Ptyp))) then
3982                Rewrite (N,
3983                  OK_Convert_To (Typ,
3984                    Make_Function_Call (Loc,
3985                      Name =>
3986                        New_Reference_To
3987                          (Find_Prim_Op
3988                            (Etype (Associated_Storage_Pool (Root_Type (Ptyp))),
3989                             Attribute_Name (N)),
3990                           Loc),
3991
3992                      Parameter_Associations => New_List (
3993                        New_Reference_To
3994                          (Associated_Storage_Pool (Root_Type (Ptyp)), Loc)))));
3995
3996             else
3997                Rewrite (N, Make_Integer_Literal (Loc, 0));
3998             end if;
3999
4000             Analyze_And_Resolve (N, Typ);
4001
4002          --  For tasks, we retrieve the size directly from the TCB. The
4003          --  size may depend on a discriminant of the type, and therefore
4004          --  can be a per-object expression, so type-level information is
4005          --  not sufficient in general. There are four cases to consider:
4006
4007          --  a) If the attribute appears within a task body, the designated
4008          --    TCB is obtained by a call to Self.
4009
4010          --  b) If the prefix of the attribute is the name of a task object,
4011          --  the designated TCB is the one stored in the corresponding record.
4012
4013          --  c) If the prefix is a task type, the size is obtained from the
4014          --  size variable created for each task type
4015
4016          --  d) If no storage_size was specified for the type , there is no
4017          --  size variable, and the value is a system-specific default.
4018
4019          else
4020             if In_Open_Scopes (Ptyp) then
4021
4022                --  Storage_Size (Self)
4023
4024                Rewrite (N,
4025                  Convert_To (Typ,
4026                    Make_Function_Call (Loc,
4027                      Name =>
4028                        New_Occurrence_Of (RTE (RE_Storage_Size), Loc),
4029                      Parameter_Associations =>
4030                        New_List (
4031                          Make_Function_Call (Loc,
4032                            Name =>
4033                              New_Reference_To (RTE (RE_Self), Loc))))));
4034
4035             elsif not Is_Entity_Name (Pref)
4036               or else not Is_Type (Entity (Pref))
4037             then
4038                --  Storage_Size (Rec (Obj).Size)
4039
4040                Rewrite (N,
4041                  Convert_To (Typ,
4042                    Make_Function_Call (Loc,
4043                      Name =>
4044                        New_Occurrence_Of (RTE (RE_Storage_Size), Loc),
4045                        Parameter_Associations =>
4046                           New_List (
4047                             Make_Selected_Component (Loc,
4048                               Prefix =>
4049                                 Unchecked_Convert_To (
4050                                   Corresponding_Record_Type (Ptyp),
4051                                     New_Copy_Tree (Pref)),
4052                               Selector_Name =>
4053                                  Make_Identifier (Loc, Name_uTask_Id))))));
4054
4055             elsif Present (Storage_Size_Variable (Ptyp)) then
4056
4057                --  Static storage size pragma given for type: retrieve value
4058                --  from its allocated storage variable.
4059
4060                Rewrite (N,
4061                  Convert_To (Typ,
4062                    Make_Function_Call (Loc,
4063                      Name => New_Occurrence_Of (
4064                        RTE (RE_Adjust_Storage_Size), Loc),
4065                      Parameter_Associations =>
4066                        New_List (
4067                          New_Reference_To (
4068                            Storage_Size_Variable (Ptyp), Loc)))));
4069             else
4070                --  Get system default
4071
4072                Rewrite (N,
4073                  Convert_To (Typ,
4074                    Make_Function_Call (Loc,
4075                      Name =>
4076                        New_Occurrence_Of (
4077                         RTE (RE_Default_Stack_Size), Loc))));
4078             end if;
4079
4080             Analyze_And_Resolve (N, Typ);
4081          end if;
4082       end Storage_Size;
4083
4084       -----------------
4085       -- Stream_Size --
4086       -----------------
4087
4088       when Attribute_Stream_Size => Stream_Size : declare
4089          Ptyp : constant Entity_Id := Etype (Pref);
4090          Size : Int;
4091
4092       begin
4093          --  If we have a Stream_Size clause for this type use it, otherwise
4094          --  the Stream_Size if the size of the type.
4095
4096          if Has_Stream_Size_Clause (Ptyp) then
4097             Size :=
4098               UI_To_Int
4099                 (Static_Integer (Expression (Stream_Size_Clause (Ptyp))));
4100          else
4101             Size := UI_To_Int (Esize (Ptyp));
4102          end if;
4103
4104          Rewrite (N, Make_Integer_Literal (Loc, Intval => Size));
4105          Analyze_And_Resolve (N, Typ);
4106       end Stream_Size;
4107
4108       ----------
4109       -- Succ --
4110       ----------
4111
4112       --  1. Deal with enumeration types with holes
4113       --  2. For floating-point, generate call to attribute function
4114       --  3. For other cases, deal with constraint checking
4115
4116       when Attribute_Succ => Succ :
4117       declare
4118          Ptyp : constant Entity_Id := Base_Type (Etype (Pref));
4119
4120       begin
4121          --  For enumeration types with non-standard representations, we
4122          --  expand typ'Succ (x) into
4123
4124          --    Pos_To_Rep (Rep_To_Pos (x) + 1)
4125
4126          --    If the representation is contiguous, we compute instead
4127          --    Lit1 + Rep_to_Pos (x+1), to catch invalid representations.
4128
4129          if Is_Enumeration_Type (Ptyp)
4130            and then Present (Enum_Pos_To_Rep (Ptyp))
4131          then
4132             if Has_Contiguous_Rep (Ptyp) then
4133                Rewrite (N,
4134                   Unchecked_Convert_To (Ptyp,
4135                      Make_Op_Add (Loc,
4136                         Left_Opnd  =>
4137                          Make_Integer_Literal (Loc,
4138                            Enumeration_Rep (First_Literal (Ptyp))),
4139                         Right_Opnd =>
4140                           Make_Function_Call (Loc,
4141                             Name =>
4142                               New_Reference_To
4143                                (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
4144
4145                             Parameter_Associations =>
4146                               New_List (
4147                                 Unchecked_Convert_To (Ptyp,
4148                                   Make_Op_Add (Loc,
4149                                   Left_Opnd =>
4150                                     Unchecked_Convert_To (Standard_Integer,
4151                                       Relocate_Node (First (Exprs))),
4152                                   Right_Opnd =>
4153                                     Make_Integer_Literal (Loc, 1))),
4154                                 Rep_To_Pos_Flag (Ptyp, Loc))))));
4155             else
4156                --  Add Boolean parameter True, to request program errror if
4157                --  we have a bad representation on our hands. Add False if
4158                --  checks are suppressed.
4159
4160                Append_To (Exprs, Rep_To_Pos_Flag (Ptyp, Loc));
4161                Rewrite (N,
4162                  Make_Indexed_Component (Loc,
4163                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Ptyp), Loc),
4164                    Expressions => New_List (
4165                      Make_Op_Add (Loc,
4166                        Left_Opnd =>
4167                          Make_Function_Call (Loc,
4168                            Name =>
4169                              New_Reference_To
4170                                (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
4171                            Parameter_Associations => Exprs),
4172                        Right_Opnd => Make_Integer_Literal (Loc, 1)))));
4173             end if;
4174
4175             Analyze_And_Resolve (N, Typ);
4176
4177          --  For floating-point, we transform 'Succ into a call to the Succ
4178          --  floating-point attribute function in Fat_xxx (xxx is root type)
4179
4180          elsif Is_Floating_Point_Type (Ptyp) then
4181             Expand_Fpt_Attribute_R (N);
4182             Analyze_And_Resolve (N, Typ);
4183
4184          --  For modular types, nothing to do (no overflow, since wraps)
4185
4186          elsif Is_Modular_Integer_Type (Ptyp) then
4187             null;
4188
4189          --  For other types, if range checking is enabled, we must generate
4190          --  a check if overflow checking is enabled.
4191
4192          elsif not Overflow_Checks_Suppressed (Ptyp) then
4193             Expand_Pred_Succ (N);
4194          end if;
4195       end Succ;
4196
4197       ---------
4198       -- Tag --
4199       ---------
4200
4201       --  Transforms X'Tag into a direct reference to the tag of X
4202
4203       when Attribute_Tag => Tag :
4204       declare
4205          Ttyp           : Entity_Id;
4206          Prefix_Is_Type : Boolean;
4207
4208       begin
4209          if Is_Entity_Name (Pref) and then Is_Type (Entity (Pref)) then
4210             Ttyp := Entity (Pref);
4211             Prefix_Is_Type := True;
4212          else
4213             Ttyp := Etype (Pref);
4214             Prefix_Is_Type := False;
4215          end if;
4216
4217          if Is_Class_Wide_Type (Ttyp) then
4218             Ttyp := Root_Type (Ttyp);
4219          end if;
4220
4221          Ttyp := Underlying_Type (Ttyp);
4222
4223          if Prefix_Is_Type then
4224
4225             --  For VMs we leave the type attribute unexpanded because
4226             --  there's not a dispatching table to reference.
4227
4228             if VM_Target = No_VM then
4229                Rewrite (N,
4230                  Unchecked_Convert_To (RTE (RE_Tag),
4231                    New_Reference_To
4232                      (Node (First_Elmt (Access_Disp_Table (Ttyp))), Loc)));
4233                Analyze_And_Resolve (N, RTE (RE_Tag));
4234             end if;
4235
4236          --  (Ada 2005 (AI-251): The use of 'Tag in the sources always
4237          --  references the primary tag of the actual object. If 'Tag is
4238          --  applied to class-wide interface objects we generate code that
4239          --  displaces "this" to reference the base of the object.
4240
4241          elsif Comes_From_Source (N)
4242             and then Is_Class_Wide_Type (Etype (Prefix (N)))
4243             and then Is_Interface (Etype (Prefix (N)))
4244          then
4245             --  Generate:
4246             --    (To_Tag_Ptr (Prefix'Address)).all
4247
4248             --  Note that Prefix'Address is recursively expanded into a call
4249             --  to Base_Address (Obj.Tag)
4250
4251             --  Not needed for VM targets, since all handled by the VM
4252
4253             if VM_Target = No_VM then
4254                Rewrite (N,
4255                  Make_Explicit_Dereference (Loc,
4256                    Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4257                      Make_Attribute_Reference (Loc,
4258                        Prefix => Relocate_Node (Pref),
4259                        Attribute_Name => Name_Address))));
4260                Analyze_And_Resolve (N, RTE (RE_Tag));
4261             end if;
4262
4263          else
4264             Rewrite (N,
4265               Make_Selected_Component (Loc,
4266                 Prefix => Relocate_Node (Pref),
4267                 Selector_Name =>
4268                   New_Reference_To (First_Tag_Component (Ttyp), Loc)));
4269             Analyze_And_Resolve (N, RTE (RE_Tag));
4270          end if;
4271       end Tag;
4272
4273       ----------------
4274       -- Terminated --
4275       ----------------
4276
4277       --  Transforms 'Terminated attribute into a call to Terminated function
4278
4279       when Attribute_Terminated => Terminated :
4280       begin
4281          --  The prefix of Terminated is of a task interface class-wide type.
4282          --  Generate:
4283
4284          --    terminated (Task_Id (Pref._disp_get_task_id));
4285
4286          if Ada_Version >= Ada_05
4287            and then Ekind (Etype (Pref)) = E_Class_Wide_Type
4288            and then Is_Interface (Etype (Pref))
4289            and then Is_Task_Interface (Etype (Pref))
4290          then
4291             Rewrite (N,
4292               Make_Function_Call (Loc,
4293                 Name =>
4294                   New_Reference_To (RTE (RE_Terminated), Loc),
4295                 Parameter_Associations => New_List (
4296                   Make_Unchecked_Type_Conversion (Loc,
4297                     Subtype_Mark =>
4298                       New_Reference_To (RTE (RO_ST_Task_Id), Loc),
4299                     Expression =>
4300                       Make_Selected_Component (Loc,
4301                         Prefix =>
4302                           New_Copy_Tree (Pref),
4303                         Selector_Name =>
4304                           Make_Identifier (Loc, Name_uDisp_Get_Task_Id))))));
4305
4306          elsif Restricted_Profile then
4307             Rewrite (N,
4308               Build_Call_With_Task (Pref, RTE (RE_Restricted_Terminated)));
4309
4310          else
4311             Rewrite (N,
4312               Build_Call_With_Task (Pref, RTE (RE_Terminated)));
4313          end if;
4314
4315          Analyze_And_Resolve (N, Standard_Boolean);
4316       end Terminated;
4317
4318       ----------------
4319       -- To_Address --
4320       ----------------
4321
4322       --  Transforms System'To_Address (X) into unchecked conversion
4323       --  from (integral) type of X to type address.
4324
4325       when Attribute_To_Address =>
4326          Rewrite (N,
4327            Unchecked_Convert_To (RTE (RE_Address),
4328              Relocate_Node (First (Exprs))));
4329          Analyze_And_Resolve (N, RTE (RE_Address));
4330
4331       ----------------
4332       -- Truncation --
4333       ----------------
4334
4335       --  Transforms 'Truncation into a call to the floating-point attribute
4336       --  function Truncation in Fat_xxx (where xxx is the root type).
4337       --  Expansion is avoided for cases the back end can handle directly.
4338
4339       when Attribute_Truncation =>
4340          if not Is_Inline_Floating_Point_Attribute (N) then
4341             Expand_Fpt_Attribute_R (N);
4342          end if;
4343
4344       -----------------------
4345       -- Unbiased_Rounding --
4346       -----------------------
4347
4348       --  Transforms 'Unbiased_Rounding into a call to the floating-point
4349       --  attribute function Unbiased_Rounding in Fat_xxx (where xxx is the
4350       --  root type). Expansion is avoided for cases the back end can handle
4351       --  directly.
4352
4353       when Attribute_Unbiased_Rounding =>
4354          if not Is_Inline_Floating_Point_Attribute (N) then
4355             Expand_Fpt_Attribute_R (N);
4356          end if;
4357
4358       -----------------
4359       -- UET_Address --
4360       -----------------
4361
4362       when Attribute_UET_Address => UET_Address : declare
4363          Ent : constant Entity_Id :=
4364                  Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
4365
4366       begin
4367          Insert_Action (N,
4368            Make_Object_Declaration (Loc,
4369              Defining_Identifier => Ent,
4370              Aliased_Present     => True,
4371              Object_Definition   =>
4372                New_Occurrence_Of (RTE (RE_Address), Loc)));
4373
4374          --  Construct name __gnat_xxx__SDP, where xxx is the unit name
4375          --  in normal external form.
4376
4377          Get_External_Unit_Name_String (Get_Unit_Name (Pref));
4378          Name_Buffer (1 + 7 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
4379          Name_Len := Name_Len + 7;
4380          Name_Buffer (1 .. 7) := "__gnat_";
4381          Name_Buffer (Name_Len + 1 .. Name_Len + 5) := "__SDP";
4382          Name_Len := Name_Len + 5;
4383
4384          Set_Is_Imported (Ent);
4385          Set_Interface_Name (Ent,
4386            Make_String_Literal (Loc,
4387              Strval => String_From_Name_Buffer));
4388
4389          --  Set entity as internal to ensure proper Sprint output of its
4390          --  implicit importation.
4391
4392          Set_Is_Internal (Ent);
4393
4394          Rewrite (N,
4395            Make_Attribute_Reference (Loc,
4396              Prefix => New_Occurrence_Of (Ent, Loc),
4397              Attribute_Name => Name_Address));
4398
4399          Analyze_And_Resolve (N, Typ);
4400       end UET_Address;
4401
4402       ---------------
4403       -- VADS_Size --
4404       ---------------
4405
4406       --  The processing for VADS_Size is shared with Size
4407
4408       ---------
4409       -- Val --
4410       ---------
4411
4412       --  For enumeration types with a standard representation, and for all
4413       --  other types, Val is handled by Gigi. For enumeration types with
4414       --  a non-standard representation we use the _Pos_To_Rep array that
4415       --  was created when the type was frozen.
4416
4417       when Attribute_Val => Val :
4418       declare
4419          Etyp : constant Entity_Id := Base_Type (Entity (Pref));
4420
4421       begin
4422          if Is_Enumeration_Type (Etyp)
4423            and then Present (Enum_Pos_To_Rep (Etyp))
4424          then
4425             if Has_Contiguous_Rep (Etyp) then
4426                declare
4427                   Rep_Node : constant Node_Id :=
4428                     Unchecked_Convert_To (Etyp,
4429                        Make_Op_Add (Loc,
4430                          Left_Opnd =>
4431                             Make_Integer_Literal (Loc,
4432                               Enumeration_Rep (First_Literal (Etyp))),
4433                          Right_Opnd =>
4434                           (Convert_To (Standard_Integer,
4435                              Relocate_Node (First (Exprs))))));
4436
4437                begin
4438                   Rewrite (N,
4439                      Unchecked_Convert_To (Etyp,
4440                          Make_Op_Add (Loc,
4441                            Left_Opnd =>
4442                              Make_Integer_Literal (Loc,
4443                                Enumeration_Rep (First_Literal (Etyp))),
4444                            Right_Opnd =>
4445                              Make_Function_Call (Loc,
4446                                Name =>
4447                                  New_Reference_To
4448                                    (TSS (Etyp, TSS_Rep_To_Pos), Loc),
4449                                Parameter_Associations => New_List (
4450                                  Rep_Node,
4451                                  Rep_To_Pos_Flag (Etyp, Loc))))));
4452                end;
4453
4454             else
4455                Rewrite (N,
4456                  Make_Indexed_Component (Loc,
4457                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Etyp), Loc),
4458                    Expressions => New_List (
4459                      Convert_To (Standard_Integer,
4460                        Relocate_Node (First (Exprs))))));
4461             end if;
4462
4463             Analyze_And_Resolve (N, Typ);
4464          end if;
4465       end Val;
4466
4467       -----------
4468       -- Valid --
4469       -----------
4470
4471       --  The code for valid is dependent on the particular types involved.
4472       --  See separate sections below for the generated code in each case.
4473
4474       when Attribute_Valid => Valid :
4475       declare
4476          Ptyp : constant Entity_Id  := Etype (Pref);
4477          Btyp : Entity_Id           := Base_Type (Ptyp);
4478          Tst  : Node_Id;
4479
4480          Save_Validity_Checks_On : constant Boolean := Validity_Checks_On;
4481          --  Save the validity checking mode. We always turn off validity
4482          --  checking during process of 'Valid since this is one place
4483          --  where we do not want the implicit validity checks to intefere
4484          --  with the explicit validity check that the programmer is doing.
4485
4486          function Make_Range_Test return Node_Id;
4487          --  Build the code for a range test of the form
4488          --    Btyp!(Pref) >= Btyp!(Ptyp'First)
4489          --      and then
4490          --    Btyp!(Pref) <= Btyp!(Ptyp'Last)
4491
4492          ---------------------
4493          -- Make_Range_Test --
4494          ---------------------
4495
4496          function Make_Range_Test return Node_Id is
4497          begin
4498             return
4499               Make_And_Then (Loc,
4500                 Left_Opnd =>
4501                   Make_Op_Ge (Loc,
4502                     Left_Opnd =>
4503                       Unchecked_Convert_To (Btyp, Duplicate_Subexpr (Pref)),
4504
4505                     Right_Opnd =>
4506                       Unchecked_Convert_To (Btyp,
4507                         Make_Attribute_Reference (Loc,
4508                           Prefix => New_Occurrence_Of (Ptyp, Loc),
4509                           Attribute_Name => Name_First))),
4510
4511                 Right_Opnd =>
4512                   Make_Op_Le (Loc,
4513                     Left_Opnd =>
4514                       Unchecked_Convert_To (Btyp,
4515                         Duplicate_Subexpr_No_Checks (Pref)),
4516
4517                     Right_Opnd =>
4518                       Unchecked_Convert_To (Btyp,
4519                         Make_Attribute_Reference (Loc,
4520                           Prefix => New_Occurrence_Of (Ptyp, Loc),
4521                           Attribute_Name => Name_Last))));
4522          end Make_Range_Test;
4523
4524       --  Start of processing for Attribute_Valid
4525
4526       begin
4527          --  Turn off validity checks. We do not want any implicit validity
4528          --  checks to intefere with the explicit check from the attribute
4529
4530          Validity_Checks_On := False;
4531
4532          --  Floating-point case. This case is handled by the Valid attribute
4533          --  code in the floating-point attribute run-time library.
4534
4535          if Is_Floating_Point_Type (Ptyp) then
4536             declare
4537                Pkg : RE_Id;
4538                Ftp : Entity_Id;
4539
4540             begin
4541                --  For vax fpt types, call appropriate routine in special vax
4542                --  floating point unit. We do not have to worry about loads in
4543                --  this case, since these types have no signalling NaN's.
4544
4545                if Vax_Float (Btyp) then
4546                   Expand_Vax_Valid (N);
4547
4548                --  The AAMP back end handles Valid for floating-point types
4549
4550                elsif Is_AAMP_Float (Btyp) then
4551                   Analyze_And_Resolve (Pref, Ptyp);
4552                   Set_Etype (N, Standard_Boolean);
4553                   Set_Analyzed (N);
4554
4555                --  Non VAX float case
4556
4557                else
4558                   Find_Fat_Info (Etype (Pref), Ftp, Pkg);
4559
4560                   --  If the floating-point object might be unaligned, we need
4561                   --  to call the special routine Unaligned_Valid, which makes
4562                   --  the needed copy, being careful not to load the value into
4563                   --  any floating-point register. The argument in this case is
4564                   --  obj'Address (see Unaligned_Valid routine in Fat_Gen).
4565
4566                   if Is_Possibly_Unaligned_Object (Pref) then
4567                      Expand_Fpt_Attribute
4568                        (N, Pkg, Name_Unaligned_Valid,
4569                         New_List (
4570                           Make_Attribute_Reference (Loc,
4571                             Prefix => Relocate_Node (Pref),
4572                             Attribute_Name => Name_Address)));
4573
4574                   --  In the normal case where we are sure the object is
4575                   --  aligned, we generate a call to Valid, and the argument in
4576                   --  this case is obj'Unrestricted_Access (after converting
4577                   --  obj to the right floating-point type).
4578
4579                   else
4580                      Expand_Fpt_Attribute
4581                        (N, Pkg, Name_Valid,
4582                         New_List (
4583                           Make_Attribute_Reference (Loc,
4584                             Prefix => Unchecked_Convert_To (Ftp, Pref),
4585                             Attribute_Name => Name_Unrestricted_Access)));
4586                   end if;
4587                end if;
4588
4589                --  One more task, we still need a range check. Required
4590                --  only if we have a constraint, since the Valid routine
4591                --  catches infinities properly (infinities are never valid).
4592
4593                --  The way we do the range check is simply to create the
4594                --  expression: Valid (N) and then Base_Type(Pref) in Typ.
4595
4596                if not Subtypes_Statically_Match (Ptyp, Btyp) then
4597                   Rewrite (N,
4598                     Make_And_Then (Loc,
4599                       Left_Opnd  => Relocate_Node (N),
4600                       Right_Opnd =>
4601                         Make_In (Loc,
4602                           Left_Opnd => Convert_To (Btyp, Pref),
4603                           Right_Opnd => New_Occurrence_Of (Ptyp, Loc))));
4604                end if;
4605             end;
4606
4607          --  Enumeration type with holes
4608
4609          --  For enumeration types with holes, the Pos value constructed by
4610          --  the Enum_Rep_To_Pos function built in Exp_Ch3 called with a
4611          --  second argument of False returns minus one for an invalid value,
4612          --  and the non-negative pos value for a valid value, so the
4613          --  expansion of X'Valid is simply:
4614
4615          --     type(X)'Pos (X) >= 0
4616
4617          --  We can't quite generate it that way because of the requirement
4618          --  for the non-standard second argument of False in the resulting
4619          --  rep_to_pos call, so we have to explicitly create:
4620
4621          --     _rep_to_pos (X, False) >= 0
4622
4623          --  If we have an enumeration subtype, we also check that the
4624          --  value is in range:
4625
4626          --    _rep_to_pos (X, False) >= 0
4627          --      and then
4628          --       (X >= type(X)'First and then type(X)'Last <= X)
4629
4630          elsif Is_Enumeration_Type (Ptyp)
4631            and then Present (Enum_Pos_To_Rep (Base_Type (Ptyp)))
4632          then
4633             Tst :=
4634               Make_Op_Ge (Loc,
4635                 Left_Opnd =>
4636                   Make_Function_Call (Loc,
4637                     Name =>
4638                       New_Reference_To
4639                         (TSS (Base_Type (Ptyp), TSS_Rep_To_Pos), Loc),
4640                     Parameter_Associations => New_List (
4641                       Pref,
4642                       New_Occurrence_Of (Standard_False, Loc))),
4643                 Right_Opnd => Make_Integer_Literal (Loc, 0));
4644
4645             if Ptyp /= Btyp
4646               and then
4647                 (Type_Low_Bound (Ptyp) /= Type_Low_Bound (Btyp)
4648                   or else
4649                  Type_High_Bound (Ptyp) /= Type_High_Bound (Btyp))
4650             then
4651                --  The call to Make_Range_Test will create declarations
4652                --  that need a proper insertion point, but Pref is now
4653                --  attached to a node with no ancestor. Attach to tree
4654                --  even if it is to be rewritten below.
4655
4656                Set_Parent (Tst, Parent (N));
4657
4658                Tst :=
4659                  Make_And_Then (Loc,
4660                    Left_Opnd  => Make_Range_Test,
4661                    Right_Opnd => Tst);
4662             end if;
4663
4664             Rewrite (N, Tst);
4665
4666          --  Fortran convention booleans
4667
4668          --  For the very special case of Fortran convention booleans, the
4669          --  value is always valid, since it is an integer with the semantics
4670          --  that non-zero is true, and any value is permissible.
4671
4672          elsif Is_Boolean_Type (Ptyp)
4673            and then Convention (Ptyp) = Convention_Fortran
4674          then
4675             Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
4676
4677          --  For biased representations, we will be doing an unchecked
4678          --  conversion without unbiasing the result. That means that the range
4679          --  test has to take this into account, and the proper form of the
4680          --  test is:
4681
4682          --    Btyp!(Pref) < Btyp!(Ptyp'Range_Length)
4683
4684          elsif Has_Biased_Representation (Ptyp) then
4685             Btyp := RTE (RE_Unsigned_32);
4686             Rewrite (N,
4687               Make_Op_Lt (Loc,
4688                 Left_Opnd =>
4689                   Unchecked_Convert_To (Btyp, Duplicate_Subexpr (Pref)),
4690                 Right_Opnd =>
4691                   Unchecked_Convert_To (Btyp,
4692                     Make_Attribute_Reference (Loc,
4693                       Prefix => New_Occurrence_Of (Ptyp, Loc),
4694                       Attribute_Name => Name_Range_Length))));
4695
4696          --  For all other scalar types, what we want logically is a
4697          --  range test:
4698
4699          --     X in type(X)'First .. type(X)'Last
4700
4701          --  But that's precisely what won't work because of possible
4702          --  unwanted optimization (and indeed the basic motivation for
4703          --  the Valid attribute is exactly that this test does not work!)
4704          --  What will work is:
4705
4706          --     Btyp!(X) >= Btyp!(type(X)'First)
4707          --       and then
4708          --     Btyp!(X) <= Btyp!(type(X)'Last)
4709
4710          --  where Btyp is an integer type large enough to cover the full
4711          --  range of possible stored values (i.e. it is chosen on the basis
4712          --  of the size of the type, not the range of the values). We write
4713          --  this as two tests, rather than a range check, so that static
4714          --  evaluation will easily remove either or both of the checks if
4715          --  they can be -statically determined to be true (this happens
4716          --  when the type of X is static and the range extends to the full
4717          --  range of stored values).
4718
4719          --  Unsigned types. Note: it is safe to consider only whether the
4720          --  subtype is unsigned, since we will in that case be doing all
4721          --  unsigned comparisons based on the subtype range. Since we use the
4722          --  actual subtype object size, this is appropriate.
4723
4724          --  For example, if we have
4725
4726          --    subtype x is integer range 1 .. 200;
4727          --    for x'Object_Size use 8;
4728
4729          --  Now the base type is signed, but objects of this type are bits
4730          --  unsigned, and doing an unsigned test of the range 1 to 200 is
4731          --  correct, even though a value greater than 127 looks signed to a
4732          --  signed comparison.
4733
4734          elsif Is_Unsigned_Type (Ptyp) then
4735             if Esize (Ptyp) <= 32 then
4736                Btyp := RTE (RE_Unsigned_32);
4737             else
4738                Btyp := RTE (RE_Unsigned_64);
4739             end if;
4740
4741             Rewrite (N, Make_Range_Test);
4742
4743          --  Signed types
4744
4745          else
4746             if Esize (Ptyp) <= Esize (Standard_Integer) then
4747                Btyp := Standard_Integer;
4748             else
4749                Btyp := Universal_Integer;
4750             end if;
4751
4752             Rewrite (N, Make_Range_Test);
4753          end if;
4754
4755          Analyze_And_Resolve (N, Standard_Boolean);
4756          Validity_Checks_On := Save_Validity_Checks_On;
4757       end Valid;
4758
4759       -----------
4760       -- Value --
4761       -----------
4762
4763       --  Value attribute is handled in separate unti Exp_Imgv
4764
4765       when Attribute_Value =>
4766          Exp_Imgv.Expand_Value_Attribute (N);
4767
4768       -----------------
4769       -- Value_Size --
4770       -----------------
4771
4772       --  The processing for Value_Size shares the processing for Size
4773
4774       -------------
4775       -- Version --
4776       -------------
4777
4778       --  The processing for Version shares the processing for Body_Version
4779
4780       ----------------
4781       -- Wide_Image --
4782       ----------------
4783
4784       --  Wide_Image attribute is handled in separate unit Exp_Imgv
4785
4786       when Attribute_Wide_Image =>
4787          Exp_Imgv.Expand_Wide_Image_Attribute (N);
4788
4789       ---------------------
4790       -- Wide_Wide_Image --
4791       ---------------------
4792
4793       --  Wide_Wide_Image attribute is handled in separate unit Exp_Imgv
4794
4795       when Attribute_Wide_Wide_Image =>
4796          Exp_Imgv.Expand_Wide_Wide_Image_Attribute (N);
4797
4798       ----------------
4799       -- Wide_Value --
4800       ----------------
4801
4802       --  We expand typ'Wide_Value (X) into
4803
4804       --    typ'Value
4805       --      (Wide_String_To_String (X, Wide_Character_Encoding_Method))
4806
4807       --  Wide_String_To_String is a runtime function that converts its wide
4808       --  string argument to String, converting any non-translatable characters
4809       --  into appropriate escape sequences. This preserves the required
4810       --  semantics of Wide_Value in all cases, and results in a very simple
4811       --  implementation approach.
4812
4813       --  Note: for this approach to be fully standard compliant for the cases
4814       --  where typ is Wide_Character and Wide_Wide_Character, the encoding
4815       --  method must cover the entire character range (e.g. UTF-8). But that
4816       --  is a reasonable requirement when dealing with encoded character
4817       --  sequences. Presumably if one of the restrictive encoding mechanisms
4818       --  is in use such as Shift-JIS, then characters that cannot be
4819       --  represented using this encoding will not appear in any case.
4820
4821       when Attribute_Wide_Value => Wide_Value :
4822       begin
4823          Rewrite (N,
4824            Make_Attribute_Reference (Loc,
4825              Prefix         => Pref,
4826              Attribute_Name => Name_Value,
4827
4828              Expressions    => New_List (
4829                Make_Function_Call (Loc,
4830                  Name =>
4831                    New_Reference_To (RTE (RE_Wide_String_To_String), Loc),
4832
4833                  Parameter_Associations => New_List (
4834                    Relocate_Node (First (Exprs)),
4835                    Make_Integer_Literal (Loc,
4836                      Intval => Int (Wide_Character_Encoding_Method)))))));
4837
4838          Analyze_And_Resolve (N, Typ);
4839       end Wide_Value;
4840
4841       ---------------------
4842       -- Wide_Wide_Value --
4843       ---------------------
4844
4845       --  We expand typ'Wide_Value_Value (X) into
4846
4847       --    typ'Value
4848       --      (Wide_Wide_String_To_String (X, Wide_Character_Encoding_Method))
4849
4850       --  Wide_Wide_String_To_String is a runtime function that converts its
4851       --  wide string argument to String, converting any non-translatable
4852       --  characters into appropriate escape sequences. This preserves the
4853       --  required semantics of Wide_Wide_Value in all cases, and results in a
4854       --  very simple implementation approach.
4855
4856       --  It's not quite right where typ = Wide_Wide_Character, because the
4857       --  encoding method may not cover the whole character type ???
4858
4859       when Attribute_Wide_Wide_Value => Wide_Wide_Value :
4860       begin
4861          Rewrite (N,
4862            Make_Attribute_Reference (Loc,
4863              Prefix         => Pref,
4864              Attribute_Name => Name_Value,
4865
4866              Expressions    => New_List (
4867                Make_Function_Call (Loc,
4868                  Name =>
4869                    New_Reference_To (RTE (RE_Wide_Wide_String_To_String), Loc),
4870
4871                  Parameter_Associations => New_List (
4872                    Relocate_Node (First (Exprs)),
4873                    Make_Integer_Literal (Loc,
4874                      Intval => Int (Wide_Character_Encoding_Method)))))));
4875
4876          Analyze_And_Resolve (N, Typ);
4877       end Wide_Wide_Value;
4878
4879       ---------------------
4880       -- Wide_Wide_Width --
4881       ---------------------
4882
4883       --  Wide_Wide_Width attribute is handled in separate unit Exp_Imgv
4884
4885       when Attribute_Wide_Wide_Width =>
4886          Exp_Imgv.Expand_Width_Attribute (N, Wide_Wide);
4887
4888       ----------------
4889       -- Wide_Width --
4890       ----------------
4891
4892       --  Wide_Width attribute is handled in separate unit Exp_Imgv
4893
4894       when Attribute_Wide_Width =>
4895          Exp_Imgv.Expand_Width_Attribute (N, Wide);
4896
4897       -----------
4898       -- Width --
4899       -----------
4900
4901       --  Width attribute is handled in separate unit Exp_Imgv
4902
4903       when Attribute_Width =>
4904          Exp_Imgv.Expand_Width_Attribute (N, Normal);
4905
4906       -----------
4907       -- Write --
4908       -----------
4909
4910       when Attribute_Write => Write : declare
4911          P_Type : constant Entity_Id := Entity (Pref);
4912          U_Type : constant Entity_Id := Underlying_Type (P_Type);
4913          Pname  : Entity_Id;
4914          Decl   : Node_Id;
4915          Prag   : Node_Id;
4916          Arg3   : Node_Id;
4917          Wfunc  : Node_Id;
4918
4919       begin
4920          --  If no underlying type, we have an error that will be diagnosed
4921          --  elsewhere, so here we just completely ignore the expansion.
4922
4923          if No (U_Type) then
4924             return;
4925          end if;
4926
4927          --  The simple case, if there is a TSS for Write, just call it
4928
4929          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Write);
4930
4931          if Present (Pname) then
4932             null;
4933
4934          else
4935             --  If there is a Stream_Convert pragma, use it, we rewrite
4936
4937             --     sourcetyp'Output (stream, Item)
4938
4939             --  as
4940
4941             --     strmtyp'Output (Stream, strmwrite (acttyp (Item)));
4942
4943             --  where strmwrite is the given Write function that converts an
4944             --  argument of type sourcetyp or a type acctyp, from which it is
4945             --  derived to type strmtyp. The conversion to acttyp is required
4946             --  for the derived case.
4947
4948             Prag := Get_Stream_Convert_Pragma (P_Type);
4949
4950             if Present (Prag) then
4951                Arg3 :=
4952                  Next (Next (First (Pragma_Argument_Associations (Prag))));
4953                Wfunc := Entity (Expression (Arg3));
4954
4955                Rewrite (N,
4956                  Make_Attribute_Reference (Loc,
4957                    Prefix => New_Occurrence_Of (Etype (Wfunc), Loc),
4958                    Attribute_Name => Name_Output,
4959                    Expressions => New_List (
4960                      Relocate_Node (First (Exprs)),
4961                      Make_Function_Call (Loc,
4962                        Name => New_Occurrence_Of (Wfunc, Loc),
4963                        Parameter_Associations => New_List (
4964                          OK_Convert_To (Etype (First_Formal (Wfunc)),
4965                            Relocate_Node (Next (First (Exprs)))))))));
4966
4967                Analyze (N);
4968                return;
4969
4970             --  For elementary types, we call the W_xxx routine directly
4971
4972             elsif Is_Elementary_Type (U_Type) then
4973                Rewrite (N, Build_Elementary_Write_Call (N));
4974                Analyze (N);
4975                return;
4976
4977             --  Array type case
4978
4979             elsif Is_Array_Type (U_Type) then
4980                Build_Array_Write_Procedure (N, U_Type, Decl, Pname);
4981                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
4982
4983             --  Tagged type case, use the primitive Write function. Note that
4984             --  this will dispatch in the class-wide case which is what we want
4985
4986             elsif Is_Tagged_Type (U_Type) then
4987                Pname := Find_Prim_Op (U_Type, TSS_Stream_Write);
4988
4989             --  All other record type cases, including protected records.
4990             --  The latter only arise for expander generated code for
4991             --  handling shared passive partition access.
4992
4993             else
4994                pragma Assert
4995                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
4996
4997                --  Ada 2005 (AI-216): Program_Error is raised when executing
4998                --  the default implementation of the Write attribute of an
4999                --  Unchecked_Union type. However, if the 'Write reference is
5000                --  within the generated Output stream procedure, Write outputs
5001                --  the components, and the default values of the discriminant
5002                --  are streamed by the Output procedure itself.
5003
5004                if Is_Unchecked_Union (Base_Type (U_Type))
5005                  and not Is_TSS (Current_Scope, TSS_Stream_Output)
5006                then
5007                   Insert_Action (N,
5008                     Make_Raise_Program_Error (Loc,
5009                       Reason => PE_Unchecked_Union_Restriction));
5010                end if;
5011
5012                if Has_Discriminants (U_Type)
5013                  and then Present
5014                    (Discriminant_Default_Value (First_Discriminant (U_Type)))
5015                then
5016                   Build_Mutable_Record_Write_Procedure
5017                     (Loc, Base_Type (U_Type), Decl, Pname);
5018                else
5019                   Build_Record_Write_Procedure
5020                     (Loc, Base_Type (U_Type), Decl, Pname);
5021                end if;
5022
5023                Insert_Action (N, Decl);
5024             end if;
5025          end if;
5026
5027          --  If we fall through, Pname is the procedure to be called
5028
5029          Rewrite_Stream_Proc_Call (Pname);
5030       end Write;
5031
5032       --  Component_Size is handled by Gigi, unless the component size is known
5033       --  at compile time, which is always true in the packed array case. It is
5034       --  important that the packed array case is handled in the front end (see
5035       --  Eval_Attribute) since Gigi would otherwise get confused by the
5036       --  equivalent packed array type.
5037
5038       when Attribute_Component_Size =>
5039          null;
5040
5041       --  The following attributes are handled by the back end (except that
5042       --  static cases have already been evaluated during semantic processing,
5043       --  but in any case the back end should not count on this). The one bit
5044       --  of special processing required is that these attributes typically
5045       --  generate conditionals in the code, so we need to check the relevant
5046       --  restriction.
5047
5048       when Attribute_Max                          |
5049            Attribute_Min                          =>
5050          Check_Restriction (No_Implicit_Conditionals, N);
5051
5052       --  The following attributes are handled by the back end (except that
5053       --  static cases have already been evaluated during semantic processing,
5054       --  but in any case the back end should not count on this).
5055
5056       --  Gigi also handles the non-class-wide cases of Size
5057
5058       when Attribute_Bit_Order                    |
5059            Attribute_Code_Address                 |
5060            Attribute_Definite                     |
5061            Attribute_Null_Parameter               |
5062            Attribute_Passed_By_Reference          |
5063            Attribute_Pool_Address                 =>
5064          null;
5065
5066       --  The following attributes are also handled by Gigi, but return a
5067       --  universal integer result, so may need a conversion for checking
5068       --  that the result is in range.
5069
5070       when Attribute_Aft                          |
5071            Attribute_Bit                          |
5072            Attribute_Max_Size_In_Storage_Elements
5073       =>
5074          Apply_Universal_Integer_Attribute_Checks (N);
5075
5076       --  The following attributes should not appear at this stage, since they
5077       --  have already been handled by the analyzer (and properly rewritten
5078       --  with corresponding values or entities to represent the right values)
5079
5080       when Attribute_Abort_Signal                 |
5081            Attribute_Address_Size                 |
5082            Attribute_Base                         |
5083            Attribute_Class                        |
5084            Attribute_Default_Bit_Order            |
5085            Attribute_Delta                        |
5086            Attribute_Denorm                       |
5087            Attribute_Digits                       |
5088            Attribute_Emax                         |
5089            Attribute_Enabled                      |
5090            Attribute_Epsilon                      |
5091            Attribute_Fast_Math                    |
5092            Attribute_Has_Access_Values            |
5093            Attribute_Has_Discriminants            |
5094            Attribute_Large                        |
5095            Attribute_Machine_Emax                 |
5096            Attribute_Machine_Emin                 |
5097            Attribute_Machine_Mantissa             |
5098            Attribute_Machine_Overflows            |
5099            Attribute_Machine_Radix                |
5100            Attribute_Machine_Rounds               |
5101            Attribute_Maximum_Alignment            |
5102            Attribute_Model_Emin                   |
5103            Attribute_Model_Epsilon                |
5104            Attribute_Model_Mantissa               |
5105            Attribute_Model_Small                  |
5106            Attribute_Modulus                      |
5107            Attribute_Partition_ID                 |
5108            Attribute_Range                        |
5109            Attribute_Safe_Emax                    |
5110            Attribute_Safe_First                   |
5111            Attribute_Safe_Large                   |
5112            Attribute_Safe_Last                    |
5113            Attribute_Safe_Small                   |
5114            Attribute_Scale                        |
5115            Attribute_Signed_Zeros                 |
5116            Attribute_Small                        |
5117            Attribute_Storage_Unit                 |
5118            Attribute_Stub_Type                    |
5119            Attribute_Target_Name                  |
5120            Attribute_Type_Class                   |
5121            Attribute_Unconstrained_Array          |
5122            Attribute_Universal_Literal_String     |
5123            Attribute_Wchar_T_Size                 |
5124            Attribute_Word_Size                    =>
5125
5126          raise Program_Error;
5127
5128       --  The Asm_Input and Asm_Output attributes are not expanded at this
5129       --  stage, but will be eliminated in the expansion of the Asm call,
5130       --  see Exp_Intr for details. So Gigi will never see these either.
5131
5132       when Attribute_Asm_Input                    |
5133            Attribute_Asm_Output                   =>
5134
5135          null;
5136
5137       end case;
5138
5139    exception
5140       when RE_Not_Available =>
5141          return;
5142    end Expand_N_Attribute_Reference;
5143
5144    ----------------------
5145    -- Expand_Pred_Succ --
5146    ----------------------
5147
5148    --  For typ'Pred (exp), we generate the check
5149
5150    --    [constraint_error when exp = typ'Base'First]
5151
5152    --  Similarly, for typ'Succ (exp), we generate the check
5153
5154    --    [constraint_error when exp = typ'Base'Last]
5155
5156    --  These checks are not generated for modular types, since the proper
5157    --  semantics for Succ and Pred on modular types is to wrap, not raise CE.
5158
5159    procedure Expand_Pred_Succ (N : Node_Id) is
5160       Loc  : constant Source_Ptr := Sloc (N);
5161       Cnam : Name_Id;
5162
5163    begin
5164       if Attribute_Name (N) = Name_Pred then
5165          Cnam := Name_First;
5166       else
5167          Cnam := Name_Last;
5168       end if;
5169
5170       Insert_Action (N,
5171         Make_Raise_Constraint_Error (Loc,
5172           Condition =>
5173             Make_Op_Eq (Loc,
5174               Left_Opnd =>
5175                 Duplicate_Subexpr_Move_Checks (First (Expressions (N))),
5176               Right_Opnd =>
5177                 Make_Attribute_Reference (Loc,
5178                   Prefix =>
5179                     New_Reference_To (Base_Type (Etype (Prefix (N))), Loc),
5180                   Attribute_Name => Cnam)),
5181           Reason => CE_Overflow_Check_Failed));
5182    end Expand_Pred_Succ;
5183
5184    -------------------
5185    -- Find_Fat_Info --
5186    -------------------
5187
5188    procedure Find_Fat_Info
5189      (T        : Entity_Id;
5190       Fat_Type : out Entity_Id;
5191       Fat_Pkg  : out RE_Id)
5192    is
5193       Btyp : constant Entity_Id := Base_Type (T);
5194       Rtyp : constant Entity_Id := Root_Type (T);
5195       Digs : constant Nat       := UI_To_Int (Digits_Value (Btyp));
5196
5197    begin
5198       --  If the base type is VAX float, then get appropriate VAX float type
5199
5200       if Vax_Float (Btyp) then
5201          case Digs is
5202             when 6 =>
5203                Fat_Type := RTE (RE_Fat_VAX_F);
5204                Fat_Pkg  := RE_Attr_VAX_F_Float;
5205
5206             when 9 =>
5207                Fat_Type := RTE (RE_Fat_VAX_D);
5208                Fat_Pkg  := RE_Attr_VAX_D_Float;
5209
5210             when 15 =>
5211                Fat_Type := RTE (RE_Fat_VAX_G);
5212                Fat_Pkg  := RE_Attr_VAX_G_Float;
5213
5214             when others =>
5215                raise Program_Error;
5216          end case;
5217
5218       --  If root type is VAX float, this is the case where the library has
5219       --  been recompiled in VAX float mode, and we have an IEEE float type.
5220       --  This is when we use the special IEEE Fat packages.
5221
5222       elsif Vax_Float (Rtyp) then
5223          case Digs is
5224             when 6 =>
5225                Fat_Type := RTE (RE_Fat_IEEE_Short);
5226                Fat_Pkg  := RE_Attr_IEEE_Short;
5227
5228             when 15 =>
5229                Fat_Type := RTE (RE_Fat_IEEE_Long);
5230                Fat_Pkg  := RE_Attr_IEEE_Long;
5231
5232             when others =>
5233                raise Program_Error;
5234          end case;
5235
5236       --  If neither the base type nor the root type is VAX_Float then VAX
5237       --  float is out of the picture, and we can just use the root type.
5238
5239       else
5240          Fat_Type := Rtyp;
5241
5242          if Fat_Type = Standard_Short_Float then
5243             Fat_Pkg := RE_Attr_Short_Float;
5244
5245          elsif Fat_Type = Standard_Float then
5246             Fat_Pkg := RE_Attr_Float;
5247
5248          elsif Fat_Type = Standard_Long_Float then
5249             Fat_Pkg := RE_Attr_Long_Float;
5250
5251          elsif Fat_Type = Standard_Long_Long_Float then
5252             Fat_Pkg := RE_Attr_Long_Long_Float;
5253
5254          --  Universal real (which is its own root type) is treated as being
5255          --  equivalent to Standard.Long_Long_Float, since it is defined to
5256          --  have the same precision as the longest Float type.
5257
5258          elsif Fat_Type = Universal_Real then
5259             Fat_Type := Standard_Long_Long_Float;
5260             Fat_Pkg := RE_Attr_Long_Long_Float;
5261
5262          else
5263             raise Program_Error;
5264          end if;
5265       end if;
5266    end Find_Fat_Info;
5267
5268    ----------------------------
5269    -- Find_Stream_Subprogram --
5270    ----------------------------
5271
5272    function Find_Stream_Subprogram
5273      (Typ : Entity_Id;
5274       Nam : TSS_Name_Type) return Entity_Id
5275    is
5276       Ent : constant Entity_Id := TSS (Typ, Nam);
5277    begin
5278       if Present (Ent) then
5279          return Ent;
5280       end if;
5281
5282       if Is_Tagged_Type (Typ)
5283         and then Is_Derived_Type (Typ)
5284       then
5285          return Find_Prim_Op (Typ, Nam);
5286       else
5287          return Find_Inherited_TSS (Typ, Nam);
5288       end if;
5289    end Find_Stream_Subprogram;
5290
5291    -----------------------
5292    -- Get_Index_Subtype --
5293    -----------------------
5294
5295    function Get_Index_Subtype (N : Node_Id) return Node_Id is
5296       P_Type : Entity_Id := Etype (Prefix (N));
5297       Indx   : Node_Id;
5298       J      : Int;
5299
5300    begin
5301       if Is_Access_Type (P_Type) then
5302          P_Type := Designated_Type (P_Type);
5303       end if;
5304
5305       if No (Expressions (N)) then
5306          J := 1;
5307       else
5308          J := UI_To_Int (Expr_Value (First (Expressions (N))));
5309       end if;
5310
5311       Indx := First_Index (P_Type);
5312       while J > 1 loop
5313          Next_Index (Indx);
5314          J := J - 1;
5315       end loop;
5316
5317       return Etype (Indx);
5318    end Get_Index_Subtype;
5319
5320    -------------------------------
5321    -- Get_Stream_Convert_Pragma --
5322    -------------------------------
5323
5324    function Get_Stream_Convert_Pragma (T : Entity_Id) return Node_Id is
5325       Typ : Entity_Id;
5326       N   : Node_Id;
5327
5328    begin
5329       --  Note: we cannot use Get_Rep_Pragma here because of the peculiarity
5330       --  that a stream convert pragma for a tagged type is not inherited from
5331       --  its parent. Probably what is wrong here is that it is basically
5332       --  incorrect to consider a stream convert pragma to be a representation
5333       --  pragma at all ???
5334
5335       N := First_Rep_Item (Implementation_Base_Type (T));
5336       while Present (N) loop
5337          if Nkind (N) = N_Pragma
5338            and then Pragma_Name (N) = Name_Stream_Convert
5339          then
5340             --  For tagged types this pragma is not inherited, so we
5341             --  must verify that it is defined for the given type and
5342             --  not an ancestor.
5343
5344             Typ :=
5345               Entity (Expression (First (Pragma_Argument_Associations (N))));
5346
5347             if not Is_Tagged_Type (T)
5348               or else T = Typ
5349               or else (Is_Private_Type (Typ) and then T = Full_View (Typ))
5350             then
5351                return N;
5352             end if;
5353          end if;
5354
5355          Next_Rep_Item (N);
5356       end loop;
5357
5358       return Empty;
5359    end Get_Stream_Convert_Pragma;
5360
5361    ---------------------------------
5362    -- Is_Constrained_Packed_Array --
5363    ---------------------------------
5364
5365    function Is_Constrained_Packed_Array (Typ : Entity_Id) return Boolean is
5366       Arr : Entity_Id := Typ;
5367
5368    begin
5369       if Is_Access_Type (Arr) then
5370          Arr := Designated_Type (Arr);
5371       end if;
5372
5373       return Is_Array_Type (Arr)
5374         and then Is_Constrained (Arr)
5375         and then Present (Packed_Array_Type (Arr));
5376    end Is_Constrained_Packed_Array;
5377
5378    ----------------------------------------
5379    -- Is_Inline_Floating_Point_Attribute --
5380    ----------------------------------------
5381
5382    function Is_Inline_Floating_Point_Attribute (N : Node_Id) return Boolean is
5383       Id : constant Attribute_Id := Get_Attribute_Id (Attribute_Name (N));
5384
5385    begin
5386       if Nkind (Parent (N)) /= N_Type_Conversion
5387         or else not Is_Integer_Type (Etype (Parent (N)))
5388       then
5389          return False;
5390       end if;
5391
5392       --  Should also support 'Machine_Rounding and 'Unbiased_Rounding, but
5393       --  required back end support has not been implemented yet ???
5394
5395       return Id = Attribute_Truncation;
5396    end Is_Inline_Floating_Point_Attribute;
5397
5398 end Exp_Attr;