OSDN Git Service

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