OSDN Git Service

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